{-# LANGUAGE CPP #-}
module Data.Yaml.Pretty
( encodePretty
, Config
, getConfCompare
, setConfCompare
, getConfDropNull
, setConfDropNull
, defConfig
, pretty
) where
import Prelude hiding (null)
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>))
#endif
import Data.Aeson.Types
import Data.ByteString (ByteString)
import Data.Function (on)
import qualified Data.HashMap.Strict as HM
import Data.List (sortBy)
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid
#endif
import Data.Text (Text)
import qualified Data.Vector as V
import Data.Yaml.Builder
data Config = Config
{ confCompare :: Text -> Text -> Ordering
, confDropNull :: Bool
}
defConfig :: Config
defConfig = Config mempty False
getConfCompare :: Config -> Text -> Text -> Ordering
getConfCompare = confCompare
setConfCompare :: (Text -> Text -> Ordering) -> Config -> Config
setConfCompare cmp c = c { confCompare = cmp }
getConfDropNull :: Config -> Bool
getConfDropNull = confDropNull
setConfDropNull :: Bool -> Config -> Config
setConfDropNull m c = c { confDropNull = m }
pretty :: Config -> Value -> YamlBuilder
pretty cfg = go
where go (Object o) = let sort = sortBy (confCompare cfg `on` fst)
select
| confDropNull cfg = HM.filter (/= Null)
| otherwise = id
in mapping (sort $ HM.toList $ HM.map go $ select o)
go (Array a) = array (go <$> V.toList a)
go Null = null
go (String s) = string s
go (Number n) = scientific n
go (Bool b) = bool b
encodePretty :: ToJSON a => Config -> a -> ByteString
encodePretty cfg = toByteString . pretty cfg . toJSON