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