module Hydra.Compute where
import qualified Hydra.Core as Core
import Data.Int
import Data.List as L
import Data.Map as M
import Data.Set as S
data Adapter s1 s2 t1 t2 v1 v2 =
Adapter {
forall s1 s2 t1 t2 v1 v2. Adapter s1 s2 t1 t2 v1 v2 -> Bool
adapterIsLossy :: Bool,
forall s1 s2 t1 t2 v1 v2. Adapter s1 s2 t1 t2 v1 v2 -> t1
adapterSource :: t1,
forall s1 s2 t1 t2 v1 v2. Adapter s1 s2 t1 t2 v1 v2 -> t2
adapterTarget :: t2,
forall s1 s2 t1 t2 v1 v2.
Adapter s1 s2 t1 t2 v1 v2 -> Coder s1 s2 v1 v2
adapterCoder :: (Coder s1 s2 v1 v2)}
_Adapter :: Name
_Adapter = (String -> Name
Core.Name String
"hydra/compute.Adapter")
_Adapter_isLossy :: Name
_Adapter_isLossy = (String -> Name
Core.Name String
"isLossy")
_Adapter_source :: Name
_Adapter_source = (String -> Name
Core.Name String
"source")
_Adapter_target :: Name
_Adapter_target = (String -> Name
Core.Name String
"target")
_Adapter_coder :: Name
_Adapter_coder = (String -> Name
Core.Name String
"coder")
data Bicoder s1 s2 t1 t2 v1 v2 =
Bicoder {
forall s1 s2 t1 t2 v1 v2.
Bicoder s1 s2 t1 t2 v1 v2 -> t1 -> Adapter s1 s2 t1 t2 v1 v2
bicoderEncode :: (t1 -> Adapter s1 s2 t1 t2 v1 v2),
forall s1 s2 t1 t2 v1 v2.
Bicoder s1 s2 t1 t2 v1 v2 -> t2 -> Adapter s2 s1 t2 t1 v2 v1
bicoderDecode :: (t2 -> Adapter s2 s1 t2 t1 v2 v1)}
_Bicoder :: Name
_Bicoder = (String -> Name
Core.Name String
"hydra/compute.Bicoder")
_Bicoder_encode :: Name
_Bicoder_encode = (String -> Name
Core.Name String
"encode")
_Bicoder_decode :: Name
_Bicoder_decode = (String -> Name
Core.Name String
"decode")
data Coder s1 s2 v1 v2 =
Coder {
forall s1 s2 v1 v2. Coder s1 s2 v1 v2 -> v1 -> Flow s1 v2
coderEncode :: (v1 -> Flow s1 v2),
forall s1 s2 v1 v2. Coder s1 s2 v1 v2 -> v2 -> Flow s2 v1
coderDecode :: (v2 -> Flow s2 v1)}
_Coder :: Name
_Coder = (String -> Name
Core.Name String
"hydra/compute.Coder")
_Coder_encode :: Name
_Coder_encode = (String -> Name
Core.Name String
"encode")
_Coder_decode :: Name
_Coder_decode = (String -> Name
Core.Name String
"decode")
newtype Flow s x =
Flow {
forall s x. Flow s x -> s -> Trace -> FlowState s x
unFlow :: (s -> Trace -> FlowState s x)}
_Flow :: Name
_Flow = (String -> Name
Core.Name String
"hydra/compute.Flow")
data FlowState s x =
FlowState {
forall s x. FlowState s x -> Maybe x
flowStateValue :: (Maybe x),
forall s x. FlowState s x -> s
flowStateState :: s,
forall s x. FlowState s x -> Trace
flowStateTrace :: Trace}
deriving (FlowState s x -> FlowState s x -> Bool
(FlowState s x -> FlowState s x -> Bool)
-> (FlowState s x -> FlowState s x -> Bool) -> Eq (FlowState s x)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall s x. (Eq x, Eq s) => FlowState s x -> FlowState s x -> Bool
$c== :: forall s x. (Eq x, Eq s) => FlowState s x -> FlowState s x -> Bool
== :: FlowState s x -> FlowState s x -> Bool
$c/= :: forall s x. (Eq x, Eq s) => FlowState s x -> FlowState s x -> Bool
/= :: FlowState s x -> FlowState s x -> Bool
Eq, Eq (FlowState s x)
Eq (FlowState s x) =>
(FlowState s x -> FlowState s x -> Ordering)
-> (FlowState s x -> FlowState s x -> Bool)
-> (FlowState s x -> FlowState s x -> Bool)
-> (FlowState s x -> FlowState s x -> Bool)
-> (FlowState s x -> FlowState s x -> Bool)
-> (FlowState s x -> FlowState s x -> FlowState s x)
-> (FlowState s x -> FlowState s x -> FlowState s x)
-> Ord (FlowState s x)
FlowState s x -> FlowState s x -> Bool
FlowState s x -> FlowState s x -> Ordering
FlowState s x -> FlowState s x -> FlowState s x
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall s x. (Ord x, Ord s) => Eq (FlowState s x)
forall s x.
(Ord x, Ord s) =>
FlowState s x -> FlowState s x -> Bool
forall s x.
(Ord x, Ord s) =>
FlowState s x -> FlowState s x -> Ordering
forall s x.
(Ord x, Ord s) =>
FlowState s x -> FlowState s x -> FlowState s x
$ccompare :: forall s x.
(Ord x, Ord s) =>
FlowState s x -> FlowState s x -> Ordering
compare :: FlowState s x -> FlowState s x -> Ordering
$c< :: forall s x.
(Ord x, Ord s) =>
FlowState s x -> FlowState s x -> Bool
< :: FlowState s x -> FlowState s x -> Bool
$c<= :: forall s x.
(Ord x, Ord s) =>
FlowState s x -> FlowState s x -> Bool
<= :: FlowState s x -> FlowState s x -> Bool
$c> :: forall s x.
(Ord x, Ord s) =>
FlowState s x -> FlowState s x -> Bool
> :: FlowState s x -> FlowState s x -> Bool
$c>= :: forall s x.
(Ord x, Ord s) =>
FlowState s x -> FlowState s x -> Bool
>= :: FlowState s x -> FlowState s x -> Bool
$cmax :: forall s x.
(Ord x, Ord s) =>
FlowState s x -> FlowState s x -> FlowState s x
max :: FlowState s x -> FlowState s x -> FlowState s x
$cmin :: forall s x.
(Ord x, Ord s) =>
FlowState s x -> FlowState s x -> FlowState s x
min :: FlowState s x -> FlowState s x -> FlowState s x
Ord, ReadPrec [FlowState s x]
ReadPrec (FlowState s x)
Int -> ReadS (FlowState s x)
ReadS [FlowState s x]
(Int -> ReadS (FlowState s x))
-> ReadS [FlowState s x]
-> ReadPrec (FlowState s x)
-> ReadPrec [FlowState s x]
-> Read (FlowState s x)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall s x. (Read x, Read s) => ReadPrec [FlowState s x]
forall s x. (Read x, Read s) => ReadPrec (FlowState s x)
forall s x. (Read x, Read s) => Int -> ReadS (FlowState s x)
forall s x. (Read x, Read s) => ReadS [FlowState s x]
$creadsPrec :: forall s x. (Read x, Read s) => Int -> ReadS (FlowState s x)
readsPrec :: Int -> ReadS (FlowState s x)
$creadList :: forall s x. (Read x, Read s) => ReadS [FlowState s x]
readList :: ReadS [FlowState s x]
$creadPrec :: forall s x. (Read x, Read s) => ReadPrec (FlowState s x)
readPrec :: ReadPrec (FlowState s x)
$creadListPrec :: forall s x. (Read x, Read s) => ReadPrec [FlowState s x]
readListPrec :: ReadPrec [FlowState s x]
Read, Int -> FlowState s x -> ShowS
[FlowState s x] -> ShowS
FlowState s x -> String
(Int -> FlowState s x -> ShowS)
-> (FlowState s x -> String)
-> ([FlowState s x] -> ShowS)
-> Show (FlowState s x)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall s x. (Show x, Show s) => Int -> FlowState s x -> ShowS
forall s x. (Show x, Show s) => [FlowState s x] -> ShowS
forall s x. (Show x, Show s) => FlowState s x -> String
$cshowsPrec :: forall s x. (Show x, Show s) => Int -> FlowState s x -> ShowS
showsPrec :: Int -> FlowState s x -> ShowS
$cshow :: forall s x. (Show x, Show s) => FlowState s x -> String
show :: FlowState s x -> String
$cshowList :: forall s x. (Show x, Show s) => [FlowState s x] -> ShowS
showList :: [FlowState s x] -> ShowS
Show)
_FlowState :: Name
_FlowState = (String -> Name
Core.Name String
"hydra/compute.FlowState")
_FlowState_value :: Name
_FlowState_value = (String -> Name
Core.Name String
"value")
_FlowState_state :: Name
_FlowState_state = (String -> Name
Core.Name String
"state")
_FlowState_trace :: Name
_FlowState_trace = (String -> Name
Core.Name String
"trace")
data Trace =
Trace {
Trace -> [String]
traceStack :: [String],
Trace -> [String]
traceMessages :: [String],
Trace -> Map String Term
traceOther :: (Map String Core.Term)}
deriving (Trace -> Trace -> Bool
(Trace -> Trace -> Bool) -> (Trace -> Trace -> Bool) -> Eq Trace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Trace -> Trace -> Bool
== :: Trace -> Trace -> Bool
$c/= :: Trace -> Trace -> Bool
/= :: Trace -> Trace -> Bool
Eq, Eq Trace
Eq Trace =>
(Trace -> Trace -> Ordering)
-> (Trace -> Trace -> Bool)
-> (Trace -> Trace -> Bool)
-> (Trace -> Trace -> Bool)
-> (Trace -> Trace -> Bool)
-> (Trace -> Trace -> Trace)
-> (Trace -> Trace -> Trace)
-> Ord Trace
Trace -> Trace -> Bool
Trace -> Trace -> Ordering
Trace -> Trace -> Trace
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Trace -> Trace -> Ordering
compare :: Trace -> Trace -> Ordering
$c< :: Trace -> Trace -> Bool
< :: Trace -> Trace -> Bool
$c<= :: Trace -> Trace -> Bool
<= :: Trace -> Trace -> Bool
$c> :: Trace -> Trace -> Bool
> :: Trace -> Trace -> Bool
$c>= :: Trace -> Trace -> Bool
>= :: Trace -> Trace -> Bool
$cmax :: Trace -> Trace -> Trace
max :: Trace -> Trace -> Trace
$cmin :: Trace -> Trace -> Trace
min :: Trace -> Trace -> Trace
Ord, ReadPrec [Trace]
ReadPrec Trace
Int -> ReadS Trace
ReadS [Trace]
(Int -> ReadS Trace)
-> ReadS [Trace]
-> ReadPrec Trace
-> ReadPrec [Trace]
-> Read Trace
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Trace
readsPrec :: Int -> ReadS Trace
$creadList :: ReadS [Trace]
readList :: ReadS [Trace]
$creadPrec :: ReadPrec Trace
readPrec :: ReadPrec Trace
$creadListPrec :: ReadPrec [Trace]
readListPrec :: ReadPrec [Trace]
Read, Int -> Trace -> ShowS
[Trace] -> ShowS
Trace -> String
(Int -> Trace -> ShowS)
-> (Trace -> String) -> ([Trace] -> ShowS) -> Show Trace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Trace -> ShowS
showsPrec :: Int -> Trace -> ShowS
$cshow :: Trace -> String
show :: Trace -> String
$cshowList :: [Trace] -> ShowS
showList :: [Trace] -> ShowS
Show)
_Trace :: Name
_Trace = (String -> Name
Core.Name String
"hydra/compute.Trace")
_Trace_stack :: Name
_Trace_stack = (String -> Name
Core.Name String
"stack")
_Trace_messages :: Name
_Trace_messages = (String -> Name
Core.Name String
"messages")
_Trace_other :: Name
_Trace_other = (String -> Name
Core.Name String
"other")