{-# LANGUAGE LambdaCase #-} {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeApplications #-} -- | Contains checks for custom ties of the map json {-# LANGUAGE DataKinds #-} module Properties (checkMap, checkTileset, checkLayer) where import Control.Monad (unless, when) import Data.Text (Text, isPrefixOf) import Tiled2 (HasProperties (adjustProperties, getProperties), IsProperty (asProperty), Layer (..), Property (..), PropertyValue (..), Tiledmap (..), Tileset (..)) import Util (layerIsEmpty, prettyprint, showText) import Data.Data (Proxy (Proxy)) import Data.Maybe (fromMaybe, isJust) import GHC.TypeLits (KnownSymbol) import LintConfig (LintConfig (..)) import LintWriter (LintWriter, adjust, askContext, askFileDepth, complain, dependsOn, forbid, lintConfig, offersEntrypoint, suggest, warn) import Paths (PathResult (..), RelPath (..), parsePath) import Types (Dep (Link, Local, LocalMap, MapLink)) import Uris (SubstError (..), applySubst) import Data.Functor ((<&>)) -- | 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" -> do -- this is kind of stupid, since if we also inject script this -- will be overriden anyways, but it also doesn't really hurt I guess -- TODO: perhaps include an explanation in the lint, or allow -- exactly that one value? lintConfig configAllowScripts >>= \case False -> isForbidden True -> pure () lintConfig configScriptInject >>= \case Nothing -> pure () Just url -> setProperty "script" url "mapName" -> pure () "mapLink" -> pure () "mapImage" -> pure () "mapDescription" -> pure () "mapCopyright" -> pure () _ -> complain $ "unknown map property " <> prettyprint 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 "Tilesets must have tile size 32×32." unless (tilesetImageheight tileset < 4096 && tilesetImagewidth tileset < 4096) $ warn "Tilesets should not be larger than 4096×4096 pixels in total." when (isJust (tilesetSource tileset)) $ complain "Tilesets must be embedded and cannot be loaded from external files." -- TODO: check copyright! unlessHasProperty "copyright" $ forbid "property \"copyright\" is required for tilesets." mapM_ checkTilesetProperty (fromMaybe [] $ tilesetProperties tileset) checkTilesetProperty :: Property -> LintWriter Tileset checkTilesetProperty (Property name _value) = case name of "copyright" -> pure () -- only allow some licenses? _ -> pure () -- are there any other properties? -- | collect lints on a single map layer checkLayer :: LintWriter Layer checkLayer = do layer <- askContext when (isJust (layerImage layer)) $ complain "imagelayer are not supported." case layerType layer of "tilelayer" -> mapM_ checkLayerProperty (getProperties layer) "group" -> pure () ty -> unless (layerName layer == "floorLayer" && ty == "objectgroup") $ complain "only group and tilelayer are supported." if layerType layer == "group" then when (null (layerLayers layer)) $ warn "Empty group layers are pointless." else when (isJust (layerLayers layer)) $ complain "Layer is not of type \"group\", but has sublayers." -- | 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 lintConfig configAssemblyTag >>= setProperty "jitsiRoomAdminTag" . ("assembly-" <>) -- prepend "assembly-" to avoid namespace clashes uselessEmptyLayer unwrapString p $ \jitsiRoom -> do suggestProperty $ Property "jitsiTrigger" "onaction" -- prepend jitsi room names to avoid name clashes unless ("shared-" `isPrefixOf` jitsiRoom) $ do assemblyname <- lintConfig configAssemblyTag setProperty "jitsiRoom" (assemblyname <> "-" <> jitsiRoom) "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 "jitsiInterfaceConfig" -> isForbidden "jitsiWidth" -> isIntInRange 0 100 p "bbbRoom" -> do removeProperty "bbbRoom" unwrapURI (Proxy @"bbb") p (\link -> do dependsOn (Link link) setProperty "openWebsite" link setProperty "openWebsitePolicy" ("fullscreen;camera;microphone;display-capture" :: Text) ) (const $ complain "property \"bbbRoom\" cannot be used with local links.") "bbbTrigger" -> do removeProperty "bbbTrigger" requireProperty "bbbRoom" unwrapString p (setProperty "openWebsiteTrigger") unlessHasProperty "bbbTriggerMessage" $ do suggest "set \"bbbTriggerMessage\" to a custom message to overwrite the default \"press SPACE to enter the bbb room\"" setProperty "openWebsiteTriggerMessage" ("press SPACE to enter bbb room" :: Text) "bbbTriggerMessage" -> do removeProperty "bbbTriggerMessage" requireProperty "bbbRoom" unwrapString p (setProperty "openWebsiteTriggerMessage") "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" "playAudioLoop" -> deprecatedUseInstead "audioLoop" "audioVolume" -> do isBool p requireProperty "playAudio" "openWebsite" -> do uselessEmptyLayer suggestProperty $ Property "openWebsiteTrigger" (StrProp "onaction") unwrapURI (Proxy @"website") p (dependsOn . Link) (dependsOn . Local) "openWebsiteTrigger" -> do isString p unlessHasProperty "openWebsiteTriggerMessage" $ suggest "set \"openWebsiteTriggerMessage\" to a custom message to overwrite the default \"press SPACE to open Website\"." requireProperty "openWebsite" "openWebsiteTriggerMessage" -> do isString p requireProperty "openWebsiteTrigger" "openWebsitePolicy" -> isForbidden "openWebsiteAllowApi" -> isForbidden "openTab" -> do isString p requireProperty "openWebsite" "url" -> isForbidden "allowApi" -> isForbidden "exitUrl" -> do forbidEmptyLayer unwrapURI (Proxy @"map") p (dependsOn . MapLink) (dependsOn . LocalMap) "exitSceneUrl" -> deprecatedUseInstead "exitUrl" "exitInstance" -> deprecatedUseInstead "exitUrl" "startLayer" -> do forbidEmptyLayer layer <- askContext offersEntrypoint $ layerName layer unwrapBool p $ \case True -> pure () False -> complain "property \"startLayer\" must be set to true." "silent" -> do isBool p uselessEmptyLayer "collides" -> unwrapBool p $ \case True -> pure () False -> warn "property \"collides\" set to 'false' is useless." "name" -> isUnsupported -- all properties relating to scripting are handled the same _ -> warn $ "unknown property type " <> prettyprint name where isForbidden = forbidProperty name requireProperty req = propertyRequiredBy req name isUnsupported = warn $ "property " <> name <> " is not (yet) supported by walint." deprecatedUseInstead instead = warn $ "property \"" <> name <> "\" is deprecated. Use \"" <> instead <> "\" instead." -- | this property can only be used on a layer that contains at least one tiles forbidEmptyLayer = do layer <- askContext when (layerIsEmpty layer) $ complain ("property " <> prettyprint 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 " <> prettyprint name <> " set on an empty layer is 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." 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<>"." -- | set a property, overwriting whatever value it had previously setProperty :: (IsProperty prop, HasProperties ctxt) => Text -> prop -> LintWriter ctxt setProperty name value = adjust $ \ctxt -> flip adjustProperties ctxt $ \ps -> Just $ Property name (asProperty value) : filter sameName ps where sameName (Property name' _) = name /= name' removeProperty :: HasProperties ctxt => Text -> LintWriter ctxt removeProperty name = adjust $ \ctxt -> flip adjustProperties ctxt $ \ps -> Just $ filter (\(Property name' _) -> name' /= name) ps -- | 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 error: property " <> prettyprint name <> " should be of type string." unwrapString' :: Property -> LintWriter a -> LintWriter a unwrapString' prop f = unwrapString prop (const f) -- | 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 error: property " <> prettyprint name <> " should be of type string and contain a valid uri." -- | 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 error: property " <> prettyprint name <> " should be of type bool." unwrapInt :: Property -> (Int -> LintWriter a) -> LintWriter a unwrapInt (Property name value) f = case value of IntProp float -> f float _ -> complain $ "type error: property " <> prettyprint name <> " should be of type int." unwrapPath :: Text -> (RelPath -> LintWriter a) -> LintWriter a unwrapPath str f = case parsePath str of OkRelPath p@(Path up _ _) -> do depth <- askFileDepth if up <= depth then f p else complain $ "cannot acess paths \"" <> str <> "\" which is outside your repository." NotAPath -> complain $ "path \"" <> str <> "\" is invalid." AbsolutePath -> complain "absolute paths are disallowed. Use world:// instead." UnderscoreMapLink -> complain "map links using /_/ are disallowed. Use world:// instead." AtMapLink -> complain "map links using /@/ are disallowed. Use world:// instead." -- | 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 ()) isIntInRange :: Int -> Int -> Property -> LintWriter a isIntInRange l r p@(Property name _) = unwrapInt p $ \int -> if l < int && int < r then pure () else complain $ "Property " <> prettyprint name <> " should be between" <> showText l <> " and " <> showText r<>"." unwrapURI :: (KnownSymbol s, HasProperties a) => Proxy s -> Property -> (Text -> LintWriter a) -> (RelPath -> LintWriter a) -> LintWriter a unwrapURI sym p@(Property name _) f g = unwrapLink p $ \link -> do subst <- lintConfig configUriSchemas case applySubst sym subst link of Right uri -> do setProperty name uri f uri Left NotALink -> unwrapPath link g Left err -> complain $ case err of IsBlocked -> link <> " is a blocked site." InvalidLink -> link <> " is invalid." SchemaDoesNotExist schema -> "the URI schema " <> schema <> ":// does not exist." WrongScope schema -> "the URI schema " <> schema <> ":// cannot be used on \""<>name<>"\"."