summaryrefslogtreecommitdiff
path: root/lib/Properties.hs
blob: fe0085711cad1535be796c12ad523c236128de35 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
{-# LANGUAGE NamedFieldPuns    #-}
{-# LANGUAGE OverloadedStrings #-}

-- | Contains checks for custom properties of the map json
module Properties (checkProperty) where


import           Control.Monad (unless, when)
import           Data.Text     (Text, isPrefixOf)
import           Tiled2        (Layer (layerProperties), Property(..), PropertyValue(..))
import           Util          (prettyprint)

import           LintWriter    (LintWriter, complain, dependsOn, forbid, info,
                                suggest, warn)
import           Types


-- | the point of this module
--
-- given a property, check if it is valid. It gets a reference
-- to its own layer since sometimes the presense of one property
-- implies the presence or absense of another.
--
-- The tests in here are meant to comply with the informal spec
-- at https://workadventu.re/map-building
--
-- I've attempted to build the LintWriter monad in a way
-- that should make this readable even to non-Haskellers
-- TODO: also pass the value of this property directly
checkProperty :: Layer -> Property -> LintWriter ()
checkProperty layer (Property name value) = case name of
    "jitsiRoom" -> strProp $ do
      info $ "found jitsi room: " <> prettyprint value
      suggestPropertyValue "jitsiTrigger" "onaction"
    "jitsiTrigger" -> strProp $ do
      unless (hasProperty "jitsiTriggerMessage" layer)
       $ suggest "set \"jitsiTriggerMessage\" to a custom message to overwrite the default \"press SPACE to enter in jitsi meet room\""
      requireProperty "jitsiRoom"
    "jitsiTriggerMessage" -> strProp
      $ requireProperty "jitsiTrigger"
    "jitsiUrl" -> isForbidden
    "jitsiConfig" -> isForbidden
    "jitsiClientConfig" -> isForbidden
    "jitsiRoomAdminTag" -> isForbidden
    "playAudio" -> linkProp $ \link -> dependsOn $ if "https://" `isPrefixOf` link
        then Link link
        else Local link
    "audioLoop" ->
      boolProp $ requireProperty "playAudio"
    "audioVolume" ->
      boolProp $ requireProperty "playAudio"
    "openWebsite" -> do
      suggestPropertyValue "openWebsiteTrigger" "onaction"
      linkProp $ \link -> dependsOn $ if "https://" `isPrefixOf` link
          then Link link
          else Local link
    "openWebsiteTrigger" -> strProp $ do
      unless (hasProperty "openWebsiteTriggerMessage" layer)
        $ suggest "set \"openWebsiteTriggerMessage\" to a custom message to overwrite the generic \"press SPACE to open Website\""
      requireProperty "openWebsite"
    "openWebsiteTriggerMessage" ->
      strProp $ requireProperty "openWebsiteTrigger"
    "openWebsitePolicy" ->
      strProp $ requireProperty "openWebsite"
    "openTab" ->
      strProp $ requireProperty "openWebsite"
    "url" -> isForbidden
    "allowApi" -> isForbidden
    "exitUrl" -> linkProp $ \link -> dependsOn $ if "https://" `isPrefixOf` link
        then MapLink link
        else LocalMap link
    "startLayer" ->
      isForbidden
    "silent" -> boolProp $ pure ()
      -- could also make this a "hard error" (i.e. Left), but then it
      -- stops checking other properties as checkLayer short-circuits.
    _ -> warn $ "unknown property type " <> prettyprint name
    where
      strProp :: LintWriter () -> LintWriter ()
      strProp andthen = case value of
        StrProp _ -> andthen
        _ -> complain $ "type mismatch in property " <> name <> "; should be of type string"
      linkProp f = case value of
        StrProp str -> if "http://" `isPrefixOf` str
          then complain "cannot access content via http; either use https or include it locally instead."
          else f str
        _ -> complain $ "type mismatch in property " <> name <> "; should be of typ string"
      boolProp f = case value of
        BoolProp _ -> f
        _ -> complain $ "type mismatch in property " <> name <> "; should be of type bool"
      -- | require some property in this layer
      requireProperty name = unless (hasProperty name layer)
        $ complain $ "property "<>prettyprint name<>" requires property "<>prettyprint name
      -- | This property is forbidden and should not be used
      isForbidden = forbid $ "property " <> prettyprint name <> " should not be used"
      -- TODO: check if the property has the correct value
      suggestPropertyValue :: Text -> Text -> LintWriter ()
      suggestPropertyValue name value = unless (hasProperty name layer)
        $ suggest $ "set property " <> prettyprint name <> " to " <> prettyprint value




-- | does this layer have the given property?
hasProperty :: Text -> Layer -> Bool
hasProperty name = any
  (\(Property name' _) -> name' == name)
  . layerProperties