{-# LANGUAGE TypeFamilies #-}
module Toml.Printer
( PrintOptions(..)
, defaultOptions
, pretty
, prettyOptions
, prettyTomlInd
) where
import Data.HashMap.Strict (HashMap)
import Data.Monoid ((<>), mconcat)
import Data.Text (Text)
import Data.Time (formatTime, defaultTimeLocale, ZonedTime)
import Data.List (splitAt, sortOn)
import Toml.PrefixTree (Key (..), Piece (..), PrefixMap, PrefixTree (..))
import Toml.Type (AnyValue (..), DateTime (..), TOML (..), Value (..))
import qualified Data.HashMap.Strict as HashMap
import qualified Data.List.NonEmpty as NonEmpty
import qualified Data.Text as Text
data PrintOptions = PrintOptions
{ shouldSort :: Bool
, indent :: Int
} deriving (Show)
defaultOptions :: PrintOptions
defaultOptions = PrintOptions True 2
tabWith :: PrintOptions -> Int -> Text
tabWith options n =
Text.cons '\n' (Text.replicate (n * indent options) " ")
orderWith :: Ord k => PrintOptions -> [(k, v)] -> [(k, v)]
orderWith options
| shouldSort options = sortOn fst
| otherwise = id
pretty :: TOML -> Text
pretty = prettyOptions defaultOptions
prettyOptions :: PrintOptions -> TOML -> Text
prettyOptions options = Text.drop 1 . prettyTomlInd options 0 ""
prettyTomlInd :: PrintOptions
-> Int
-> Text
-> TOML
-> Text
prettyTomlInd options i prefix TOML{..} =
prettyKeyValue options i tomlPairs <> "\n"
<> prettyTables options i prefix tomlTables
prettyKeyValue :: PrintOptions -> Int -> HashMap Key AnyValue -> Text
prettyKeyValue options i =
Text.concat . map kvText . orderWith options . HashMap.toList
where
kvText :: (Key, AnyValue) -> Text
kvText (k, AnyValue v) = mconcat
[ tabWith options i
, prettyKey k
, " = "
, valText v ]
valText :: Value t -> Text
valText (Bool b) = Text.toLower $ showText b
valText (Integer n) = showText n
valText (Double d) = showDouble d
valText (Text s) = showText s
valText (Date d) = timeText d
valText (Array a) = "[" <> Text.intercalate ", " (map valText a) <> "]"
timeText :: DateTime -> Text
timeText (Zoned z) = showZonedTime z
timeText (Local l) = showText l
timeText (Day d) = showText d
timeText (Hours h) = showText h
showText :: Show a => a -> Text
showText = Text.pack . show
showDouble :: Double -> Text
showDouble d | isInfinite d && d < 0 = "-inf"
| isInfinite d = "inf"
| isNaN d = "nan"
| otherwise = showText d
showZonedTime :: ZonedTime -> Text
showZonedTime t = Text.pack $ showZonedDateTime t <> showZonedZone t
where
showZonedDateTime = formatTime defaultTimeLocale "%FT%T%Q"
showZonedZone
= (\(x,y) -> x ++ ":" ++ y)
. (\z -> splitAt (length z - 2) z)
. formatTime defaultTimeLocale "%z"
prettyTables :: PrintOptions -> Int -> Text -> PrefixMap TOML -> Text
prettyTables options i pref =
Text.concat . map (prettyTable . snd) . orderWith options . HashMap.toList
where
prettyTable :: PrefixTree TOML -> Text
prettyTable (Leaf k toml) =
let name = getPref k in mconcat
[ tabWith options i
, prettyTableName name
, prettyTomlInd options (succ i) name toml ]
prettyTable (Branch k mToml prefMap) =
let name = getPref k
nextI = succ i
toml = case mToml of
Nothing -> ""
Just t -> prettyTomlInd options nextI name t
in mconcat
[ tabWith options i
, prettyTableName name
, toml
, prettyTables options nextI name prefMap ]
getPref :: Key -> Text
getPref k = case pref of
"" -> prettyKey k
_ -> pref <> "." <> prettyKey k
prettyTableName :: Text -> Text
prettyTableName n = "[" <> n <> "]"
prettyKey :: Key -> Text
prettyKey (Key k) = Text.intercalate "." $ map unPiece (NonEmpty.toList k)