{- hlint ignore "Avoid restricted extensions" -}
{-# LANGUAGE CPP #-}

module Rattletrap.Utility.Json
  ( module Rattletrap.Utility.Json,
    Aeson.FromJSON (parseJSON),
    Key.Key,
    Aeson.ToJSON (toJSON),
    Aeson.Value,
    Aeson.encode,
    Aeson.object,
    Aeson.withObject,
    Aeson.withText,
  )
where

import qualified Data.Aeson as Aeson
import qualified Data.Aeson.Encode.Pretty as Aeson
import qualified Data.Aeson.Key as Key
import qualified Data.Aeson.Types as Aeson
import qualified Data.ByteString as ByteString
import qualified Data.ByteString.Lazy as LazyByteString

keyToString :: Key.Key -> String
keyToString :: Key -> String
keyToString = Key -> String
Key.toString

required ::
  (Aeson.FromJSON value) => Aeson.Object -> String -> Aeson.Parser value
required :: forall value. FromJSON value => Object -> String -> Parser value
required Object
object String
key = Object
object Object -> Key -> Parser value
forall a. FromJSON a => Object -> Key -> Parser a
Aeson..: String -> Key
Key.fromString String
key

optional ::
  (Aeson.FromJSON value) =>
  Aeson.Object ->
  String ->
  Aeson.Parser (Maybe value)
optional :: forall value.
FromJSON value =>
Object -> String -> Parser (Maybe value)
optional Object
object String
key = Object
object Object -> Key -> Parser (Maybe value)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Aeson..:? String -> Key
Key.fromString String
key

# if MIN_VERSION_aeson(2, 2, 0)
pair :: (Aeson.ToJSON value, Aeson.KeyValue e p) => String -> value -> p
# else
pair :: (Aeson.ToJSON value, Aeson.KeyValue p) => String -> value -> p
# endif
pair :: forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
pair String
key value
value = String -> Key
Key.fromString String
key Key -> value -> p
forall v. ToJSON v => Key -> v -> p
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
Aeson..= value
value

decode :: (Aeson.FromJSON a) => ByteString.ByteString -> Either String a
decode :: forall a. FromJSON a => ByteString -> Either String a
decode = ByteString -> Either String a
forall a. FromJSON a => ByteString -> Either String a
Aeson.eitherDecodeStrict'

encodePretty :: (Aeson.ToJSON a) => a -> LazyByteString.ByteString
encodePretty :: forall a. ToJSON a => a -> ByteString
encodePretty =
  Config -> a -> ByteString
forall a. ToJSON a => Config -> a -> ByteString
Aeson.encodePretty'
    Config
Aeson.defConfig
      { Aeson.confCompare = compare,
        Aeson.confIndent = Aeson.Tab,
        Aeson.confTrailingNewline = True
      }