summaryrefslogtreecommitdiff
path: root/lib/Properties.hs
blob: 78993cef46d3afd3990bc4ab85cccf81c64df048 (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
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
{-# LANGUAGE LambdaCase        #-}
{-# LANGUAGE NamedFieldPuns    #-}
{-# LANGUAGE OverloadedStrings #-}

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


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

import           Data.Maybe    (fromMaybe)
import           LintWriter    (LintWriter, askContext, askFileDepth, complain,
                                dependsOn, forbid, offersEntrypoint, suggest,
                                warn)
import           Paths         (RelPath (..), parsePath)
import           Types         (Dep (Link, Local, LocalMap, MapLink))


-- | Checks an entire map for "general" lints.
--
-- Note that it does /not/ call checkMapProperty; this is handled
-- seperately in CheckMap.hs, since these lints go into a different
-- field of the resulting json.
checkMap :: LintWriter Tiledmap
checkMap = do
  tiledmap <- askContext

  -- test other things
  mapM_ checkMapProperty (fromMaybe [] $ tiledmapProperties tiledmap)

  -- some layers should exist
  hasLayerNamed "start" (const True)
    "The map must have one layer named \"start\""
  hasLayerNamed "floorLayer" ((==) "objectgroup" . layerType)
    "The map must have one layer named \"floorLayer\" of type \"objectgroup\""
  hasLayer (flip containsProperty "exitUrl" . getProperties)
    "The map must contain at least one layer with the property \"exitUrl\" set"

  -- reject maps not suitable for workadventure
  unless (tiledmapOrientation tiledmap == "orthogonal")
    $ complain "The map's orientation must be set to \"orthogonal\""
  unless (tiledmapTileheight tiledmap == 32 && tiledmapTilewidth tiledmap == 32)
    $ complain "The map's tile size must be 32 by 32 pixels"
  where
    hasLayerNamed name p = hasLayer (\l -> layerName l == name && p l)
    hasLayer p err = do
      tiledmap <- askContext
      unless (any p (tiledmapLayers tiledmap))
        $ complain err


-- | 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 :: Property -> LintWriter Tiledmap
checkMapProperty (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"


-- | check an embedded tile set.
--
-- Important to collect dependency files
checkTileset ::  LintWriter Tileset
checkTileset = do
  tileset <- askContext
  -- TODO: can tilesets be non-local dependencies?
  unwrapPath (tilesetImage tileset) (dependsOn . Local)

  -- reject tilesets unsuitable for workadventure
  unless (tilesetTilewidth tileset == 32 && tilesetTileheight tileset == 32)
    $ complain $ "Tileset " <> tilesetName tileset <> " must have tile size 32×32"

  unless (tilesetImageheight tileset < 4096 && tilesetImagewidth tileset < 4096)
    $ warn $ "Tileset " <> tilesetName tileset <> " should not be larger than 4096×4096 pixels in total"

  -- TODO: check copyright!
  requireProperty "copyright"
  mapM_ checkTilesetProperty (fromMaybe [] $ tilesetProperties tileset)

checkTilesetProperty :: Property -> LintWriter Tileset
checkTilesetProperty p@(Property name value) = case name of
  "copyright" -> pure () -- only allow some licenses?
  _           -> pure () -- are there any other properties?

-- | Checks a single (custom) property of a layer
--
-- It gets a reference to its own layer since sometimes the presence
-- of one property implies the presence or absense of another.
checkLayerProperty :: Property -> LintWriter Layer
checkLayerProperty p@(Property name _value) = case name of
    "jitsiRoom" -> do
      uselessEmptyLayer
      unwrapString p $ \_val -> do
        suggestProperty $ Property "jitsiTrigger" (StrProp "onaction")
    "jitsiTrigger" -> do
      isString p
      unlessHasProperty "jitsiTriggerMessage"
       $ suggest "set \"jitsiTriggerMessage\" to a custom message to overwrite the default \"press SPACE to enter in jitsi meet room\""
      requireProperty "jitsiRoom"
    "jitsiTriggerMessage" -> do
      isString p
      requireProperty "jitsiTrigger"
    "jitsiUrl" -> isForbidden
    "jitsiConfig" -> isForbidden
    "jitsiClientConfig" -> isForbidden
    "jitsiRoomAdminTag" -> isForbidden
    "playAudio" -> do
      uselessEmptyLayer
      unwrapLink p $ \link -> if "https://" `isPrefixOf` link
        then dependsOn $ Link link
        else unwrapPath link (dependsOn . Local)
    "audioLoop" -> do
      isBool p
      requireProperty "playAudio"
    "audioVolume" -> do
      isBool p
      requireProperty "playAudio"
    "openWebsite" -> do
      uselessEmptyLayer
      suggestProperty $ Property "openWebsiteTrigger" (StrProp "onaction")
      unwrapLink p $ \link -> if "https://" `isPrefixOf` link
        then dependsOn $ Link link
        else unwrapPath link (dependsOn . Local)
    "openWebsiteTrigger" -> do
      isString p
      unlessHasProperty "openWebsiteTriggerMessage"
        $ suggest "set \"openWebsiteTriggerMessage\" to a custom message to overwrite the generic \"press SPACE to open Website\""
      requireProperty "openWebsite"
    "openWebsiteTriggerMessage" -> do
      isString p
      requireProperty "openWebsiteTrigger"
    "openWebsitePolicy" -> do
      isString p
      requireProperty "openWebsite"
    "openTab" -> do
      isString p
      requireProperty "openWebsite"
    "url" -> isForbidden
    "allowApi" -> isForbidden
    "exitUrl" -> do
      forbidEmptyLayer
      unwrapLink p $ \link -> if "https://" `isPrefixOf` link
        then dependsOn $ MapLink link
        else unwrapPath link (dependsOn . LocalMap)
    "startLayer" -> do
      forbidEmptyLayer
      layer <- askContext
      offersEntrypoint $ layerName layer
      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
      isForbidden = forbidProperty name
      requireProperty req = propertyRequiredBy req name

      -- | this property can only be used on a layer that contains at least one tiles
      forbidEmptyLayer = do
        layer <- askContext
        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 = do
        layer <- askContext
        when (layerIsEmpty layer)
          $ warn ("property" <> name <> " was set on an empty layer and is thereby useless")





--------- Helper functions & stuff ---------

unlessHasProperty :: HasProperties a => Text -> LintWriter a -> LintWriter a
unlessHasProperty name andthen = do
  layer <- askContext
  let hasprop = any (\(Property name' _) -> name == name') (getProperties layer)
  unless hasprop andthen


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



-- | require some property
requireProperty :: HasProperties a => Text -> LintWriter a
requireProperty name =
  unlessHasProperty name
  $ complain $ "property "<>prettyprint name<>" is required"

propertyRequiredBy :: HasProperties a => Text -> Text -> LintWriter a
propertyRequiredBy req by =
  unlessHasProperty req
  $ complain $ "property "<>prettyprint req<>" is required by property "<> prettyprint by


-- | suggest some value for another property if that property does not
-- also already exist
suggestProperty :: Property -> LintWriter Layer
suggestProperty (Property name value) =
  unlessHasProperty name
  $ suggest $ "set property " <> prettyprint name <> " to " <> prettyprint value





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


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

unwrapPath :: Text -> (RelPath -> LintWriter a) -> LintWriter a
unwrapPath str f = case parsePath str of
  Just p@(Path up _ _) -> do
    depth <- askFileDepth
    if up <= depth
      then f p
      else complain $ "cannot acess paths \"" <> str <> "\" which is outside your repository"
  Nothing   -> complain $ "path \"" <> str <> "\" is invalid"

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

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