summaryrefslogtreecommitdiff
path: root/lib/Properties.hs
blob: 405e98437beda6e1706b89669cc6c5a184a89a15 (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
{-# LANGUAGE LambdaCase        #-}
{-# 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          (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
checkProperty :: Layer -> Property -> LintWriter ()
checkProperty layer (Property name value) = case name of
    "jitsiRoom" -> do
      uselessEmptyLayer
      unwrapString $ \val -> do
        info $ "found jitsi room: " <> prettyprint val
        suggestPropertyValue "jitsiTrigger" "onaction"
    "jitsiTrigger" -> do
      isString
      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" -> do
      isString
      requireProperty "jitsiTrigger"
    "jitsiUrl" -> isForbidden
    "jitsiConfig" -> isForbidden
    "jitsiClientConfig" -> isForbidden
    "jitsiRoomAdminTag" -> isForbidden
    "playAudio" -> do
      uselessEmptyLayer
      unwrapLink $ \link -> dependsOn $ if "https://" `isPrefixOf` link
        then Link link
        else Local link
    "audioLoop" -> do
      isBool
      requireProperty "playAudio"
    "audioVolume" -> do
      isBool
      requireProperty "playAudio"
    "openWebsite" -> do
      uselessEmptyLayer
      suggestPropertyValue "openWebsiteTrigger" "onaction"
      unwrapLink $ \link -> dependsOn $ if "https://" `isPrefixOf` link
        then Link link
        else Local link
    "openWebsiteTrigger" -> do
      isString
      unless (hasProperty "openWebsiteTriggerMessage" layer)
        $ suggest "set \"openWebsiteTriggerMessage\" to a custom message to overwrite the generic \"press SPACE to open Website\""
      requireProperty "openWebsite"
    "openWebsiteTriggerMessage" -> do
      isString
      requireProperty "openWebsiteTrigger"
    "openWebsitePolicy" -> do
      isString
      requireProperty "openWebsite"
    "openTab" -> do
      isString
      requireProperty "openWebsite"
    "url" -> isForbidden
    "allowApi" -> isForbidden
    "exitUrl" -> do
      forbidEmptyLayer
      unwrapLink $ \link -> dependsOn $ if "https://" `isPrefixOf` link
        then MapLink link
        else LocalMap link
    "startLayer" -> do
      forbidEmptyLayer
      unwrapBool $ \case
        True  -> pure ()
        False -> complain "startLayer must be set to true"
    "silent" -> do
      isBool
      uselessEmptyLayer
    _ ->
      complain $ "unknown property type " <> prettyprint name
    where

      -- | asserts that this property is a string, and unwraps it
      unwrapString 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 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 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 = unwrapString (const $ pure ())
      -- | just asserts  that this is a boolean
      isBool = unwrapBool (const $ pure ())


      -- | this property is forbidden and should not be used
      isForbidden = forbid $ "property " <> prettyprint name <> " should not be used"
      -- | 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")

      -- | require some property in this layer
      requireProperty name = unless (hasProperty name layer)
        $ complain $ "property "<>prettyprint name<>" requires property "<>prettyprint name
      -- | suggest a certain value for some other property in this layer
      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