{-# 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, 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 (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 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 :: Tileset -> LintWriter Tiledmap checkTileset tileset = do -- 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 by 32" -- | 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 -- | 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 :: Text -> LintWriter Layer -> LintWriter Layer unlessHasProperty name andthen = do layer <- askContext let hasprop = any (\(Property name' _) -> name == name') (layerProperties 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 :: Text -> LintWriter Layer requireProperty name = unlessHasProperty name $ complain $ "property "<>prettyprint name<>" requires property "<>prettyprint name -- | 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 :: [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 ())