{-# LANGUAGE CPP #-}

-- | Compatibility helpers for the @aeson-2@ migration.
module Dhall.JSON.Compat (
      objectFromList
    , mapToAscList
    , filterObject
    , lookupObject
    , traverseObjectWithKey
    , objectKeys
    , textToKey
    ) where

import Data.Aeson (Object, Value)
import Data.Text  (Text)

#if MIN_VERSION_aeson(2,0,0)
import           Data.Aeson.Key    (Key)
import qualified Data.Aeson.Key    as Key
import           Data.Aeson.KeyMap (KeyMap)
import qualified Data.Aeson.KeyMap as KeyMap
import           Data.Bifunctor    (first)
#else
import           Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import qualified Data.List           as List
#endif

objectFromList :: [(Text, Value)] -> Object
#if MIN_VERSION_aeson(2,0,0)
objectFromList :: [(Text, Value)] -> Object
objectFromList = [(Key, Value)] -> Object
forall v. [(Key, v)] -> KeyMap v
KeyMap.fromList ([(Key, Value)] -> Object)
-> ([(Text, Value)] -> [(Key, Value)]) -> [(Text, Value)] -> Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Text, Value) -> (Key, Value))
-> [(Text, Value)] -> [(Key, Value)]
forall a b. (a -> b) -> [a] -> [b]
map ((Text -> Key) -> (Text, Value) -> (Key, Value)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first Text -> Key
Key.fromText)
#else
objectFromList = HashMap.fromList
#endif

filterObject :: (Value -> Bool) -> Object -> Object
#if MIN_VERSION_aeson(2,0,0)
filterObject :: (Value -> Bool) -> Object -> Object
filterObject = (Value -> Bool) -> Object -> Object
forall v. (v -> Bool) -> KeyMap v -> KeyMap v
KeyMap.filter
#else
filterObject = HashMap.filter
#endif

#if MIN_VERSION_aeson(2,0,0)
mapToAscList :: KeyMap a -> [(Text, a)]
mapToAscList :: KeyMap a -> [(Text, a)]
mapToAscList = ((Key, a) -> (Text, a)) -> [(Key, a)] -> [(Text, a)]
forall a b. (a -> b) -> [a] -> [b]
map ((Key -> Text) -> (Key, a) -> (Text, a)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first Key -> Text
Key.toText) ([(Key, a)] -> [(Text, a)])
-> (KeyMap a -> [(Key, a)]) -> KeyMap a -> [(Text, a)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. KeyMap a -> [(Key, a)]
forall v. KeyMap v -> [(Key, v)]
KeyMap.toAscList
#else
mapToAscList :: HashMap Text a -> [(Text, a)]
mapToAscList = List.sortOn fst . HashMap.toList
#endif

lookupObject :: Text -> Object -> Maybe Value
#if MIN_VERSION_aeson(2,0,0)
lookupObject :: Text -> Object -> Maybe Value
lookupObject Text
k = Key -> Object -> Maybe Value
forall v. Key -> KeyMap v -> Maybe v
KeyMap.lookup (Text -> Key
Key.fromText Text
k)
#else
lookupObject = HashMap.lookup
#endif

objectKeys :: Object -> [Text]
#if MIN_VERSION_aeson(2,0,0)
objectKeys :: Object -> [Text]
objectKeys = (Key -> Text) -> [Key] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Key -> Text
Key.toText) ([Key] -> [Text]) -> (Object -> [Key]) -> Object -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Object -> [Key]
forall v. KeyMap v -> [Key]
KeyMap.keys
#else
objectKeys = HashMap.keys
#endif

#if MIN_VERSION_aeson(2,0,0)
textToKey :: Text -> Key
textToKey :: Text -> Key
textToKey = Text -> Key
Key.fromText
#else
textToKey :: Text -> Text
textToKey = id
#endif

#if MIN_VERSION_aeson(2,0,0)
traverseObjectWithKey :: Applicative f => (Key -> v1 -> f v2) -> KeyMap v1 -> f (KeyMap v2)
traverseObjectWithKey :: (Key -> v1 -> f v2) -> KeyMap v1 -> f (KeyMap v2)
traverseObjectWithKey = (Key -> v1 -> f v2) -> KeyMap v1 -> f (KeyMap v2)
forall (f :: * -> *) v1 v2.
Applicative f =>
(Key -> v1 -> f v2) -> KeyMap v1 -> f (KeyMap v2)
KeyMap.traverseWithKey
#else
traverseObjectWithKey :: Applicative f => (Text -> v1 -> f v2) -> HashMap Text v1 -> f (HashMap Text v2)
traverseObjectWithKey = HashMap.traverseWithKey
#endif