{-# OPTIONS_HADDOCK hide #-}
module Blockfrost.Types.Shared.Opts
( ToLower
, aesonOptions
) where
import Data.Aeson (Options (..), camelTo2, defaultOptions)
import Data.Char (toLower)
import Deriving.Aeson (StringModifier (..))
data ToLower
instance StringModifier ToLower where
getStringModifier :: String -> String
getStringModifier String
"" = String
""
getStringModifier (Char
c : String
xs) = Char -> Char
toLower Char
c Char -> String -> String
forall a. a -> [a] -> [a]
: String
xs
aesonOptions :: Maybe String -> Options
aesonOptions :: Maybe String -> Options
aesonOptions Maybe String
mPrefix = Options
defaultOptions {
fieldLabelModifier = camelTo2 '_' . dropIfPrefixed
, constructorTagModifier = map toLower
}
where dropIfPrefixed :: String -> String
dropIfPrefixed = (String -> String)
-> (String -> String -> String) -> Maybe String -> String -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String -> String
forall a. a -> a
id (Int -> String -> String
forall a. Int -> [a] -> [a]
drop (Int -> String -> String)
-> (String -> Int) -> String -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length) Maybe String
mPrefix