module Hydra.Dsl.Lib.Flows where
import Hydra.Dsl.Base
import Hydra.Core
import Hydra.Compute
import Hydra.Phantoms
import Hydra.Sources.Libraries
import qualified Hydra.Dsl.Terms as Terms
import qualified Hydra.Dsl.Types as Types
import qualified Data.Map as M
apply :: TTerm (Flow s (x -> y) -> Flow s x -> Flow s y)
apply :: forall s x y. TTerm (Flow s (x -> y) -> Flow s x -> Flow s y)
apply = Term -> TTerm (Flow s (x -> y) -> Flow s x -> Flow s y)
forall a. Term -> TTerm a
TTerm (Term -> TTerm (Flow s (x -> y) -> Flow s x -> Flow s y))
-> Term -> TTerm (Flow s (x -> y) -> Flow s x -> Flow s y)
forall a b. (a -> b) -> a -> b
$ Name -> Term
Terms.primitive Name
_flows_apply
bind :: TTerm (Flow s x -> (x -> Flow s y) -> Flow s y)
bind :: forall s x y. TTerm (Flow s x -> (x -> Flow s y) -> Flow s y)
bind = Term -> TTerm (Flow s x -> (x -> Flow s y) -> Flow s y)
forall a. Term -> TTerm a
TTerm (Term -> TTerm (Flow s x -> (x -> Flow s y) -> Flow s y))
-> Term -> TTerm (Flow s x -> (x -> Flow s y) -> Flow s y)
forall a b. (a -> b) -> a -> b
$ Name -> Term
Terms.primitive Name
_flows_bind
fail :: TTerm (String -> Flow s x)
fail :: forall s x. TTerm (String -> Flow s x)
fail = Term -> TTerm (String -> Flow s x)
forall a. Term -> TTerm a
TTerm (Term -> TTerm (String -> Flow s x))
-> Term -> TTerm (String -> Flow s x)
forall a b. (a -> b) -> a -> b
$ Name -> Term
Terms.primitive Name
_flows_fail
map :: TTerm ((x -> y) -> Flow s x -> Flow s y)
map :: forall x y s. TTerm ((x -> y) -> Flow s x -> Flow s y)
map = Term -> TTerm ((x -> y) -> Flow s x -> Flow s y)
forall a. Term -> TTerm a
TTerm (Term -> TTerm ((x -> y) -> Flow s x -> Flow s y))
-> Term -> TTerm ((x -> y) -> Flow s x -> Flow s y)
forall a b. (a -> b) -> a -> b
$ Name -> Term
Terms.primitive Name
_flows_map
mapList :: TTerm ((x -> Flow s y) -> [x] -> Flow s [y])
mapList :: forall x s y. TTerm ((x -> Flow s y) -> [x] -> Flow s [y])
mapList = Term -> TTerm ((x -> Flow s y) -> [x] -> Flow s [y])
forall a. Term -> TTerm a
TTerm (Term -> TTerm ((x -> Flow s y) -> [x] -> Flow s [y]))
-> Term -> TTerm ((x -> Flow s y) -> [x] -> Flow s [y])
forall a b. (a -> b) -> a -> b
$ Name -> Term
Terms.primitive Name
_flows_mapList
pure :: TTerm (x -> Flow s x)
pure :: forall x s. TTerm (x -> Flow s x)
pure = Term -> TTerm (x -> Flow s x)
forall a. Term -> TTerm a
TTerm (Term -> TTerm (x -> Flow s x)) -> Term -> TTerm (x -> Flow s x)
forall a b. (a -> b) -> a -> b
$ Name -> Term
Terms.primitive Name
_flows_pure
sequence :: TTerm ([Flow s a] -> Flow s [a])
sequence :: forall s a. TTerm ([Flow s a] -> Flow s [a])
sequence = Term -> TTerm ([Flow s a] -> Flow s [a])
forall a. Term -> TTerm a
TTerm (Term -> TTerm ([Flow s a] -> Flow s [a]))
-> Term -> TTerm ([Flow s a] -> Flow s [a])
forall a b. (a -> b) -> a -> b
$ Name -> Term
Terms.primitive Name
_flows_sequence
flowState :: TTerm (Maybe x) -> TTerm s -> TTerm Trace -> TTerm (FlowState s x)
flowState :: forall x s.
TTerm (Maybe x) -> TTerm s -> TTerm Trace -> TTerm (FlowState s x)
flowState TTerm (Maybe x)
value TTerm s
state TTerm Trace
trace = Name -> [Field] -> TTerm (FlowState s x)
forall a. Name -> [Field] -> TTerm a
record Name
_FlowState [
Name
_FlowState_valueName -> TTerm (Maybe x) -> Field
forall a. Name -> TTerm a -> Field
>>: TTerm (Maybe x)
value,
Name
_FlowState_stateName -> TTerm s -> Field
forall a. Name -> TTerm a -> Field
>>: TTerm s
state,
Name
_FlowState_traceName -> TTerm Trace -> Field
forall a. Name -> TTerm a -> Field
>>: TTerm Trace
trace]
flowStateState :: TTerm (FlowState s x -> s)
flowStateState :: forall s x. TTerm (FlowState s x -> s)
flowStateState = Name -> Name -> TTerm (FlowState s x -> s)
forall a b. Name -> Name -> TTerm (a -> b)
project Name
_FlowState Name
_FlowState_state
flowStateTrace :: TTerm (FlowState s x -> Trace)
flowStateTrace :: forall s x. TTerm (FlowState s x -> Trace)
flowStateTrace = Name -> Name -> TTerm (FlowState s x -> Trace)
forall a b. Name -> Name -> TTerm (a -> b)
project Name
_FlowState Name
_FlowState_trace
flowStateValue :: TTerm (FlowState s x -> Maybe x)
flowStateValue :: forall s x. TTerm (FlowState s x -> Maybe x)
flowStateValue = Name -> Name -> TTerm (FlowState s x -> Maybe x)
forall a b. Name -> Name -> TTerm (a -> b)
project Name
_FlowState Name
_FlowState_value
trace :: TTerm [String] -> TTerm [String] -> TTerm (M.Map String (Term)) -> TTerm Trace
trace :: TTerm [String]
-> TTerm [String] -> TTerm (Map String Term) -> TTerm Trace
trace TTerm [String]
stack TTerm [String]
messages TTerm (Map String Term)
other = Name -> [Field] -> TTerm Trace
forall a. Name -> [Field] -> TTerm a
record Name
_Trace [
Name
_Trace_stackName -> TTerm [String] -> Field
forall a. Name -> TTerm a -> Field
>>: TTerm [String]
stack,
Name
_Trace_messagesName -> TTerm [String] -> Field
forall a. Name -> TTerm a -> Field
>>: TTerm [String]
messages,
Name
_Trace_otherName -> TTerm (Map String Term) -> Field
forall a. Name -> TTerm a -> Field
>>: TTerm (Map String Term)
other]
traceStack :: TTerm (Trace -> [String])
traceStack :: TTerm (Trace -> [String])
traceStack = Name -> Name -> TTerm (Trace -> [String])
forall a b. Name -> Name -> TTerm (a -> b)
project Name
_Trace Name
_Trace_stack
traceMessages :: TTerm (Trace -> [String])
traceMessages :: TTerm (Trace -> [String])
traceMessages = Name -> Name -> TTerm (Trace -> [String])
forall a b. Name -> Name -> TTerm (a -> b)
project Name
_Trace Name
_Trace_messages
traceOther :: TTerm (Trace -> M.Map String (Term))
traceOther :: TTerm (Trace -> Map String Term)
traceOther = Name -> Name -> TTerm (Trace -> Map String Term)
forall a b. Name -> Name -> TTerm (a -> b)
project Name
_Trace Name
_Trace_other
unFlow :: TTerm (Flow s x -> s -> Trace -> FlowState s x)
unFlow :: forall s x. TTerm (Flow s x -> s -> Trace -> FlowState s x)
unFlow = Name -> TTerm (Flow s x -> s -> Trace -> FlowState s x)
forall a b. Name -> TTerm (a -> b)
unwrap Name
_Flow