{-# LANGUAGE DeriveGeneric #-}
module Dhall.Syntax.Binding
( Binding(..)
, makeBinding
, bindingExprs
) where
import Data.Text (Text)
import {-# SOURCE #-} Dhall.Syntax.Expr (Expr)
import GHC.Generics (Generic)
data Binding s a = Binding
{ forall s a. Binding s a -> Maybe s
bindingSrc0 :: Maybe s
, forall s a. Binding s a -> Text
variable :: Text
, forall s a. Binding s a -> Maybe s
bindingSrc1 :: Maybe s
, forall s a. Binding s a -> Maybe (Maybe s, Expr s a)
annotation :: Maybe (Maybe s, Expr s a)
, forall s a. Binding s a -> Maybe s
bindingSrc2 :: Maybe s
, forall s a. Binding s a -> Expr s a
value :: Expr s a
} deriving (forall x. Binding s a -> Rep (Binding s a) x)
-> (forall x. Rep (Binding s a) x -> Binding s a)
-> Generic (Binding s a)
forall x. Rep (Binding s a) x -> Binding s a
forall x. Binding s a -> Rep (Binding s a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall s a x. Rep (Binding s a) x -> Binding s a
forall s a x. Binding s a -> Rep (Binding s a) x
$cfrom :: forall s a x. Binding s a -> Rep (Binding s a) x
from :: forall x. Binding s a -> Rep (Binding s a) x
$cto :: forall s a x. Rep (Binding s a) x -> Binding s a
to :: forall x. Rep (Binding s a) x -> Binding s a
Generic
makeBinding :: Text -> Expr s a -> Binding s a
makeBinding :: forall s a. Text -> Expr s a -> Binding s a
makeBinding Text
name = Maybe s
-> Text
-> Maybe s
-> Maybe (Maybe s, Expr s a)
-> Maybe s
-> Expr s a
-> Binding s a
forall s a.
Maybe s
-> Text
-> Maybe s
-> Maybe (Maybe s, Expr s a)
-> Maybe s
-> Expr s a
-> Binding s a
Binding Maybe s
forall a. Maybe a
Nothing Text
name Maybe s
forall a. Maybe a
Nothing Maybe (Maybe s, Expr s a)
forall a. Maybe a
Nothing Maybe s
forall a. Maybe a
Nothing
bindingExprs
:: (Applicative f)
=> (Expr s a -> f (Expr s b))
-> Binding s a -> f (Binding s b)
bindingExprs :: forall (f :: * -> *) s a b.
Applicative f =>
(Expr s a -> f (Expr s b)) -> Binding s a -> f (Binding s b)
bindingExprs Expr s a -> f (Expr s b)
f (Binding Maybe s
s0 Text
n Maybe s
s1 Maybe (Maybe s, Expr s a)
t Maybe s
s2 Expr s a
v) =
Maybe s
-> Text
-> Maybe s
-> Maybe (Maybe s, Expr s b)
-> Maybe s
-> Expr s b
-> Binding s b
forall s a.
Maybe s
-> Text
-> Maybe s
-> Maybe (Maybe s, Expr s a)
-> Maybe s
-> Expr s a
-> Binding s a
Binding
(Maybe s
-> Text
-> Maybe s
-> Maybe (Maybe s, Expr s b)
-> Maybe s
-> Expr s b
-> Binding s b)
-> f (Maybe s)
-> f (Text
-> Maybe s
-> Maybe (Maybe s, Expr s b)
-> Maybe s
-> Expr s b
-> Binding s b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe s -> f (Maybe s)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe s
s0
f (Text
-> Maybe s
-> Maybe (Maybe s, Expr s b)
-> Maybe s
-> Expr s b
-> Binding s b)
-> f Text
-> f (Maybe s
-> Maybe (Maybe s, Expr s b) -> Maybe s -> Expr s b -> Binding s b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> f Text
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
n
f (Maybe s
-> Maybe (Maybe s, Expr s b) -> Maybe s -> Expr s b -> Binding s b)
-> f (Maybe s)
-> f (Maybe (Maybe s, Expr s b)
-> Maybe s -> Expr s b -> Binding s b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe s -> f (Maybe s)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe s
s1
f (Maybe (Maybe s, Expr s b) -> Maybe s -> Expr s b -> Binding s b)
-> f (Maybe (Maybe s, Expr s b))
-> f (Maybe s -> Expr s b -> Binding s b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Maybe s, Expr s a) -> f (Maybe s, Expr s b))
-> Maybe (Maybe s, Expr s a) -> f (Maybe (Maybe s, Expr s b))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Maybe a -> f (Maybe b)
traverse ((Expr s a -> f (Expr s b))
-> (Maybe s, Expr s a) -> f (Maybe s, Expr s b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> (Maybe s, a) -> f (Maybe s, b)
traverse Expr s a -> f (Expr s b)
f) Maybe (Maybe s, Expr s a)
t
f (Maybe s -> Expr s b -> Binding s b)
-> f (Maybe s) -> f (Expr s b -> Binding s b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe s -> f (Maybe s)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe s
s2
f (Expr s b -> Binding s b) -> f (Expr s b) -> f (Binding s b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Expr s a -> f (Expr s b)
f Expr s a
v
{-# INLINABLE bindingExprs #-}