Skip to content
Snippets Groups Projects
Select Git revision
  • eced432b67b23302f10d94533c9cc6d9bcc5ce74
  • master default protected
  • style-2021
  • newstyle
  • archive/2020
  • vanion-master-patch-78871
  • deinkoks-master-patch-08946
  • 2020
8 results

maps.md

Blame
  • Properties.hs 20.30 KiB
    {-# LANGUAGE DataKinds         #-}
    {-# LANGUAGE LambdaCase        #-}
    {-# LANGUAGE MultiWayIf        #-}
    {-# LANGUAGE NamedFieldPuns    #-}
    {-# LANGUAGE OverloadedStrings #-}
    {-# LANGUAGE RecordWildCards   #-}
    {-# LANGUAGE TypeApplications  #-}
    
    -- | Contains checks for custom ties of the map json
    module Properties (checkMap, checkTileset, checkLayer) where
    
    
    import           Control.Monad (forM_, unless, when)
    import           Data.Text     (Text, isPrefixOf)
    import qualified Data.Vector   as V
    import           Tiled         (Layer (..), Object (..), Property (..),
                                    PropertyValue (..), Tiledmap (..), Tileset (..))
    import           TiledAbstract (HasName (..), HasProperties (..),
                                    HasTypeName (..), IsProperty (..))
    import           Util          (layerIsEmpty, mkProxy, naiveEscapeHTML,
                                    prettyprint, showText)
    
    import           Badges        (Badge (Badge),
                                    BadgeArea (BadgePoint, BadgeRect), BadgeToken,
                                    parseToken)
    import           Data.Data     (Proxy (Proxy))
    import           Data.Maybe    (fromMaybe, isJust)
    import           Data.Set      (Set)
    import qualified Data.Set      as S
    import           GHC.TypeLits  (KnownSymbol)
    import           LayerData     (Collision, layerOverlaps)
    import           LintConfig    (LintConfig (..))
    import           LintWriter    (LintWriter, adjust, askContext, askFileDepth,
                                    complain, dependsOn, forbid, lintConfig,
                                    offersBadge, offersEntrypoint, suggest, warn)
    import           Paths         (PathResult (..), RelPath (..), parsePath)
    import           Types         (Dep (Link, Local, LocalMap, MapLink))
    import           Uris          (SubstError (..), applySubst)
    
    
    -- | Checks an entire map for "general" lints.
    --
    -- Note that it does /not/ check any tile layer/tileset properties;
    -- these are handled seperately in CheckMap, since these lints go
    -- into a different field of the output.
    checkMap :: LintWriter Tiledmap
    checkMap = do
      tiledmap <- askContext
      let unlessLayer = unlessElement (tiledmapLayers tiledmap)
    
      -- test custom map properties
      mapM_ checkMapProperty (fromMaybe mempty $ tiledmapProperties tiledmap)
    
      -- can't have these with the rest of layer/tileset lints since they're
      -- not specific to any one of them
      refuseDoubledNames (tiledmapLayers tiledmap)
      refuseDoubledNames (tiledmapTilesets tiledmap)
    
      -- some layers should exist
      unlessElementNamed (tiledmapLayers tiledmap) "start"
        $ complain "The map must have one layer named \"start\"."
      unlessLayer (\l -> getName l == "floorLayer" && layerType l == "objectgroup")
        $ complain "The map must have one layer named \"floorLayer\" of type \"objectgroup\"."
      unlessLayer (flip containsProperty "exitUrl" . getProperties)
        $ complain "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."
    
      unlessHasProperty "mapCopyright"
        $ complain "must give the map's copyright via the \"mapCopyright\" property."
    
      -- TODO: this doesn't catch collisions with the default start layer!
      whenLayerCollisions (\(Property name _) -> name == "exitUrl" || name == "startLayer")
        $ \cols -> warn $ "collisions between entry and / or exit layers: " <> prettyprint cols
    
    
    -- | 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 p@(Property name _) = 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 -> forbid "cannot use property \"script\"; custom scripts are disallowed"
          True  -> pure ()
        lintConfig configScriptInject >>= \case
          Nothing  -> pure ()
          Just url -> setProperty "script" url
      "mapName" -> naiveEscapeProperty p
      "mapDescription" -> naiveEscapeProperty p
      "mapCopyright" -> naiveEscapeProperty p
      "mapLink" -> pure ()
      "mapImage" -> pure ()
      _        -> complain $ "unknown map property " <> prettyprint name
    
    
    -- | 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)
    
      refuseDoubledNames (getProperties tileset)
    
      -- 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 "tilesetCopyright"
        $ forbid "property \"tilesetCopyright\" for tilesets must be set."
    
      -- check individual tileset properties
      mapM_ checkTilesetProperty (fromMaybe [] $ tilesetProperties tileset)
      where
        checkTilesetProperty :: Property -> LintWriter Tileset
        checkTilesetProperty p@(Property name _value) = case name of
          "copyright" -> naiveEscapeProperty p
          _           -> warn $ "unknown tileset property " <> prettyprint name
    
    
    -- | collect lints on a single map layer
    checkLayer :: LintWriter Layer
    checkLayer = do
      layer <- askContext
    
      refuseDoubledNames (getProperties  layer)
    
      when (isJust (layerImage layer))
        $ complain "imagelayer are not supported."
    
      case layerType layer of
        "tilelayer" -> mapM_ checkTileLayerProperty (getProperties layer)
        "group" -> pure ()
        "objectgroup" -> do
          -- TODO: this still retains object group layers, just empties them out.
          -- perhaps actually delete the entire layer, since this still leaves hints
          -- as to where badges are?
          adjust $ \l -> l { layerObjects = Nothing, layerProperties = Nothing }
    
          unless (layerName layer == "floorLayer") $ do
    
            -- TODO: these two checks can probably be unified
            unlessHasProperty "getBadge"
              $ warn "objectgrouop layer (which aren't the floor layer)\
                     \are useless if not used to define badges."
    
            when (null (layerObjects layer) || layerObjects layer == Just mempty)
              $ warn "empty objectgroup layers (which aren't the floor\
                     \layer) are useless."
    
          -- individual objects can't have properties
          forM_ (fromMaybe mempty (layerObjects layer)) $ \object ->
            unless (null (objectProperties object))
              $ warn "Properties cannot be set on individual objects. For setting\
                     \badge tokens, use per-layer properties instead."
    
          forM_ (getProperties layer) checkObjectGroupProperty
        ty -> complain $ "unsupported layer type " <> prettyprint ty <> "."
    
      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 an objectgroup layer
    checkObjectGroupProperty :: Property -> LintWriter Layer
    checkObjectGroupProperty p@(Property name _) = case name of
      "getBadge" ->
        unwrapString p $ \str ->
          unwrapBadgeToken str $ \token -> do
            layer <- askContext
            forM_ (fromMaybe (V.fromList []) $ layerObjects layer) $ \object -> do
              case object of
                ObjectPoint {..} ->
                  offersBadge (Badge token (BadgePoint objectX objectY))
                ObjectRectangle {..} ->
                  offersBadge (Badge token area)
                  where area = BadgeRect
                          objectX objectY
                          objectWidth objectHeight
                          (objectEllipse == Just True)
                ObjectPolygon {} -> complain "cannot use polygons for badges."
                ObjectPolyline {} -> complain "cannot use polylines for badges."
      _ -> warn $ "unknown property " <> prettyprint name <> " for objectgroup layers"
    
    
    -- | Checks a single (custom) property of a "normal" tile layer
    checkTileLayerProperty :: Property -> LintWriter Layer
    checkTileLayerProperty 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 "silent" (BoolProp True)
                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
           setProperty "openWebsiteTriggerMessage"
             ("press SPACE to enter bbb room" :: Text)
           suggest "set \"bbbTriggerMessage\" to a custom message to overwrite the\
                   \default \"press SPACE to enter the bbb room\""
        "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
          requireProperty "openWebsite"
          unlessHasProperty "openWebsiteTriggerMessage"
            $ suggest "set \"openWebsiteTriggerMessage\" to a custom message to\
                      \overwrite the default \"press SPACE to open Website\"."
        "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
        _ ->
            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 tile
          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.")
    
    
    -- | refuse doubled names in everything that's somehow a collection of names
    refuseDoubledNames
      :: (HasName a, HasTypeName a)
      => (Foldable t, Functor t)
      => t a
      -> LintWriter b
    refuseDoubledNames things = foldr folding base things mempty
      where
        -- this accumulates a function that complains about things it's already seen
        folding thing cont seen = do
          when (name `elem` seen)
            $ complain $ "cannot use " <> typeName (mkProxy thing) <> " name \"" <> name <> "\" twice"
          cont (S.insert name seen)
          where name = getName thing
        base _ = pure ()
    
    
    ---- General functions ----
    
    unlessElement
      :: Foldable f
      => f a
      -> (a -> Bool)
      -> LintWriter b
      -> LintWriter b
    unlessElement things op = unless (any op things)
    
    unlessElementNamed :: (HasName a, Foldable f)
      => f a -> Text -> LintWriter b -> LintWriter b
    unlessElementNamed things name =
      unlessElement things ((==) name . getName)
    
    unlessHasProperty :: HasProperties a => Text -> LintWriter a -> LintWriter a
    unlessHasProperty name linter =
      askContext >>= \ctxt ->
        unlessElementNamed (getProperties ctxt) name linter
    
    -- | does this layer have the given property?
    containsProperty :: Foldable t => t Property -> Text -> Bool
    containsProperty props name = any
      (\(Property name' _) -> name' == name) props
    
    -- | should the layers fulfilling the given predicate collide, then perform andthen.
    whenLayerCollisions
      :: (Property -> Bool)
      -> (Set Collision -> LintWriter Tiledmap)
      -> LintWriter Tiledmap
    whenLayerCollisions f andthen = do
      tiledmap <- askContext
      let collisions = layerOverlaps . V.filter (any f . getProperties) $ tiledmapLayers tiledmap
      unless (null collisions)
        $ andthen collisions
    
    ----- Functions with concrete lint messages -----
    
    -- | this property is forbidden and should not be used
    forbidProperty :: Text -> LintWriter Layer
    forbidProperty name = do
      forbid $ "property " <> prettyprint name <> " is disallowed."
    
    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<>"."
    
    
    
    ---- Functions for adjusting the context -----
    
    
    -- | 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
    
    naiveEscapeProperty :: HasProperties a =>  Property -> LintWriter a
    naiveEscapeProperty prop@(Property name _) =
      unwrapString prop (setProperty name . naiveEscapeHTML)
    
    ---- "unwrappers" checking that a property has some type, then do something ----
    
    -- | 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."
    
    -- | 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 in your repository 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."
    
    unwrapBadgeToken :: Text -> (BadgeToken -> LintWriter a) -> LintWriter a
    unwrapBadgeToken str f = case parseToken str of
      Just a  -> f a
      Nothing -> complain "invalid badge token."
    
    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<>"\"."
    
    -- | 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<>"."