{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} -- | Module that contains the high-level checking functions module CheckMap (loadAndLintMap, MapResult(..)) where import Data.Aeson (ToJSON (toJSON)) import qualified Data.Aeson as A import Data.Map (Map, toList) import qualified Data.Map as M import Data.Maybe (mapMaybe) import Data.Text (Text) import qualified Data.Text as T import qualified Data.Vector as V import GHC.Generics (Generic) import Data.Aeson.Types ((.=)) import LintWriter (LintWriter, askContext, filterLintLevel, invertLintResult, lintToDep, resultToLints, runLintWriter) import Properties (checkLayerProperty, checkMap, checkTileset) import Tiled2 (HasName (getName), HasProperties (getProperties), Layer (layerName, layerProperties), LoadResult (..), Tiledmap (tiledmapLayers, tiledmapTilesets), Tileset (tilesetName), loadTiledmap) import Types (Dep, Hint (hintLevel, hintMsg), Level (..), Lint (..), hint) import Util (PrettyPrint (prettyprint), prettyprint) -- | What this linter produces: lints for a single map data MapResult = MapResult { mapresultLayer :: Map Hint [Layer] , mapresultTileset :: Map Hint [Tileset] --Map Text (LintResult Tileset) , mapresultGeneral :: [Lint] , mapresultDepends :: [Dep] , mapresultProvides :: [Text] } deriving (Generic) instance ToJSON MapResult where toJSON res = A.object [ "layer" .= CollectedLints (fmap getName <$> mapresultLayer res) , "tileset" .= CollectedLints (fmap getName <$> mapresultTileset res) , "general" .= mapresultGeneral res -- TODO: not sure if these are necessary of even useful , "depends" .= mapresultDepends res , "provides" .= mapresultProvides res ] newtype CollectedLints = CollectedLints (Map Hint [Text]) instance ToJSON CollectedLints where toJSON (CollectedLints col) = toJSON . M.mapKeys hintMsg $ M.mapWithKey (\h cs -> A.object [ "level" .= hintLevel h, "in" .= cs ]) col -- | this module's raison d'ĂȘtre -- Lints the map at `path`, and limits local links to at most `depth` -- layers upwards in the file hierarchy loadAndLintMap :: FilePath -> Int -> IO (Maybe MapResult) loadAndLintMap path depth = loadTiledmap path >>= pure . \case DecodeErr err -> Just $ MapResult { mapresultLayer = mempty , mapresultTileset = mempty , mapresultDepends = [] , mapresultProvides = [] , mapresultGeneral = [ hint Fatal . T.pack $ path <> ": Fatal: " <> err ] } IOErr _ -> Nothing Loaded waMap -> Just (runLinter waMap depth) -- | lint a loaded map runLinter :: Tiledmap -> Int -> MapResult runLinter tiledmap depth = MapResult { mapresultLayer = layer' , mapresultTileset = tileset'-- fromList tileset , mapresultGeneral = generalLints , mapresultDepends = --concatMap (resultToDeps . snd) layer {-<>-} mapMaybe lintToDep generalLints -- <> concatMap (resultToDeps . snd) tileset , mapresultProvides = mempty --concatMap (resultToOffers . snd) layer } where layer' = M.unionsWith (<>) $ fmap invertLintResult layer tileset' = M.unionsWith (<>) $ fmap invertLintResult tileset layer = V.toList . V.map runCheck $ tiledmapLayers tiledmap where runCheck l = runLintWriter l depth checkLayer tileset = V.toList . V.map runCheck $ tiledmapTilesets tiledmap where runCheck l = runLintWriter l depth (checkTileset l) -- lints collected from properties generalLints = resultToLints $ runLintWriter tiledmap depth checkMap -- | collect lints on a single map layer checkLayer :: LintWriter Layer checkLayer = do layer <- askContext mapM_ checkLayerProperty (getProperties layer) -- human-readable lint output, e.g. for consoles instance PrettyPrint (Level, MapResult) where prettyprint (level, mapResult) = if complete == "" then " all good!\n" else complete where complete = T.concat $ prettyGeneral <> prettyLints mapresultLayer <> prettyLints mapresultTileset -- | pretty-prints a collection of Hints, printing each -- Hint only once, then a list of its occurences line-wrapped -- to fit onto a decent-sized terminal prettyLints :: HasName a => (MapResult -> Map Hint [a]) -> [Text] prettyLints getter = fmap (\(h, cs) -> prettyprint h <> "\n (in " -- foldl :: ((length of current line, acc) -> next ctxt -> list) -> ... <> snd (foldl (\(l,a) c -> case l of 0 -> (T.length c, c) _ | l < 70 -> (l+2+T.length c, a <> ", " <> c) _ -> (6+T.length c, a <> ",\n " <> c) ) (0, "") (fmap getName cs)) <> ")\n") (toList . getter $ mapResult) prettyGeneral :: [Text] prettyGeneral = map ((<> "\n") . prettyprint) . filterLintLevel level $ mapresultGeneral mapResult