module Data.Aeson.Encode.Pretty (
encodePretty, encodePrettyToTextBuilder,
encodePretty', encodePrettyToTextBuilder',
Config (..), defConfig,
Indent(..), NumberFormat(..),
mempty,
compare,
keyOrder
) where
import Data.Aeson (Value(..), ToJSON(..))
import qualified Data.Aeson.Encode as Aeson
import Data.ByteString.Lazy (ByteString)
import Data.Function (on)
import qualified Data.HashMap.Strict as H (toList)
import Data.List (intersperse, sortBy, elemIndex)
import Data.Maybe (fromMaybe)
import Data.Monoid ((<>))
import qualified Data.Scientific as S (Scientific, FPFormat(..))
import Data.Ord (comparing)
import Data.Text (Text)
import Data.Text.Lazy.Builder (Builder, toLazyText)
import Data.Text.Lazy.Builder.Scientific (formatScientificBuilder)
import Data.Text.Lazy.Encoding (encodeUtf8)
import qualified Data.Vector as V (toList)
import Prelude ()
import Prelude.Compat
data PState = PState { pLevel :: Int
, pIndent :: Builder
, pNewline :: Builder
, pItemSep :: Builder
, pKeyValSep :: Builder
, pNumFormat :: NumberFormat
, pSort :: [(Text, Value)] -> [(Text, Value)]
}
data Indent = Spaces Int | Tab
data NumberFormat
= Generic
| Scientific
| Decimal
| Custom (S.Scientific -> Builder)
data Config = Config
{ confIndent :: Indent
, confCompare :: Text -> Text -> Ordering
, confNumFormat :: NumberFormat
, confTrailingNewline :: Bool
}
keyOrder :: [Text] -> Text -> Text -> Ordering
keyOrder ks = comparing $ \k -> fromMaybe maxBound (elemIndex k ks)
defConfig :: Config
defConfig =
Config {confIndent = Spaces 4, confCompare = mempty, confNumFormat = Generic, confTrailingNewline = False}
encodePretty :: ToJSON a => a -> ByteString
encodePretty = encodePretty' defConfig
encodePretty' :: ToJSON a => Config -> a -> ByteString
encodePretty' conf = encodeUtf8 . toLazyText . encodePrettyToTextBuilder' conf
encodePrettyToTextBuilder :: ToJSON a => a -> Builder
encodePrettyToTextBuilder = encodePrettyToTextBuilder' defConfig
encodePrettyToTextBuilder' :: ToJSON a => Config -> a -> Builder
encodePrettyToTextBuilder' Config{..} x = fromValue st (toJSON x) <> trail
where
st = PState 0 indent newline itemSep kvSep confNumFormat sortFn
indent = case confIndent of
Spaces n -> mconcat (replicate n " ")
Tab -> "\t"
newline = case confIndent of
Spaces 0 -> ""
_ -> "\n"
itemSep = ","
kvSep = case confIndent of
Spaces 0 -> ":"
_ -> ": "
sortFn = sortBy (confCompare `on` fst)
trail = if confTrailingNewline then "\n" else ""
fromValue :: PState -> Value -> Builder
fromValue st@PState{..} val = go val
where
go (Array v) = fromCompound st ("[","]") fromValue (V.toList v)
go (Object m) = fromCompound st ("{","}") fromPair (pSort (H.toList m))
go (Number x) = fromNumber st x
go v = Aeson.encodeToTextBuilder v
fromCompound :: PState
-> (Builder, Builder)
-> (PState -> a -> Builder)
-> [a]
-> Builder
fromCompound st@PState{..} (delimL,delimR) fromItem items = mconcat
[ delimL
, if null items then mempty
else pNewline <> items' <> pNewline <> fromIndent st
, delimR
]
where
items' = mconcat . intersperse (pItemSep <> pNewline) $
map (\item -> fromIndent st' <> fromItem st' item)
items
st' = st { pLevel = pLevel + 1}
fromPair :: PState -> (Text, Value) -> Builder
fromPair st (k,v) =
Aeson.encodeToTextBuilder (toJSON k) <> pKeyValSep st <> fromValue st v
fromIndent :: PState -> Builder
fromIndent PState{..} = mconcat (replicate pLevel pIndent)
fromNumber :: PState -> S.Scientific -> Builder
fromNumber st x = case pNumFormat st of
Generic
| (x > 1.0e19 || x < 1.0e19) -> formatScientificBuilder S.Exponent Nothing x
| otherwise -> Aeson.encodeToTextBuilder $ Number x
Scientific -> formatScientificBuilder S.Exponent Nothing x
Decimal -> formatScientificBuilder S.Fixed Nothing x
Custom f -> f x