{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
module Dhall.Marshal.Internal
( InputNormalizer(..)
, defaultInputNormalizer
, InterpretOptions(..)
, SingletonConstructors(..)
, defaultInterpretOptions
, Result(..)
, getSelName
, notEmptyRecord
, notEmptyRecordLit
, unsafeExpectRecord
, unsafeExpectRecordLit
, unsafeExpectUnion
, unsafeExpectUnionLit
, Fix(..)
, HashMap
, Int8
, Int16
, Int32
, Int64
, Map
, Natural
, Scientific
, Seq
, Text
, Vector
, Void
, Word8
, Word16
, Word32
, Word64
, Generic
) where
import Control.Monad.Trans.State.Strict
import Data.Fix (Fix (..))
import Data.HashMap.Strict (HashMap)
import Data.Int (Int16, Int32, Int64, Int8)
import Data.Map (Map)
import Data.Scientific (Scientific)
import Data.Sequence (Seq)
import Data.Text (Text)
import Data.Vector (Vector)
import Data.Void (Void)
import Data.Word (Word16, Word32, Word64, Word8)
import Dhall.Parser (Src (..))
import Dhall.Syntax (Expr (..), RecordField (..))
import GHC.Generics
import Numeric.Natural (Natural)
import Prelude hiding (maybe, sequence)
import qualified Data.Text
import qualified Dhall.Core as Core
import qualified Dhall.Map
newtype Result f = Result { forall (f :: * -> *). Result f -> f (Result f)
_unResult :: f (Result f) }
data InterpretOptions = InterpretOptions
{ InterpretOptions -> Text -> Text
fieldModifier :: Text -> Text
, InterpretOptions -> Text -> Text
constructorModifier :: Text -> Text
, InterpretOptions -> SingletonConstructors
singletonConstructors :: SingletonConstructors
}
newtype InputNormalizer = InputNormalizer
{ InputNormalizer -> ReifiedNormalizer Void
getInputNormalizer :: Core.ReifiedNormalizer Void }
defaultInputNormalizer :: InputNormalizer
defaultInputNormalizer :: InputNormalizer
defaultInputNormalizer = InputNormalizer
{ getInputNormalizer :: ReifiedNormalizer Void
getInputNormalizer = forall a. Normalizer a -> ReifiedNormalizer a
Core.ReifiedNormalizer (forall a b. a -> b -> a
const (forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing)) }
data SingletonConstructors
= Bare
| Wrapped
| Smart
defaultInterpretOptions :: InterpretOptions
defaultInterpretOptions :: InterpretOptions
defaultInterpretOptions = InterpretOptions
{ fieldModifier :: Text -> Text
fieldModifier =
forall a. a -> a
id
, constructorModifier :: Text -> Text
constructorModifier =
forall a. a -> a
id
, singletonConstructors :: SingletonConstructors
singletonConstructors =
SingletonConstructors
Smart
}
unsafeExpectUnion
:: Text -> Expr Src Void -> Dhall.Map.Map Text (Maybe (Expr Src Void))
unsafeExpectUnion :: Text -> Expr Src Void -> Map Text (Maybe (Expr Src Void))
unsafeExpectUnion Text
_ (Union Map Text (Maybe (Expr Src Void))
kts) =
Map Text (Maybe (Expr Src Void))
kts
unsafeExpectUnion Text
name Expr Src Void
expression =
Text -> forall b. b
Core.internalError
(Text
name forall a. Semigroup a => a -> a -> a
<> Text
": Unexpected constructor: " forall a. Semigroup a => a -> a -> a
<> forall a. Pretty a => a -> Text
Core.pretty Expr Src Void
expression)
unsafeExpectRecord
:: Text -> Expr Src Void -> Dhall.Map.Map Text (RecordField Src Void)
unsafeExpectRecord :: Text -> Expr Src Void -> Map Text (RecordField Src Void)
unsafeExpectRecord Text
_ (Record Map Text (RecordField Src Void)
kts) =
Map Text (RecordField Src Void)
kts
unsafeExpectRecord Text
name Expr Src Void
expression =
Text -> forall b. b
Core.internalError
(Text
name forall a. Semigroup a => a -> a -> a
<> Text
": Unexpected constructor: " forall a. Semigroup a => a -> a -> a
<> forall a. Pretty a => a -> Text
Core.pretty Expr Src Void
expression)
unsafeExpectUnionLit
:: Text
-> Expr Src Void
-> (Text, Maybe (Expr Src Void))
unsafeExpectUnionLit :: Text -> Expr Src Void -> (Text, Maybe (Expr Src Void))
unsafeExpectUnionLit Text
_ (Field (Union Map Text (Maybe (Expr Src Void))
_) (forall s. FieldSelection s -> Text
Core.fieldSelectionLabel -> Text
k)) =
(Text
k, forall a. Maybe a
Nothing)
unsafeExpectUnionLit Text
_ (App (Field (Union Map Text (Maybe (Expr Src Void))
_) (forall s. FieldSelection s -> Text
Core.fieldSelectionLabel -> Text
k)) Expr Src Void
v) =
(Text
k, forall a. a -> Maybe a
Just Expr Src Void
v)
unsafeExpectUnionLit Text
name Expr Src Void
expression =
Text -> forall b. b
Core.internalError
(Text
name forall a. Semigroup a => a -> a -> a
<> Text
": Unexpected constructor: " forall a. Semigroup a => a -> a -> a
<> forall a. Pretty a => a -> Text
Core.pretty Expr Src Void
expression)
unsafeExpectRecordLit
:: Text -> Expr Src Void -> Dhall.Map.Map Text (RecordField Src Void)
unsafeExpectRecordLit :: Text -> Expr Src Void -> Map Text (RecordField Src Void)
unsafeExpectRecordLit Text
_ (RecordLit Map Text (RecordField Src Void)
kvs) =
Map Text (RecordField Src Void)
kvs
unsafeExpectRecordLit Text
name Expr Src Void
expression =
Text -> forall b. b
Core.internalError
(Text
name forall a. Semigroup a => a -> a -> a
<> Text
": Unexpected constructor: " forall a. Semigroup a => a -> a -> a
<> forall a. Pretty a => a -> Text
Core.pretty Expr Src Void
expression)
notEmptyRecordLit :: Expr s a -> Maybe (Expr s a)
notEmptyRecordLit :: forall s a. Expr s a -> Maybe (Expr s a)
notEmptyRecordLit Expr s a
e = case Expr s a
e of
RecordLit Map Text (RecordField s a)
m | forall (t :: * -> *) a. Foldable t => t a -> Bool
null Map Text (RecordField s a)
m -> forall a. Maybe a
Nothing
Expr s a
_ -> forall a. a -> Maybe a
Just Expr s a
e
notEmptyRecord :: Expr s a -> Maybe (Expr s a)
notEmptyRecord :: forall s a. Expr s a -> Maybe (Expr s a)
notEmptyRecord Expr s a
e = case Expr s a
e of
Record Map Text (RecordField s a)
m | forall (t :: * -> *) a. Foldable t => t a -> Bool
null Map Text (RecordField s a)
m -> forall a. Maybe a
Nothing
Expr s a
_ -> forall a. a -> Maybe a
Just Expr s a
e
getSelName :: Selector s => M1 i s f a -> State Int Text
getSelName :: forall (s :: Meta) i (f :: * -> *) a.
Selector s =>
M1 i s f a -> State Int Text
getSelName M1 i s f a
n = case forall {k} (s :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
(f :: k1 -> *) (a :: k1).
Selector s =>
t s f a -> [Char]
selName M1 i s f a
n of
[Char]
"" -> do Int
i <- forall (m :: * -> *) s. Monad m => StateT s m s
get
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
put (Int
i forall a. Num a => a -> a -> a
+ Int
1)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Char] -> Text
Data.Text.pack ([Char]
"_" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Int
i))
[Char]
nn -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Char] -> Text
Data.Text.pack [Char]
nn)