module Hydra.Langs.Json.Decoding where
import qualified Hydra.Compute as Compute
import qualified Hydra.Json as Json
import qualified Hydra.Lib.Flows as Flows
import qualified Hydra.Lib.Maps as Maps
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
decodeString :: (Json.Value -> Compute.Flow s String)
decodeString :: forall s. Value -> Flow s String
decodeString Value
x = case Value
x of
Json.ValueString String
v277 -> (String -> Flow s String
forall x s. x -> Flow s x
Flows.pure String
v277)
Value
_ -> (String -> Flow s String
forall s x. String -> Flow s x
Flows.fail String
"expected a string")
decodeNumber :: (Json.Value -> Compute.Flow s Double)
decodeNumber :: forall s. Value -> Flow s Double
decodeNumber Value
x = case Value
x of
Json.ValueNumber Double
v278 -> (Double -> Flow s Double
forall x s. x -> Flow s x
Flows.pure Double
v278)
Value
_ -> (String -> Flow s Double
forall s x. String -> Flow s x
Flows.fail String
"expected a number")
decodeBoolean :: (Json.Value -> Compute.Flow s Bool)
decodeBoolean :: forall s. Value -> Flow s Bool
decodeBoolean Value
x = case Value
x of
Json.ValueBoolean Bool
v279 -> (Bool -> Flow s Bool
forall x s. x -> Flow s x
Flows.pure Bool
v279)
Value
_ -> (String -> Flow s Bool
forall s x. String -> Flow s x
Flows.fail String
"expected a boolean")
decodeArray :: ((Json.Value -> Compute.Flow s a) -> Json.Value -> Compute.Flow s [a])
decodeArray :: forall s a. (Value -> Flow s a) -> Value -> Flow s [a]
decodeArray Value -> Flow s a
decodeElem Value
x = case Value
x of
Json.ValueArray [Value]
v280 -> ((Value -> Flow s a) -> [Value] -> Flow s [a]
forall x s y. (x -> Flow s y) -> [x] -> Flow s [y]
Flows.mapList Value -> Flow s a
decodeElem [Value]
v280)
Value
_ -> (String -> Flow s [a]
forall s x. String -> Flow s x
Flows.fail String
"expected an array")
decodeObject :: (Json.Value -> Compute.Flow s (Map String Json.Value))
decodeObject :: forall s. Value -> Flow s (Map String Value)
decodeObject Value
x = case Value
x of
Json.ValueObject Map String Value
v281 -> (Map String Value -> Flow s (Map String Value)
forall x s. x -> Flow s x
Flows.pure Map String Value
v281)
Value
_ -> (String -> Flow s (Map String Value)
forall s x. String -> Flow s x
Flows.fail String
"expected an object")
decodeField :: ((Json.Value -> Compute.Flow s a) -> String -> Map String Json.Value -> Compute.Flow s a)
decodeField :: forall s a.
(Value -> Flow s a) -> String -> Map String Value -> Flow s a
decodeField Value -> Flow s a
decodeValue String
name Map String Value
m = (Flow s (Maybe a) -> (Maybe a -> Flow s a) -> Flow s a
forall s x y. Flow s x -> (x -> Flow s y) -> Flow s y
Flows.bind ((Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a)
forall s a.
(Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a)
decodeOptionalField Value -> Flow s a
decodeValue String
name Map String Value
m) (\Maybe a
x -> case Maybe a
x of
Maybe a
Nothing -> (String -> Flow s a
forall s x. String -> Flow s x
Flows.fail ([String] -> String
Strings.cat [
String
"missing field: ",
String
name]))
Just a
v282 -> (a -> Flow s a
forall x s. x -> Flow s x
Flows.pure a
v282)))
decodeOptionalField :: ((Json.Value -> Compute.Flow s a) -> String -> Map String Json.Value -> Compute.Flow s (Maybe a))
decodeOptionalField :: forall s a.
(Value -> Flow s a)
-> String -> Map String Value -> Flow s (Maybe a)
decodeOptionalField Value -> Flow s a
decodeValue String
name Map String Value
m = ((\Maybe Value
x -> case Maybe Value
x of
Maybe Value
Nothing -> (Maybe a -> Flow s (Maybe a)
forall x s. x -> Flow s x
Flows.pure Maybe a
forall a. Maybe a
Nothing)
Just Value
v283 -> ((a -> Maybe a) -> Flow s a -> Flow s (Maybe a)
forall x y s. (x -> y) -> Flow s x -> Flow s y
Flows.map (\a
x -> a -> Maybe a
forall a. a -> Maybe a
Just a
x) (Value -> Flow s a
decodeValue Value
v283))) (String -> Map String Value -> Maybe Value
forall k v. Ord k => k -> Map k v -> Maybe v
Maps.lookup String
name Map String Value
m))