Skip to content
Snippets Groups Projects
Unverified Commit c6be6366 authored by stuebinm's avatar stuebinm
Browse files

use PrettyPrinter more

parent 42df3cf0
No related branches found
No related tags found
No related merge requests found
...@@ -5,7 +5,6 @@ ...@@ -5,7 +5,6 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
-- | Module that contains the high-level checking functions -- | Module that contains the high-level checking functions
{-# OPTIONS_GHC -Wno-deferred-out-of-scope-variables #-}
module CheckMap (loadAndLintMap) where module CheckMap (loadAndLintMap) where
import Data.Aeson (ToJSON) import Data.Aeson (ToJSON)
...@@ -22,7 +21,7 @@ import LintWriter (LintResult (..), LintWriter, askContext, ...@@ -22,7 +21,7 @@ import LintWriter (LintResult (..), LintWriter, askContext,
import Properties (checkLayerProperty, checkMap) import Properties (checkLayerProperty, checkMap)
import Tiled2 (Layer (layerName, layerProperties), import Tiled2 (Layer (layerName, layerProperties),
Tiledmap (tiledmapLayers), loadTiledmap) Tiledmap (tiledmapLayers), loadTiledmap)
import Types (Dep, Level (..), Lint (..), hint, lintLevel) import Types (Dep, Level (..), Lint (..), hint)
import Util (PrettyPrint (prettyprint), prettyprint) import Util (PrettyPrint (prettyprint), prettyprint)
...@@ -81,26 +80,9 @@ instance PrettyPrint a => PrettyPrint (MapResult a) where ...@@ -81,26 +80,9 @@ instance PrettyPrint a => PrettyPrint (MapResult a) where
where where
-- TODO: this can be simplified further -- TODO: this can be simplified further
prettyLayer :: [Text] prettyLayer :: [Text]
prettyLayer = mapMaybe prettyLayer = map
(uncurry showResult) (prettyprint . snd)
(maybe [] toList . mapresultLayer $ mapResult) (maybe [] toList . mapresultLayer $ mapResult)
prettyGeneral :: [Text] prettyGeneral :: [Text]
prettyGeneral = flip (<>) "\n" . prettyprint <$> mapresultGeneral mapResult prettyGeneral = flip (<>) "\n" . prettyprint <$> mapresultGeneral mapResult
-- TODO: possibly expand this to something more detailed?
showContext :: Text -> Text
showContext ctxt = " (in layer " <> ctxt <> ")\n"
-- | pretty-printer for a LintResult. Isn't an instance of PrettyPrint since
-- it needs to know about the result's context (yes, there could be
-- a wrapper type for that – but I wasn't really in the mood)
showResult :: Text -> LintResult c -> Maybe Text
showResult ctxt (LintResult (_, lints)) =
Just $ T.concat (mapMaybe showHint lints)
where
-- TODO: make the "log level" configurable
showHint hint = case lintLevel hint of
Info -> Nothing
_ -> Just $ prettyprint hint <> ctxtHint
ctxtHint = showContext ctxt
...@@ -14,12 +14,12 @@ import Control.Monad.Writer (MonadWriter (tell), WriterT, ...@@ -14,12 +14,12 @@ import Control.Monad.Writer (MonadWriter (tell), WriterT,
import Data.Aeson (ToJSON (toJSON)) import Data.Aeson (ToJSON (toJSON))
import Data.Text (Text) import Data.Text (Text)
import Control.Monad.Reader (local)
import Control.Monad.Trans.Reader (Reader, asks, runReader) import Control.Monad.Trans.Reader (Reader, asks, runReader)
import Control.Monad.Writer.Lazy (lift) import Control.Monad.Writer.Lazy (lift)
import Data.Maybe (mapMaybe) import Data.Maybe (mapMaybe)
import GHC.Generics (Generic) import qualified Data.Text as T
import Types import Types
import Util (PrettyPrint (..))
-- | for now, all context we have is how "deep" in the directory tree -- | for now, all context we have is how "deep" in the directory tree
...@@ -38,9 +38,15 @@ newtype LintResult ctxt = LintResult (LintResult' ctxt) ...@@ -38,9 +38,15 @@ newtype LintResult ctxt = LintResult (LintResult' ctxt)
-- better, less confusing serialisation of an Either Hint (a, [Hint]). -- better, less confusing serialisation of an Either Hint (a, [Hint]).
-- Note that Left hint is also serialised as a list to make the resulting -- Note that Left hint is also serialised as a list to make the resulting
-- json schema more regular. -- json schema more regular.
instance ToJSON a => ToJSON (LintResult a) where instance ToJSON (LintResult a) where
toJSON (LintResult res) = toJSON $ snd res toJSON (LintResult res) = toJSON $ snd res
instance PrettyPrint ctxt => PrettyPrint (LintResult ctxt) where
prettyprint (LintResult (ctxt, res)) =
T.concat (map showHint res)
where showHint hint = prettyprint hint <> context
context = " (" <> prettyprint ctxt <> ")\n"
lintToDep :: Lint -> Maybe Dep lintToDep :: Lint -> Maybe Dep
lintToDep = \case lintToDep = \case
Depends dep -> Just dep Depends dep -> Just dep
......
...@@ -13,8 +13,8 @@ import Tiled2 (Layer (..), Property (..), PropertyValue (..), ...@@ -13,8 +13,8 @@ import Tiled2 (Layer (..), Property (..), PropertyValue (..),
import Util (layerIsEmpty, prettyprint) import Util (layerIsEmpty, prettyprint)
import LintWriter (LintWriter, askContext, askFileDepth, complain, import LintWriter (LintWriter, askContext, askFileDepth, complain,
dependsOn, forbid, info, suggest, warn) dependsOn, forbid, suggest, warn)
import Paths import Paths (RelPath (..), parsePath)
import Types (Dep (Link, Local, LocalMap, MapLink)) import Types (Dep (Link, Local, LocalMap, MapLink))
...@@ -88,8 +88,7 @@ checkLayerProperty :: Property -> LintWriter Layer ...@@ -88,8 +88,7 @@ checkLayerProperty :: Property -> LintWriter Layer
checkLayerProperty p@(Property name _value) = case name of checkLayerProperty p@(Property name _value) = case name of
"jitsiRoom" -> do "jitsiRoom" -> do
uselessEmptyLayer uselessEmptyLayer
unwrapString p $ \val -> do unwrapString p $ \_val -> do
info $ "found jitsi room: " <> prettyprint val
suggestProperty $ Property "jitsiTrigger" (StrProp "onaction") suggestProperty $ Property "jitsiTrigger" (StrProp "onaction")
"jitsiTrigger" -> do "jitsiTrigger" -> do
isString p isString p
......
...@@ -9,7 +9,8 @@ module Util where ...@@ -9,7 +9,8 @@ module Util where
import Data.Aeson as Aeson import Data.Aeson as Aeson
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as T import qualified Data.Text as T
import Tiled2 (Layer (layerData), PropertyValue (..), mkTiledId) import Tiled2 (Layer (layerData), PropertyValue (..), layerName,
mkTiledId)
-- | haskell's many string types are FUN … -- | haskell's many string types are FUN …
showText :: Show a => a -> Text showText :: Show a => a -> Text
...@@ -39,6 +40,9 @@ instance PrettyPrint PropertyValue where ...@@ -39,6 +40,9 @@ instance PrettyPrint PropertyValue where
instance PrettyPrint () where instance PrettyPrint () where
prettyprint _ = error "shouldn't pretty-print Unit" prettyprint _ = error "shouldn't pretty-print Unit"
instance PrettyPrint Layer where
prettyprint = (<>) "layer " . layerName
printPretty :: PrettyPrint a => a -> IO () printPretty :: PrettyPrint a => a -> IO ()
printPretty = putStr . T.unpack . prettyprint printPretty = putStr . T.unpack . prettyprint
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment