summaryrefslogtreecommitdiff
path: root/lib/Properties.hs
blob: 0805a4ddab02195cc1f6d6b338f7aacf6181f4cc (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
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
{-# LANGUAGE LambdaCase        #-}
{-# LANGUAGE NamedFieldPuns    #-}
{-# LANGUAGE OverloadedStrings #-}

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


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

import           LintWriter    (LintWriter, complain, dependsOn, forbid, info,
                                suggest, warn)
import           Types         (Dep (Link, Local, LocalMap, MapLink))



-- | 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
checkLayerProperty :: Layer -> Property -> LintWriter ()
checkLayerProperty layer p@(Property name value) = case name of
    "jitsiRoom" -> do
      uselessEmptyLayer
      unwrapString p $ \val -> do
        info $ "found jitsi room: " <> prettyprint val
        suggestProp $ Property "jitsiTrigger" (StrProp "onaction")
    "jitsiTrigger" -> do
      isString p
      unless (hasProperty "jitsiTriggerMessage")
       $ suggest "set \"jitsiTriggerMessage\" to a custom message to overwrite the default \"press SPACE to enter in jitsi meet room\""
      requireProp "jitsiRoom"
    "jitsiTriggerMessage" -> do
      isString p
      requireProp "jitsiTrigger"
    "jitsiUrl" -> isForbidden
    "jitsiConfig" -> isForbidden
    "jitsiClientConfig" -> isForbidden
    "jitsiRoomAdminTag" -> isForbidden
    "playAudio" -> do
      uselessEmptyLayer
      unwrapLink p $ \link -> dependsOn $ if "https://" `isPrefixOf` link
        then Link link
        else Local link
    "audioLoop" -> do
      isBool p
      requireProp "playAudio"
    "audioVolume" -> do
      isBool p
      requireProp "playAudio"
    "openWebsite" -> do
      uselessEmptyLayer
      suggestProp $ Property "openWebsiteTrigger" (StrProp "onaction")
      unwrapLink p $ \link -> dependsOn $ if "https://" `isPrefixOf` link
        then Link link
        else Local link
    "openWebsiteTrigger" -> do
      isString p
      unless (hasProperty "openWebsiteTriggerMessage")
        $ suggest "set \"openWebsiteTriggerMessage\" to a custom message to overwrite the generic \"press SPACE to open Website\""
      requireProp "openWebsite"
    "openWebsiteTriggerMessage" -> do
      isString p
      requireProp "openWebsiteTrigger"
    "openWebsitePolicy" -> do
      isString p
      requireProp "openWebsite"
    "openTab" -> do
      isString p
      requireProp "openWebsite"
    "url" -> isForbidden
    "allowApi" -> isForbidden
    "exitUrl" -> do
      forbidEmptyLayer
      unwrapLink p $ \link -> dependsOn $ if "https://" `isPrefixOf` link
        then MapLink link
        else LocalMap link
    "startLayer" -> do
      forbidEmptyLayer
      unwrapBool p $ \case
        True  -> pure ()
        False -> complain "startLayer must be set to true"
    "silent" -> do
      isBool p
      uselessEmptyLayer
    _ ->
      complain $ "unknown property type " <> prettyprint name
    where
      properties = layerProperties layer
      hasProperty = containsProperty properties
      isForbidden = forbidProperty name
      requireProp = requireProperty properties
      suggestProp = suggestPropertyValue properties

      -- | this property can only be used on a layer that contains at least one tiles
      forbidEmptyLayer = when (layerIsEmpty layer)
        $ complain ("property " <> name <> " should not be set on an empty layer")
      -- | this layer is allowed, but also useless on a layer that contains no tiles
      uselessEmptyLayer = when (layerIsEmpty layer)
        $ warn ("property" <> name <> " was set on an empty layer and is thereby useless")

-- | Checks a single property of a map.
--
-- Doesn't really do all that much, but could in theory be expanded into a
-- longer function same as checkLayerProperty.
checkMapProperty :: Tiledmap -> Property -> LintWriter ()
checkMapProperty map (Property name value) = case name of
  "script" -> isForbidden
  _        -> complain $ "unknown map property " <> name
  where
    -- | this property is forbidden and should not be used
    isForbidden = forbid $ "property " <> prettyprint name <> " should not be used"





-- | does this layer have the given property?
containsProperty :: [Property] -> Text -> Bool
containsProperty props name = any
  (\(Property name' _) -> name' == name) props

-- | this property is forbidden and should not be used
forbidProperty :: Text -> LintWriter ()
forbidProperty name = forbid $ "property " <> prettyprint name <> " should not be used"


-- | asserts that this property is a string, and unwraps it
unwrapString :: Property -> (Text -> LintWriter ()) -> LintWriter ()
unwrapString (Property name value) f = case value of
  StrProp str -> f str
  _ -> complain $ "type mismatch in property " <> name <> "; should be of type string"

-- | same as unwrapString, but also forbids http:// as prefix
unwrapLink :: Property -> (Text -> LintWriter ()) -> LintWriter ()
unwrapLink (Property name value) 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"

-- | asserts that this property is a boolean, and unwraps it
unwrapBool :: Property -> (Bool -> LintWriter ()) -> LintWriter ()
unwrapBool (Property name value) f = case value of
  BoolProp b -> f b
  _ -> complain $ "type mismatch in property " <> name <> "; should be of type bool"

-- | just asserts that this is a string
isString :: Property -> LintWriter ()
isString = flip unwrapString (const $ pure ())

-- | just asserts that this is a boolean
isBool :: Property -> LintWriter ()
isBool = flip unwrapBool (const $ pure ())

-- | require some property
requireProperty :: [Property] -> Text -> LintWriter ()
requireProperty props name = unless (containsProperty props name)
  $ complain $ "property "<>prettyprint name<>" requires property "<>prettyprint name

-- | suggest soem value for another property if that property does not
-- also already exist
suggestPropertyValue :: [Property] -> Property -> LintWriter ()
suggestPropertyValue props (Property name value) = unless (containsProperty props name)
  $ suggest $ "set property " <> prettyprint name <> " to " <> prettyprint value