summaryrefslogtreecommitdiff
path: root/lib/Util.hs
blob: 18dfb5b925ed392776576e931e9f524c59dc4699 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase        #-}
{-# LANGUAGE OverloadedStrings #-}

-- | has (perhaps inevitably) morphed into a module that mostly
-- concerns itself with wrangling haskell's string types
module Util where

import           Data.Aeson as Aeson
import           Data.Text  (Text)
import qualified Data.Text  as T
import           Tiled2     (Layer (layerData), PropertyValue (..),
                             Tileset (tilesetName), layerName, mkTiledId)

-- | haskell's many string types are FUN …
showText :: Show a => a -> Text
showText = T.pack . show

-- | a class to address all the string conversions necessary
-- when using Show to much that just uses Text instead
class PrettyPrint a where
  prettyprint :: a -> Text

-- | let's see if this is a good idea or makes type inference bite us
instance PrettyPrint Text where
  prettyprint text = "\"" <> text <> "\""

-- | same as show json, but without the "String" prefix for json strings
instance PrettyPrint Aeson.Value where
  prettyprint = \case
    Aeson.String s -> prettyprint s
    v              -> (T.pack . show) v

instance PrettyPrint PropertyValue where
  prettyprint = \case
    StrProp str   -> str
    BoolProp bool -> if bool then "true" else "false"

-- | here since Unit is sometimes used as dummy type
instance PrettyPrint () where
  prettyprint _ = error "shouldn't pretty-print Unit"

instance PrettyPrint Layer where
  prettyprint = (<>) "layer " . layerName

instance PrettyPrint Tileset where
  prettyprint = (<>) "tileset " . tilesetName

printPretty :: PrettyPrint a => a -> IO ()
printPretty = putStr . T.unpack . prettyprint


layerIsEmpty :: Layer -> Bool
layerIsEmpty layer = case layerData layer of
  Nothing -> True
  Just d  -> all ((==) $ mkTiledId 0) d