{-# 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 = KeyMap.fromList . map (first Key.fromText)
#else
objectFromList :: [(Text, Value)] -> Object
objectFromList = [(Text, Value)] -> Object
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
#endif

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

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

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

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

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

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