summaryrefslogtreecommitdiff
path: root/lib/Properties.hs
diff options
context:
space:
mode:
authorstuebinm2021-09-16 02:27:26 +0200
committerstuebinm2021-09-16 02:27:26 +0200
commit35566bf15f43c355bdc72d62841a850a90c8ba03 (patch)
tree98ea0739e5aed68b6beff18edb23cf6c325283e5 /lib/Properties.hs
parenta27f5e365b83d88b230eb66b7032649bdb372546 (diff)
moving lots of code around
(also renaming things now that concepts seem a bit clearer)
Diffstat (limited to 'lib/Properties.hs')
-rw-r--r--lib/Properties.hs116
1 files changed, 116 insertions, 0 deletions
diff --git a/lib/Properties.hs b/lib/Properties.hs
new file mode 100644
index 0000000..0b9a71f
--- /dev/null
+++ b/lib/Properties.hs
@@ -0,0 +1,116 @@
+{-# LANGUAGE NamedFieldPuns #-}
+{-# LANGUAGE OverloadedStrings #-}
+
+-- | Contains checks for custom properties of the map json
+module Properties (checkProperty) where
+
+
+import Control.Monad (unless, when)
+import Control.Monad.Trans.Class (lift)
+import Data.Aeson as Aeson (Value (String))
+import Data.Map (Map, (!?))
+import Data.Text (Text)
+import Tiled2 (Layer (layerProperties))
+import Util (quote, showAeson)
+
+import LintWriter (Hint, LintWriter, Level(..), hint,
+ assertWarn, complain, forbid, info,
+ suggest, unwrapWarn, warn)
+
+-- | values may be anything, and are not typechecked (for now),
+-- since they may contain arbitrary json – our only guarantee
+-- is that they are named, and therefore a map.
+type Properties = Map Text Aeson.Value
+
+
+
+-- | /technically/ the main function here
+--
+-- 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
+--
+-- In practice, the actual specifiaction of what is allowed is
+-- handled in checkProperty', since apparently all possible layerProperties
+-- are strings anyways, so this just extracts that string and then
+-- calls that.
+checkProperty :: Layer -> Properties -> LintWriter ()
+checkProperty layer prop = do
+ tyObj <- lift $ getAttr prop "name"
+ ty <- lift $ case tyObj of
+ Aeson.String str -> Right str
+ _ -> Left (hint Suggestion "wtf")
+ checkProperty' layer prop ty
+
+-- | The /real/ main thing.
+--
+-- I've attempted to build the LintWriter monad in a way
+-- that should make this readable even to non-Haskellers
+checkProperty' :: Layer -> Properties -> Text -> LintWriter ()
+checkProperty' layer prop ty = case ty of
+ "jitsiRoom" -> do
+ propEqual prop "type" "string"
+ urlValue <- lift $ getAttr prop "value"
+ info $ "found jitsi room: " <> showAeson urlValue
+ suggestPropertyValue "jitsiTrigger" "onaction"
+ "jitsiTrigger" ->
+ requireProperty "jitsiRoom"
+ "jitsiUrl" -> isForbidden
+ "jitsiConfig" -> isForbidden
+ "jitsiClientConfig" -> isForbidden
+ "jitsiRoomAdminTag" -> isForbidden
+ "playAudio" -> do
+ -- TODO: check for url validity?
+ propEqual prop "type" "string"
+ "audioLoop" ->
+ requireProperty "playAudio"
+ "audioVolume" ->
+ requireProperty "playAudio"
+ "openWebsite" ->
+ suggestPropertyValue "openWebsiteTrigger" "onaction"
+ "openWebsiteTrigger" ->
+ requireProperty "openWebsite"
+ "openWebsitePolicy" ->
+ requireProperty "openWebsite"
+ "exitUrl" -> pure ()
+ "startLayer" -> 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 " <> quote ty
+ where
+ -- | require some property in this layer
+ requireProperty name = unless (hasProperty name layer)
+ $ complain $ "property "<>quote name<>" requires property "<>quote ty
+ -- | forbid some property in this layer
+ forbidProperty name = when (hasProperty name layer)
+ $ forbid $ "property " <> quote name <> " should not be used"
+ -- | This property is forbidden and should not be used
+ isForbidden = forbid $ "property " <> quote ty <> " should not be used"
+ -- TODO: check if the property has the correct value
+ suggestPropertyValue name value = unless (hasProperty name layer)
+ $ suggest $ "set property " <> quote name <> " to " <> quote value
+
+
+
+
+-- | does this layer have the given property?
+hasProperty :: Text -> Layer -> Bool
+hasProperty name = any
+ (\prop -> prop !? "name" == Just (Aeson.String name))
+ . layerProperties
+
+-- | get an attribute from a map
+getAttr :: Properties -> Text -> Either Hint Aeson.Value
+getAttr props name = unwrapWarn msg $ props !? name
+ where msg = "field " <> name <> "does not exist"
+
+-- | lint goal: the property with the given name has given value
+propEqual :: Properties -> Text -> Aeson.Value -> LintWriter ()
+propEqual props name value = do
+ value' <- lift $ getAttr props name
+ assertWarn ("field "<>name<>" has unexpected value "<>showAeson value'
+ <>", should be "<>showAeson value)
+ $ value' == value