{-# LANGUAGE DeriveGeneric #-}
module Dhall.Syntax.Types
( DhallDouble(..)
, PreferAnnotation(..)
, FieldSelection(..)
, makeFieldSelection
, WithComponent(..)
) where
import Data.Text (Text)
import GHC.Generics (Generic)
newtype DhallDouble = DhallDouble { DhallDouble -> Double
getDhallDouble :: Double }
deriving (forall x. DhallDouble -> Rep DhallDouble x)
-> (forall x. Rep DhallDouble x -> DhallDouble)
-> Generic DhallDouble
forall x. Rep DhallDouble x -> DhallDouble
forall x. DhallDouble -> Rep DhallDouble x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DhallDouble -> Rep DhallDouble x
from :: forall x. DhallDouble -> Rep DhallDouble x
$cto :: forall x. Rep DhallDouble x -> DhallDouble
to :: forall x. Rep DhallDouble x -> DhallDouble
Generic
data PreferAnnotation
= PreferFromSource
| PreferFromCompletion
deriving (forall x. PreferAnnotation -> Rep PreferAnnotation x)
-> (forall x. Rep PreferAnnotation x -> PreferAnnotation)
-> Generic PreferAnnotation
forall x. Rep PreferAnnotation x -> PreferAnnotation
forall x. PreferAnnotation -> Rep PreferAnnotation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PreferAnnotation -> Rep PreferAnnotation x
from :: forall x. PreferAnnotation -> Rep PreferAnnotation x
$cto :: forall x. Rep PreferAnnotation x -> PreferAnnotation
to :: forall x. Rep PreferAnnotation x -> PreferAnnotation
Generic
data FieldSelection s = FieldSelection
{ forall s. FieldSelection s -> Maybe s
fieldSelectionSrc0 :: Maybe s
, forall s. FieldSelection s -> Text
fieldSelectionLabel :: !Text
, forall s. FieldSelection s -> Maybe s
fieldSelectionSrc1 :: Maybe s
} deriving (forall x. FieldSelection s -> Rep (FieldSelection s) x)
-> (forall x. Rep (FieldSelection s) x -> FieldSelection s)
-> Generic (FieldSelection s)
forall x. Rep (FieldSelection s) x -> FieldSelection s
forall x. FieldSelection s -> Rep (FieldSelection s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall s x. Rep (FieldSelection s) x -> FieldSelection s
forall s x. FieldSelection s -> Rep (FieldSelection s) x
$cfrom :: forall s x. FieldSelection s -> Rep (FieldSelection s) x
from :: forall x. FieldSelection s -> Rep (FieldSelection s) x
$cto :: forall s x. Rep (FieldSelection s) x -> FieldSelection s
to :: forall x. Rep (FieldSelection s) x -> FieldSelection s
Generic
makeFieldSelection :: Text -> FieldSelection s
makeFieldSelection :: forall s. Text -> FieldSelection s
makeFieldSelection Text
t = Maybe s -> Text -> Maybe s -> FieldSelection s
forall s. Maybe s -> Text -> Maybe s -> FieldSelection s
FieldSelection Maybe s
forall a. Maybe a
Nothing Text
t Maybe s
forall a. Maybe a
Nothing
data WithComponent = WithLabel Text | WithQuestion
deriving (forall x. WithComponent -> Rep WithComponent x)
-> (forall x. Rep WithComponent x -> WithComponent)
-> Generic WithComponent
forall x. Rep WithComponent x -> WithComponent
forall x. WithComponent -> Rep WithComponent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. WithComponent -> Rep WithComponent x
from :: forall x. WithComponent -> Rep WithComponent x
$cto :: forall x. Rep WithComponent x -> WithComponent
to :: forall x. Rep WithComponent x -> WithComponent
Generic