{-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} -- | Contains checks for custom properties of the map json module Properties (checkLayerProperty, checkMap) where import Control.Monad (unless, when) import Data.Text (Text, isPrefixOf) import Tiled2 (Layer (..), Property (..), PropertyValue (..), Tiledmap (..), Tileset (..)) 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" -- | 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 :: Tiledmap -> LintWriter () checkMap tiledmap = do -- check properties mapM_ (checkMapProperty tiledmap) (tiledmapProperties tiledmap) mapM_ checkTileset (tiledmapTilesets 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" . layerProperties) "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 layers = tiledmapLayers tiledmap hasLayerNamed name pred = hasLayer (\l -> layerName l == name && pred l) hasLayer pred err = unless (any pred layers) $ complain err -- | check an embedded tile set. -- -- Important to collect dependency files checkTileset :: Tileset -> LintWriter () checkTileset tileset = do -- TODO: can tilesets be non-local dependencies? dependsOn $ Local (tilesetImage tileset) -- reject tilesets unsuitable for workadventure unless (tilesetTilewidth tileset == 32 && tilesetTileheight tileset == 32) $ complain $ "Tileset " <> tilesetName tileset <> " must have tile size 32 by 32" -- | 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