{-# 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. 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
$cto :: forall x. Rep DhallDouble x -> DhallDouble
$cfrom :: forall x. DhallDouble -> Rep DhallDouble x
Generic
data PreferAnnotation
= PreferFromSource
| PreferFromCompletion
deriving 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
$cto :: forall x. Rep PreferAnnotation x -> PreferAnnotation
$cfrom :: forall x. PreferAnnotation -> Rep PreferAnnotation x
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 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
$cto :: forall s x. Rep (FieldSelection s) x -> FieldSelection s
$cfrom :: forall s x. FieldSelection s -> Rep (FieldSelection s) x
Generic
makeFieldSelection :: Text -> FieldSelection s
makeFieldSelection :: forall s. Text -> FieldSelection s
makeFieldSelection Text
t = forall s. Maybe s -> Text -> Maybe s -> FieldSelection s
FieldSelection forall a. Maybe a
Nothing Text
t forall a. Maybe a
Nothing
data WithComponent = WithLabel Text | WithQuestion
deriving 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
$cto :: forall x. Rep WithComponent x -> WithComponent
$cfrom :: forall x. WithComponent -> Rep WithComponent x
Generic