module Hydra.Tier2 where
import qualified Hydra.Compute as Compute
import qualified Hydra.Core as Core
import qualified Hydra.Graph as Graph
import qualified Hydra.Lib.Flows as Flows
import qualified Hydra.Lib.Strings as Strings
import Data.Int
import Data.List as L
import Data.Map as M
import Data.Set as S
getState :: (Compute.Flow s s)
getState :: forall s. Flow s s
getState = ((s -> Trace -> FlowState s s) -> Flow s s
forall s x. (s -> Trace -> FlowState s x) -> Flow s x
Compute.Flow (\s
s0 -> \Trace
t0 ->
let fs1 :: FlowState s ()
fs1 = (Flow s () -> s -> Trace -> FlowState s ()
forall s x. Flow s x -> s -> Trace -> FlowState s x
Compute.unFlow (() -> Flow s ()
forall x s. x -> Flow s x
Flows.pure ()) s
s0 Trace
t0)
in ((\Maybe ()
v -> \s
s -> \Trace
t -> (\Maybe ()
x -> case Maybe ()
x of
Maybe ()
Nothing -> Compute.FlowState {
flowStateValue :: Maybe s
Compute.flowStateValue = Maybe s
forall a. Maybe a
Nothing,
flowStateState :: s
Compute.flowStateState = s
s,
flowStateTrace :: Trace
Compute.flowStateTrace = Trace
t}
Just ()
_ -> Compute.FlowState {
flowStateValue :: Maybe s
Compute.flowStateValue = (s -> Maybe s
forall a. a -> Maybe a
Just s
s),
flowStateState :: s
Compute.flowStateState = s
s,
flowStateTrace :: Trace
Compute.flowStateTrace = Trace
t}) Maybe ()
v) (FlowState s () -> Maybe ()
forall s x. FlowState s x -> Maybe x
Compute.flowStateValue FlowState s ()
fs1) (FlowState s () -> s
forall s x. FlowState s x -> s
Compute.flowStateState FlowState s ()
fs1) (FlowState s () -> Trace
forall s x. FlowState s x -> Trace
Compute.flowStateTrace FlowState s ()
fs1))))
getTermType :: (Core.Term -> Maybe Core.Type)
getTermType :: Term -> Maybe Type
getTermType Term
x = case Term
x of
Core.TermAnnotated AnnotatedTerm
v315 -> (Term -> Maybe Type
getTermType (AnnotatedTerm -> Term
Core.annotatedTermSubject AnnotatedTerm
v315))
Core.TermTyped TypedTerm
v316 -> (Type -> Maybe Type
forall a. a -> Maybe a
Just (TypedTerm -> Type
Core.typedTermType TypedTerm
v316))
Term
_ -> Maybe Type
forall a. Maybe a
Nothing
putState :: (s -> Compute.Flow s ())
putState :: forall s. s -> Flow s ()
putState s
cx = ((s -> Trace -> FlowState s ()) -> Flow s ()
forall s x. (s -> Trace -> FlowState s x) -> Flow s x
Compute.Flow (\s
s0 -> \Trace
t0 ->
let f1 :: FlowState s ()
f1 = (Flow s () -> s -> Trace -> FlowState s ()
forall s x. Flow s x -> s -> Trace -> FlowState s x
Compute.unFlow (() -> Flow s ()
forall x s. x -> Flow s x
Flows.pure ()) s
s0 Trace
t0)
in Compute.FlowState {
flowStateValue :: Maybe ()
Compute.flowStateValue = (FlowState s () -> Maybe ()
forall s x. FlowState s x -> Maybe x
Compute.flowStateValue FlowState s ()
f1),
flowStateState :: s
Compute.flowStateState = s
cx,
flowStateTrace :: Trace
Compute.flowStateTrace = (FlowState s () -> Trace
forall s x. FlowState s x -> Trace
Compute.flowStateTrace FlowState s ()
f1)}))
requireElementType :: (Graph.Element -> Compute.Flow Graph.Graph Core.Type)
requireElementType :: Element -> Flow Graph Type
requireElementType Element
el =
let withType :: Maybe x -> Flow s x
withType = (\Maybe x
x -> case Maybe x
x of
Maybe x
Nothing -> (String -> Flow s x
forall s x. String -> Flow s x
Flows.fail ([String] -> String
Strings.cat [
String
"missing type annotation for element ",
(Name -> String
Core.unName (Element -> Name
Graph.elementName Element
el))]))
Just x
v317 -> (x -> Flow s x
forall x s. x -> Flow s x
Flows.pure x
v317))
in (Maybe Type -> Flow Graph Type
forall {x} {s}. Maybe x -> Flow s x
withType (Term -> Maybe Type
getTermType (Element -> Term
Graph.elementData Element
el)))
requireTermType :: (Core.Term -> Compute.Flow Graph.Graph Core.Type)
requireTermType :: Term -> Flow Graph Type
requireTermType Term
x = (Maybe Type -> Flow Graph Type
forall {x} {s}. Maybe x -> Flow s x
withType (Term -> Maybe Type
getTermType Term
x))
where
withType :: Maybe x -> Flow s x
withType = (\Maybe x
x -> case Maybe x
x of
Maybe x
Nothing -> (String -> Flow s x
forall s x. String -> Flow s x
Flows.fail String
"missing type annotation")
Just x
v318 -> (x -> Flow s x
forall x s. x -> Flow s x
Flows.pure x
v318))
unexpected :: (String -> String -> Compute.Flow s x)
unexpected :: forall s x. String -> String -> Flow s x
unexpected String
expected String
actual = (String -> Flow s x
forall s x. String -> Flow s x
Flows.fail ([String] -> String
Strings.cat [
[String] -> String
Strings.cat [
[String] -> String
Strings.cat [
String
"expected ",
String
expected],
String
" but found: "],
String
actual]))