{-# LANGUAGE OverloadedStrings #-}
module Hydra.Sources.Tier4.Ext.Json.Decoding where
import Prelude hiding ((++))
import qualified Data.List as L
import qualified Data.Map as M
import qualified Data.Set as S
import qualified Data.Maybe as Y
import Hydra.Dsl.Base as Base
import qualified Hydra.Dsl.Core as Core
import qualified Hydra.Dsl.Graph as Graph
import qualified Hydra.Dsl.Lib.Equality as Equality
import qualified Hydra.Dsl.Lib.Flows as Flows
import qualified Hydra.Dsl.Lib.Io as Io
import qualified Hydra.Dsl.Lib.Lists as Lists
import qualified Hydra.Dsl.Lib.Literals as Literals
import qualified Hydra.Dsl.Lib.Logic as Logic
import qualified Hydra.Dsl.Lib.Maps as Maps
import qualified Hydra.Dsl.Lib.Math as Math
import qualified Hydra.Dsl.Lib.Optionals as Optionals
import qualified Hydra.Dsl.Lib.Sets as Sets
import Hydra.Dsl.Lib.Strings as Strings
import qualified Hydra.Dsl.Module as Module
import qualified Hydra.Dsl.Terms as Terms
import qualified Hydra.Dsl.Types as Types
import Hydra.Sources.Tier2.All
import qualified Hydra.Json as Json
import Hydra.Sources.Tier0.Json
jsonDecodingModule :: Module
jsonDecodingModule :: Module
jsonDecodingModule = Namespace
-> [Element] -> [Module] -> [Module] -> Maybe String -> Module
Module (String -> Namespace
Namespace String
"hydra/ext/org/json/decoding") [Element]
elements
[Module
jsonModelModule, Module
hydraCoreModule] (Module
jsonModelModuleModule -> [Module] -> [Module]
forall a. a -> [a] -> [a]
:[Module]
tier0Modules) (Maybe String -> Module) -> Maybe String -> Module
forall a b. (a -> b) -> a -> b
$
String -> Maybe String
forall a. a -> Maybe a
Just String
"Decoding functions for JSON data"
where
elements :: [Element]
elements = [
TElement (Value -> Flow Any String) -> Element
forall a. TElement a -> Element
Base.el TElement (Value -> Flow Any String)
forall s. TElement (Value -> Flow s String)
decodeStringDef,
TElement (Value -> Flow Any Double) -> Element
forall a. TElement a -> Element
Base.el TElement (Value -> Flow Any Double)
forall s. TElement (Value -> Flow s Double)
decodeNumberDef,
TElement (Value -> Flow Any Bool) -> Element
forall a. TElement a -> Element
Base.el TElement (Value -> Flow Any Bool)
forall s. TElement (Value -> Flow s Bool)
decodeBooleanDef,
TElement ((Value -> Flow Any Any) -> Value -> Flow Any [Any])
-> Element
forall a. TElement a -> Element
Base.el TElement ((Value -> Flow Any Any) -> Value -> Flow Any [Any])
forall s a. TElement ((Value -> Flow s a) -> Value -> Flow s [a])
decodeArrayDef,
TElement (Value -> Flow Any (Map String Value)) -> Element
forall a. TElement a -> Element
Base.el TElement (Value -> Flow Any (Map String Value))
forall s. TElement (Value -> Flow s (Map String Value))
decodeObjectDef,
TElement
((Value -> Flow Any Any)
-> String -> Map String Value -> Flow Any Any)
-> Element
forall a. TElement a -> Element
Base.el TElement
((Value -> Flow Any Any)
-> String -> Map String Value -> Flow Any Any)
forall s a.
TElement
((Value -> Flow s a) -> String -> Map String Value -> Flow s a)
decodeFieldDef,
TElement
((Value -> Flow Any Any)
-> String -> Map String Value -> Flow Any (Maybe Any))
-> Element
forall a. TElement a -> Element
Base.el TElement
((Value -> Flow Any Any)
-> String -> Map String Value -> Flow Any (Maybe Any))
forall s a.
TElement
((Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a))
decodeOptionalFieldDef]
jsonDecodingDefinition :: String -> TTerm a -> TElement a
jsonDecodingDefinition :: forall a. String -> TTerm a -> TElement a
jsonDecodingDefinition String
label = Module -> String -> TTerm a -> TElement a
forall a. Module -> String -> TTerm a -> TElement a
definitionInModule Module
jsonDecodingModule (String
"decode" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
label)
valueT :: Type
valueT = Name -> Type
TypeVariable Name
Json._Value
decodeStringDef :: TElement (Json.Value -> Flow s String)
decodeStringDef :: forall s. TElement (Value -> Flow s String)
decodeStringDef = String
-> TTerm (Value -> Flow s String)
-> TElement (Value -> Flow s String)
forall a. String -> TTerm a -> TElement a
jsonDecodingDefinition String
"String" (TTerm (Value -> Flow s String)
-> TElement (Value -> Flow s String))
-> TTerm (Value -> Flow s String)
-> TElement (Value -> Flow s String)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> TTerm (Value -> Flow s String)
-> TTerm (Value -> Flow s String)
forall a. Type -> Type -> TTerm a -> TTerm a
function Type
valueT (Type -> Type -> Type
flowT Type
sT Type
stringT) (TTerm (Value -> Flow s String) -> TTerm (Value -> Flow s String))
-> TTerm (Value -> Flow s String) -> TTerm (Value -> Flow s String)
forall a b. (a -> b) -> a -> b
$
Name
-> Maybe (TTerm (Flow s String))
-> [Field]
-> TTerm (Value -> Flow s String)
forall b u. Name -> Maybe (TTerm b) -> [Field] -> TTerm (u -> b)
match Name
Json._Value (TTerm (Flow s String) -> Maybe (TTerm (Flow s String))
forall a. a -> Maybe a
Just (TTerm (Flow s String) -> Maybe (TTerm (Flow s String)))
-> TTerm (Flow s String) -> Maybe (TTerm (Flow s String))
forall a b. (a -> b) -> a -> b
$ TTerm (String -> Flow s String)
forall s x. TTerm (String -> Flow s x)
Flows.fail TTerm (String -> Flow s String)
-> TTerm String -> TTerm (Flow s String)
forall a b. TTerm (a -> b) -> TTerm a -> TTerm b
@@ TTerm String
"expected a string") [
Name
Json._Value_stringName -> TTerm (Any -> Flow Any Any) -> Field
forall a. Name -> TTerm a -> Field
>>: TTerm (Any -> Flow Any Any)
forall x s. TTerm (x -> Flow s x)
Flows.pure]
decodeNumberDef :: TElement (Json.Value -> Flow s Double)
decodeNumberDef :: forall s. TElement (Value -> Flow s Double)
decodeNumberDef = String
-> TTerm (Value -> Flow s Double)
-> TElement (Value -> Flow s Double)
forall a. String -> TTerm a -> TElement a
jsonDecodingDefinition String
"Number" (TTerm (Value -> Flow s Double)
-> TElement (Value -> Flow s Double))
-> TTerm (Value -> Flow s Double)
-> TElement (Value -> Flow s Double)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> TTerm (Value -> Flow s Double)
-> TTerm (Value -> Flow s Double)
forall a. Type -> Type -> TTerm a -> TTerm a
function Type
valueT (Type -> Type -> Type
flowT Type
sT Type
Types.bigfloat) (TTerm (Value -> Flow s Double) -> TTerm (Value -> Flow s Double))
-> TTerm (Value -> Flow s Double) -> TTerm (Value -> Flow s Double)
forall a b. (a -> b) -> a -> b
$
Name
-> Maybe (TTerm (Flow s Double))
-> [Field]
-> TTerm (Value -> Flow s Double)
forall b u. Name -> Maybe (TTerm b) -> [Field] -> TTerm (u -> b)
match Name
Json._Value (TTerm (Flow s Double) -> Maybe (TTerm (Flow s Double))
forall a. a -> Maybe a
Just (TTerm (Flow s Double) -> Maybe (TTerm (Flow s Double)))
-> TTerm (Flow s Double) -> Maybe (TTerm (Flow s Double))
forall a b. (a -> b) -> a -> b
$ TTerm (String -> Flow s Double)
forall s x. TTerm (String -> Flow s x)
Flows.fail TTerm (String -> Flow s Double)
-> TTerm String -> TTerm (Flow s Double)
forall a b. TTerm (a -> b) -> TTerm a -> TTerm b
@@ TTerm String
"expected a number") [
Name
Json._Value_numberName -> TTerm (Any -> Flow Any Any) -> Field
forall a. Name -> TTerm a -> Field
>>: TTerm (Any -> Flow Any Any)
forall x s. TTerm (x -> Flow s x)
Flows.pure]
decodeBooleanDef :: TElement (Json.Value -> Flow s Bool)
decodeBooleanDef :: forall s. TElement (Value -> Flow s Bool)
decodeBooleanDef = String
-> TTerm (Value -> Flow s Bool) -> TElement (Value -> Flow s Bool)
forall a. String -> TTerm a -> TElement a
jsonDecodingDefinition String
"Boolean" (TTerm (Value -> Flow s Bool) -> TElement (Value -> Flow s Bool))
-> TTerm (Value -> Flow s Bool) -> TElement (Value -> Flow s Bool)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> TTerm (Value -> Flow s Bool)
-> TTerm (Value -> Flow s Bool)
forall a. Type -> Type -> TTerm a -> TTerm a
function Type
valueT (Type -> Type -> Type
flowT Type
sT Type
booleanT) (TTerm (Value -> Flow s Bool) -> TTerm (Value -> Flow s Bool))
-> TTerm (Value -> Flow s Bool) -> TTerm (Value -> Flow s Bool)
forall a b. (a -> b) -> a -> b
$
Name
-> Maybe (TTerm (Flow s Bool))
-> [Field]
-> TTerm (Value -> Flow s Bool)
forall b u. Name -> Maybe (TTerm b) -> [Field] -> TTerm (u -> b)
match Name
Json._Value (TTerm (Flow s Bool) -> Maybe (TTerm (Flow s Bool))
forall a. a -> Maybe a
Just (TTerm (Flow s Bool) -> Maybe (TTerm (Flow s Bool)))
-> TTerm (Flow s Bool) -> Maybe (TTerm (Flow s Bool))
forall a b. (a -> b) -> a -> b
$ TTerm (String -> Flow s Bool)
forall s x. TTerm (String -> Flow s x)
Flows.fail TTerm (String -> Flow s Bool)
-> TTerm String -> TTerm (Flow s Bool)
forall a b. TTerm (a -> b) -> TTerm a -> TTerm b
@@ TTerm String
"expected a boolean") [
Name
Json._Value_booleanName -> TTerm (Any -> Flow Any Any) -> Field
forall a. Name -> TTerm a -> Field
>>: TTerm (Any -> Flow Any Any)
forall x s. TTerm (x -> Flow s x)
Flows.pure]
decodeArrayDef :: TElement ((Json.Value -> Flow s a) -> Json.Value -> Flow s [a])
decodeArrayDef :: forall s a. TElement ((Value -> Flow s a) -> Value -> Flow s [a])
decodeArrayDef = String
-> TTerm ((Value -> Flow s a) -> Value -> Flow s [a])
-> TElement ((Value -> Flow s a) -> Value -> Flow s [a])
forall a. String -> TTerm a -> TElement a
jsonDecodingDefinition String
"Array" (TTerm ((Value -> Flow s a) -> Value -> Flow s [a])
-> TElement ((Value -> Flow s a) -> Value -> Flow s [a]))
-> TTerm ((Value -> Flow s a) -> Value -> Flow s [a])
-> TElement ((Value -> Flow s a) -> Value -> Flow s [a])
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> TTerm ((Value -> Flow s a) -> Value -> Flow s [a])
-> TTerm ((Value -> Flow s a) -> Value -> Flow s [a])
forall a. Type -> Type -> TTerm a -> TTerm a
function (Type -> Type -> Type
funT Type
valueT (Type -> Type -> Type
flowT Type
sT Type
aT)) (Type -> Type -> Type
funT Type
valueT (Type -> Type -> Type
flowT Type
sT (Type -> Type
listT Type
aT))) (TTerm ((Value -> Flow s a) -> Value -> Flow s [a])
-> TTerm ((Value -> Flow s a) -> Value -> Flow s [a]))
-> TTerm ((Value -> Flow s a) -> Value -> Flow s [a])
-> TTerm ((Value -> Flow s a) -> Value -> Flow s [a])
forall a b. (a -> b) -> a -> b
$
String
-> TTerm (Any -> Flow Any Any)
-> TTerm ((Value -> Flow s a) -> Value -> Flow s [a])
forall x a b. String -> TTerm x -> TTerm (a -> b)
lambda String
"decodeElem" (TTerm (Any -> Flow Any Any)
-> TTerm ((Value -> Flow s a) -> Value -> Flow s [a]))
-> TTerm (Any -> Flow Any Any)
-> TTerm ((Value -> Flow s a) -> Value -> Flow s [a])
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe (TTerm (Flow Any Any))
-> [Field]
-> TTerm (Any -> Flow Any Any)
forall b u. Name -> Maybe (TTerm b) -> [Field] -> TTerm (u -> b)
match Name
Json._Value (TTerm (Flow Any Any) -> Maybe (TTerm (Flow Any Any))
forall a. a -> Maybe a
Just (TTerm (Flow Any Any) -> Maybe (TTerm (Flow Any Any)))
-> TTerm (Flow Any Any) -> Maybe (TTerm (Flow Any Any))
forall a b. (a -> b) -> a -> b
$ TTerm (String -> Flow Any Any)
forall s x. TTerm (String -> Flow s x)
Flows.fail TTerm (String -> Flow Any Any)
-> TTerm String -> TTerm (Flow Any Any)
forall a b. TTerm (a -> b) -> TTerm a -> TTerm b
@@ TTerm String
"expected an array") [
Name
Json._Value_arrayName -> TTerm ([Any] -> Flow Any [Any]) -> Field
forall a. Name -> TTerm a -> Field
>>: TTerm ((Any -> Flow Any Any) -> [Any] -> Flow Any [Any])
forall x s y. TTerm ((x -> Flow s y) -> [x] -> Flow s [y])
Flows.mapList TTerm ((Any -> Flow Any Any) -> [Any] -> Flow Any [Any])
-> TTerm (Any -> Flow Any Any) -> TTerm ([Any] -> Flow Any [Any])
forall a b. TTerm (a -> b) -> TTerm a -> TTerm b
@@ (String -> TTerm (Any -> Flow Any Any)
forall a. String -> TTerm a
var String
"decodeElem")]
decodeObjectDef :: TElement (Json.Value -> Flow s (M.Map String Json.Value))
decodeObjectDef :: forall s. TElement (Value -> Flow s (Map String Value))
decodeObjectDef = String
-> TTerm (Value -> Flow s (Map String Value))
-> TElement (Value -> Flow s (Map String Value))
forall a. String -> TTerm a -> TElement a
jsonDecodingDefinition String
"Object" (TTerm (Value -> Flow s (Map String Value))
-> TElement (Value -> Flow s (Map String Value)))
-> TTerm (Value -> Flow s (Map String Value))
-> TElement (Value -> Flow s (Map String Value))
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> TTerm (Value -> Flow s (Map String Value))
-> TTerm (Value -> Flow s (Map String Value))
forall a. Type -> Type -> TTerm a -> TTerm a
function Type
valueT (Type -> Type -> Type
flowT Type
sT (Type -> Type -> Type
mapT Type
stringT Type
valueT)) (TTerm (Value -> Flow s (Map String Value))
-> TTerm (Value -> Flow s (Map String Value)))
-> TTerm (Value -> Flow s (Map String Value))
-> TTerm (Value -> Flow s (Map String Value))
forall a b. (a -> b) -> a -> b
$
Name
-> Maybe (TTerm (Flow s (Map String Value)))
-> [Field]
-> TTerm (Value -> Flow s (Map String Value))
forall b u. Name -> Maybe (TTerm b) -> [Field] -> TTerm (u -> b)
match Name
Json._Value (TTerm (Flow s (Map String Value))
-> Maybe (TTerm (Flow s (Map String Value)))
forall a. a -> Maybe a
Just (TTerm (Flow s (Map String Value))
-> Maybe (TTerm (Flow s (Map String Value))))
-> TTerm (Flow s (Map String Value))
-> Maybe (TTerm (Flow s (Map String Value)))
forall a b. (a -> b) -> a -> b
$ TTerm (String -> Flow s (Map String Value))
forall s x. TTerm (String -> Flow s x)
Flows.fail TTerm (String -> Flow s (Map String Value))
-> TTerm String -> TTerm (Flow s (Map String Value))
forall a b. TTerm (a -> b) -> TTerm a -> TTerm b
@@ TTerm String
"expected an object") [
Name
Json._Value_objectName -> TTerm (Any -> Flow Any Any) -> Field
forall a. Name -> TTerm a -> Field
>>: TTerm (Any -> Flow Any Any)
forall x s. TTerm (x -> Flow s x)
Flows.pure]
decodeFieldDef :: TElement ((Json.Value -> Flow s a) -> String -> (M.Map String Json.Value) -> Flow s a)
decodeFieldDef :: forall s a.
TElement
((Value -> Flow s a) -> String -> Map String Value -> Flow s a)
decodeFieldDef = String
-> TTerm
((Value -> Flow s a) -> String -> Map String Value -> Flow s a)
-> TElement
((Value -> Flow s a) -> String -> Map String Value -> Flow s a)
forall a. String -> TTerm a -> TElement a
jsonDecodingDefinition String
"Field" (TTerm
((Value -> Flow s a) -> String -> Map String Value -> Flow s a)
-> TElement
((Value -> Flow s a) -> String -> Map String Value -> Flow s a))
-> TTerm
((Value -> Flow s a) -> String -> Map String Value -> Flow s a)
-> TElement
((Value -> Flow s a) -> String -> Map String Value -> Flow s a)
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> TTerm
((Value -> Flow s a) -> String -> Map String Value -> Flow s a)
-> TTerm
((Value -> Flow s a) -> String -> Map String Value -> Flow s a)
forall a. Type -> Type -> TTerm a -> TTerm a
function (Type -> Type -> Type
funT Type
valueT (Type -> Type -> Type
flowT Type
sT Type
aT)) (Type -> Type -> Type
funT Type
stringT (Type -> Type -> Type
funT (Type -> Type -> Type
mapT Type
stringT Type
valueT) (Type -> Type -> Type
flowT Type
sT Type
aT))) (TTerm
((Value -> Flow s a) -> String -> Map String Value -> Flow s a)
-> TTerm
((Value -> Flow s a) -> String -> Map String Value -> Flow s a))
-> TTerm
((Value -> Flow s a) -> String -> Map String Value -> Flow s a)
-> TTerm
((Value -> Flow s a) -> String -> Map String Value -> Flow s a)
forall a b. (a -> b) -> a -> b
$
String
-> TTerm (Any -> Any)
-> TTerm
((Value -> Flow s a) -> String -> Map String Value -> Flow s a)
forall x a b. String -> TTerm x -> TTerm (a -> b)
lambda String
"decodeValue" (TTerm (Any -> Any)
-> TTerm
((Value -> Flow s a) -> String -> Map String Value -> Flow s a))
-> TTerm (Any -> Any)
-> TTerm
((Value -> Flow s a) -> String -> Map String Value -> Flow s a)
forall a b. (a -> b) -> a -> b
$ String -> TTerm (Any -> Any) -> TTerm (Any -> Any)
forall x a b. String -> TTerm x -> TTerm (a -> b)
lambda String
"name" (TTerm (Any -> Any) -> TTerm (Any -> Any))
-> TTerm (Any -> Any) -> TTerm (Any -> Any)
forall a b. (a -> b) -> a -> b
$ String -> TTerm (Flow Any Any) -> TTerm (Any -> Any)
forall x a b. String -> TTerm x -> TTerm (a -> b)
lambda String
"m" (TTerm (Flow Any Any) -> TTerm (Any -> Any))
-> TTerm (Flow Any Any) -> TTerm (Any -> Any)
forall a b. (a -> b) -> a -> b
$
TTerm
(Flow Any (Maybe Any)
-> (Maybe Any -> Flow Any Any) -> Flow Any Any)
forall s x y. TTerm (Flow s x -> (x -> Flow s y) -> Flow s y)
Flows.bind
TTerm
(Flow Any (Maybe Any)
-> (Maybe Any -> Flow Any Any) -> Flow Any Any)
-> TTerm (Flow Any (Maybe Any))
-> TTerm ((Maybe Any -> Flow Any Any) -> Flow Any Any)
forall a b. TTerm (a -> b) -> TTerm a -> TTerm b
@@ (TElement
((Value -> Flow Any Any)
-> String -> Map String Value -> Flow Any (Maybe Any))
-> TTerm
((Value -> Flow Any Any)
-> String -> Map String Value -> Flow Any (Maybe Any))
forall a. TElement a -> TTerm a
ref TElement
((Value -> Flow Any Any)
-> String -> Map String Value -> Flow Any (Maybe Any))
forall s a.
TElement
((Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a))
decodeOptionalFieldDef TTerm
((Value -> Flow Any Any)
-> String -> Map String Value -> Flow Any (Maybe Any))
-> TTerm (Value -> Flow Any Any)
-> TTerm (String -> Map String Value -> Flow Any (Maybe Any))
forall a b. TTerm (a -> b) -> TTerm a -> TTerm b
@@ String -> TTerm (Value -> Flow Any Any)
forall a. String -> TTerm a
var String
"decodeValue" TTerm (String -> Map String Value -> Flow Any (Maybe Any))
-> TTerm String -> TTerm (Map String Value -> Flow Any (Maybe Any))
forall a b. TTerm (a -> b) -> TTerm a -> TTerm b
@@ String -> TTerm String
forall a. String -> TTerm a
var String
"name" TTerm (Map String Value -> Flow Any (Maybe Any))
-> TTerm (Map String Value) -> TTerm (Flow Any (Maybe Any))
forall a b. TTerm (a -> b) -> TTerm a -> TTerm b
@@ String -> TTerm (Map String Value)
forall a. String -> TTerm a
var String
"m")
TTerm ((Maybe Any -> Flow Any Any) -> Flow Any Any)
-> TTerm (Maybe Any -> Flow Any Any) -> TTerm (Flow Any Any)
forall a b. TTerm (a -> b) -> TTerm a -> TTerm b
@@ (TTerm (Flow Any Any)
-> TTerm (Any -> Flow Any Any) -> TTerm (Maybe Any -> Flow Any Any)
forall b a. TTerm b -> TTerm (a -> b) -> TTerm (Maybe a -> b)
matchOpt (TTerm (String -> Flow Any Any)
forall s x. TTerm (String -> Flow s x)
Flows.fail TTerm (String -> Flow Any Any)
-> TTerm String -> TTerm (Flow Any Any)
forall a b. TTerm (a -> b) -> TTerm a -> TTerm b
@@ (TTerm String
"missing field: " TTerm String -> TTerm String -> TTerm String
++ String -> TTerm String
forall a. String -> TTerm a
var String
"name")) TTerm (Any -> Flow Any Any)
forall x s. TTerm (x -> Flow s x)
Flows.pure)
decodeOptionalFieldDef :: TElement ((Json.Value -> Flow s a) -> String -> (M.Map String Json.Value) -> Flow s (Maybe a))
decodeOptionalFieldDef :: forall s a.
TElement
((Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a))
decodeOptionalFieldDef = String
-> TTerm
((Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a))
-> TElement
((Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a))
forall a. String -> TTerm a -> TElement a
jsonDecodingDefinition String
"OptionalField" (TTerm
((Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a))
-> TElement
((Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a)))
-> TTerm
((Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a))
-> TElement
((Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a))
forall a b. (a -> b) -> a -> b
$
Type
-> Type
-> TTerm
((Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a))
-> TTerm
((Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a))
forall a. Type -> Type -> TTerm a -> TTerm a
function (Type -> Type -> Type
funT Type
valueT (Type -> Type -> Type
flowT Type
sT Type
aT)) (Type -> Type -> Type
funT Type
stringT (Type -> Type -> Type
funT (Type -> Type -> Type
mapT Type
stringT Type
valueT) (Type -> Type -> Type
flowT Type
sT (Type -> Type
Types.optional Type
aT)))) (TTerm
((Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a))
-> TTerm
((Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a)))
-> TTerm
((Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a))
-> TTerm
((Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a))
forall a b. (a -> b) -> a -> b
$
String
-> TTerm (Any -> Any)
-> TTerm
((Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a))
forall x a b. String -> TTerm x -> TTerm (a -> b)
lambda String
"decodeValue" (TTerm (Any -> Any)
-> TTerm
((Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a)))
-> TTerm (Any -> Any)
-> TTerm
((Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a))
forall a b. (a -> b) -> a -> b
$ String -> TTerm (Any -> Any) -> TTerm (Any -> Any)
forall x a b. String -> TTerm x -> TTerm (a -> b)
lambda String
"name" (TTerm (Any -> Any) -> TTerm (Any -> Any))
-> TTerm (Any -> Any) -> TTerm (Any -> Any)
forall a b. (a -> b) -> a -> b
$ String -> TTerm (Flow Any Any) -> TTerm (Any -> Any)
forall x a b. String -> TTerm x -> TTerm (a -> b)
lambda String
"m" (TTerm (Flow Any Any) -> TTerm (Any -> Any))
-> TTerm (Flow Any Any) -> TTerm (Any -> Any)
forall a b. (a -> b) -> a -> b
$
(TTerm (Flow Any Any)
-> TTerm (Any -> Flow Any Any) -> TTerm (Maybe Any -> Flow Any Any)
forall b a. TTerm b -> TTerm (a -> b) -> TTerm (Maybe a -> b)
matchOpt (TTerm (Any -> Flow Any Any)
forall x s. TTerm (x -> Flow s x)
Flows.pure TTerm (Any -> Flow Any Any) -> TTerm Any -> TTerm (Flow Any Any)
forall a b. TTerm (a -> b) -> TTerm a -> TTerm b
@@ TTerm Any
forall a. TTerm a
nothing) (String -> TTerm (Flow Any Any) -> TTerm (Any -> Flow Any Any)
forall x a b. String -> TTerm x -> TTerm (a -> b)
lambda String
"v" (TTerm ((Any -> Any) -> Flow Any Any -> Flow Any Any)
forall x y s. TTerm ((x -> y) -> Flow s x -> Flow s y)
Flows.map TTerm ((Any -> Any) -> Flow Any Any -> Flow Any Any)
-> TTerm (Any -> Any) -> TTerm (Flow Any Any -> Flow Any Any)
forall a b. TTerm (a -> b) -> TTerm a -> TTerm b
@@ (String -> TTerm (Maybe Any) -> TTerm (Any -> Any)
forall x a b. String -> TTerm x -> TTerm (a -> b)
lambda String
"x" (TTerm Any -> TTerm (Maybe Any)
forall x. TTerm x -> TTerm (Maybe x)
just (TTerm Any -> TTerm (Maybe Any)) -> TTerm Any -> TTerm (Maybe Any)
forall a b. (a -> b) -> a -> b
$ String -> TTerm Any
forall a. String -> TTerm a
var String
"x")) TTerm (Flow Any Any -> Flow Any Any)
-> TTerm (Flow Any Any) -> TTerm (Flow Any Any)
forall a b. TTerm (a -> b) -> TTerm a -> TTerm b
@@ (String -> TTerm (Any -> Flow Any Any)
forall a. String -> TTerm a
var String
"decodeValue" TTerm (Any -> Flow Any Any) -> TTerm Any -> TTerm (Flow Any Any)
forall a b. TTerm (a -> b) -> TTerm a -> TTerm b
@@ String -> TTerm Any
forall a. String -> TTerm a
var String
"v"))))
TTerm (Maybe Any -> Flow Any Any)
-> TTerm (Maybe Any) -> TTerm (Flow Any Any)
forall a b. TTerm (a -> b) -> TTerm a -> TTerm b
@@ (TTerm (Any -> Map Any Any -> Maybe Any)
forall k v. TTerm (k -> Map k v -> Maybe v)
Maps.lookup TTerm (Any -> Map Any Any -> Maybe Any)
-> TTerm Any -> TTerm (Map Any Any -> Maybe Any)
forall a b. TTerm (a -> b) -> TTerm a -> TTerm b
@@ String -> TTerm Any
forall a. String -> TTerm a
var String
"name" TTerm (Map Any Any -> Maybe Any)
-> TTerm (Map Any Any) -> TTerm (Maybe Any)
forall a b. TTerm (a -> b) -> TTerm a -> TTerm b
@@ String -> TTerm (Map Any Any)
forall a. String -> TTerm a
var String
"m")