module Hasql.Private.Decoders where
import qualified Data.Aeson as Aeson
import qualified Data.Vector as Vector
import qualified Data.Vector.Generic as GenericVector
import qualified Hasql.Private.Decoders.Array as Array
import qualified Hasql.Private.Decoders.Composite as Composite
import qualified Hasql.Private.Decoders.Result as Result
import qualified Hasql.Private.Decoders.Results as Results
import qualified Hasql.Private.Decoders.Row as Row
import qualified Hasql.Private.Decoders.Value as Value
import qualified Hasql.Private.Errors as Errors
import Hasql.Private.Prelude hiding (bool, maybe)
import qualified Hasql.Private.Prelude as Prelude
import qualified Network.IP.Addr as NetworkIp
import qualified PostgreSQL.Binary.Decoding as A
newtype Result a = Result (Results.Results a) deriving (forall a b. a -> Result b -> Result a
forall a b. (a -> b) -> Result a -> Result b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Result b -> Result a
$c<$ :: forall a b. a -> Result b -> Result a
fmap :: forall a b. (a -> b) -> Result a -> Result b
$cfmap :: forall a b. (a -> b) -> Result a -> Result b
Functor)
{-# INLINEABLE noResult #-}
noResult :: Result ()
noResult :: Result ()
noResult = forall a. Results a -> Result a
Result (forall a. Result a -> Results a
Results.single Result ()
Result.noResult)
{-# INLINEABLE rowsAffected #-}
rowsAffected :: Result Int64
rowsAffected :: Result Int64
rowsAffected = forall a. Results a -> Result a
Result (forall a. Result a -> Results a
Results.single Result Int64
Result.rowsAffected)
{-# INLINEABLE singleRow #-}
singleRow :: Row a -> Result a
singleRow :: forall a. Row a -> Result a
singleRow (Row Row a
row) = forall a. Results a -> Result a
Result (forall a. Result a -> Results a
Results.single (forall a. Row a -> Result a
Result.single Row a
row))
refineResult :: (a -> Either Text b) -> Result a -> Result b
refineResult :: forall a b. (a -> Either Text b) -> Result a -> Result b
refineResult a -> Either Text b
refiner (Result Results a
results) = forall a. Results a -> Result a
Result (forall a b. (a -> Either Text b) -> Results a -> Results b
Results.refine a -> Either Text b
refiner Results a
results)
{-# INLINEABLE foldlRows #-}
foldlRows :: (a -> b -> a) -> a -> Row b -> Result a
foldlRows :: forall a b. (a -> b -> a) -> a -> Row b -> Result a
foldlRows a -> b -> a
step a
init (Row Row b
row) = forall a. Results a -> Result a
Result (forall a. Result a -> Results a
Results.single (forall a b. (a -> b -> a) -> a -> Row b -> Result a
Result.foldl a -> b -> a
step a
init Row b
row))
{-# INLINEABLE foldrRows #-}
foldrRows :: (b -> a -> a) -> a -> Row b -> Result a
foldrRows :: forall b a. (b -> a -> a) -> a -> Row b -> Result a
foldrRows b -> a -> a
step a
init (Row Row b
row) = forall a. Results a -> Result a
Result (forall a. Result a -> Results a
Results.single (forall b a. (b -> a -> a) -> a -> Row b -> Result a
Result.foldr b -> a -> a
step a
init Row b
row))
{-# INLINEABLE rowMaybe #-}
rowMaybe :: Row a -> Result (Maybe a)
rowMaybe :: forall a. Row a -> Result (Maybe a)
rowMaybe (Row Row a
row) = forall a. Results a -> Result a
Result (forall a. Result a -> Results a
Results.single (forall a. Row a -> Result (Maybe a)
Result.maybe Row a
row))
{-# INLINEABLE rowVector #-}
rowVector :: Row a -> Result (Vector a)
rowVector :: forall a. Row a -> Result (Vector a)
rowVector (Row Row a
row) = forall a. Results a -> Result a
Result (forall a. Result a -> Results a
Results.single (forall a. Row a -> Result (Vector a)
Result.vector Row a
row))
{-# INLINEABLE rowList #-}
rowList :: Row a -> Result [a]
rowList :: forall a. Row a -> Result [a]
rowList = forall b a. (b -> a -> a) -> a -> Row b -> Result a
foldrRows forall a. a -> [a] -> [a]
strictCons []
newtype Row a = Row (Row.Row a)
deriving (forall a b. a -> Row b -> Row a
forall a b. (a -> b) -> Row a -> Row b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Row b -> Row a
$c<$ :: forall a b. a -> Row b -> Row a
fmap :: forall a b. (a -> b) -> Row a -> Row b
$cfmap :: forall a b. (a -> b) -> Row a -> Row b
Functor, Functor Row
forall a. a -> Row a
forall a b. Row a -> Row b -> Row a
forall a b. Row a -> Row b -> Row b
forall a b. Row (a -> b) -> Row a -> Row b
forall a b c. (a -> b -> c) -> Row a -> Row b -> Row c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: forall a b. Row a -> Row b -> Row a
$c<* :: forall a b. Row a -> Row b -> Row a
*> :: forall a b. Row a -> Row b -> Row b
$c*> :: forall a b. Row a -> Row b -> Row b
liftA2 :: forall a b c. (a -> b -> c) -> Row a -> Row b -> Row c
$cliftA2 :: forall a b c. (a -> b -> c) -> Row a -> Row b -> Row c
<*> :: forall a b. Row (a -> b) -> Row a -> Row b
$c<*> :: forall a b. Row (a -> b) -> Row a -> Row b
pure :: forall a. a -> Row a
$cpure :: forall a. a -> Row a
Applicative, Applicative Row
forall a. a -> Row a
forall a b. Row a -> Row b -> Row b
forall a b. Row a -> (a -> Row b) -> Row b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: forall a. a -> Row a
$creturn :: forall a. a -> Row a
>> :: forall a b. Row a -> Row b -> Row b
$c>> :: forall a b. Row a -> Row b -> Row b
>>= :: forall a b. Row a -> (a -> Row b) -> Row b
$c>>= :: forall a b. Row a -> (a -> Row b) -> Row b
Monad, Monad Row
forall a. String -> Row a
forall (m :: * -> *).
Monad m -> (forall a. String -> m a) -> MonadFail m
fail :: forall a. String -> Row a
$cfail :: forall a. String -> Row a
MonadFail)
{-# INLINEABLE column #-}
column :: NullableOrNot Value a -> Row a
column :: forall a. NullableOrNot Value a -> Row a
column = \case
NonNullable (Value Value a
imp) -> forall a. Row a -> Row a
Row (forall a. Value a -> Row a
Row.nonNullValue Value a
imp)
Nullable (Value Value a
imp) -> forall a. Row a -> Row a
Row (forall a. Value a -> Row (Maybe a)
Row.value Value a
imp)
data NullableOrNot decoder a where
NonNullable :: decoder a -> NullableOrNot decoder a
Nullable :: decoder a -> NullableOrNot decoder (Maybe a)
nonNullable :: decoder a -> NullableOrNot decoder a
nonNullable :: forall (decoder :: * -> *) a. decoder a -> NullableOrNot decoder a
nonNullable = forall (decoder :: * -> *) a. decoder a -> NullableOrNot decoder a
NonNullable
nullable :: decoder a -> NullableOrNot decoder (Maybe a)
nullable :: forall (decoder :: * -> *) a.
decoder a -> NullableOrNot decoder (Maybe a)
nullable = forall (decoder :: * -> *) a.
decoder a -> NullableOrNot decoder (Maybe a)
Nullable
newtype Value a = Value (Value.Value a)
deriving (forall a b. a -> Value b -> Value a
forall a b. (a -> b) -> Value a -> Value b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Value b -> Value a
$c<$ :: forall a b. a -> Value b -> Value a
fmap :: forall a b. (a -> b) -> Value a -> Value b
$cfmap :: forall a b. (a -> b) -> Value a -> Value b
Functor)
type role Value representational
{-# INLINEABLE bool #-}
bool :: Value Bool
bool :: Value Bool
bool = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a b. a -> b -> a
const Value Bool
A.bool))
{-# INLINEABLE int2 #-}
int2 :: Value Int16
int2 :: Value Int16
int2 = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a b. a -> b -> a
const forall a. (Integral a, Bits a) => Value a
A.int))
{-# INLINEABLE int4 #-}
int4 :: Value Int32
int4 :: Value Int32
int4 = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a b. a -> b -> a
const forall a. (Integral a, Bits a) => Value a
A.int))
{-# INLINEABLE int8 #-}
int8 :: Value Int64
int8 :: Value Int64
int8 =
{-# SCC "int8" #-}
forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a b. a -> b -> a
const ({-# SCC "int8.int" #-} forall a. (Integral a, Bits a) => Value a
A.int)))
{-# INLINEABLE float4 #-}
float4 :: Value Float
float4 :: Value Float
float4 = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a b. a -> b -> a
const Value Float
A.float4))
{-# INLINEABLE float8 #-}
float8 :: Value Double
float8 :: Value Double
float8 = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a b. a -> b -> a
const Value Double
A.float8))
{-# INLINEABLE numeric #-}
numeric :: Value Scientific
numeric :: Value Scientific
numeric = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a b. a -> b -> a
const Value Scientific
A.numeric))
{-# INLINEABLE char #-}
char :: Value Char
char :: Value Char
char = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a b. a -> b -> a
const Value Char
A.char))
{-# INLINEABLE text #-}
text :: Value Text
text :: Value Text
text = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a b. a -> b -> a
const Value Text
A.text_strict))
{-# INLINEABLE bytea #-}
bytea :: Value ByteString
bytea :: Value ByteString
bytea = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a b. a -> b -> a
const Value ByteString
A.bytea_strict))
{-# INLINEABLE date #-}
date :: Value Day
date :: Value Day
date = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a b. a -> b -> a
const Value Day
A.date))
{-# INLINEABLE timestamp #-}
timestamp :: Value LocalTime
timestamp :: Value LocalTime
timestamp = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a. a -> a -> Bool -> a
Prelude.bool Value LocalTime
A.timestamp_float Value LocalTime
A.timestamp_int))
{-# INLINEABLE timestamptz #-}
timestamptz :: Value UTCTime
timestamptz :: Value UTCTime
timestamptz = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a. a -> a -> Bool -> a
Prelude.bool Value UTCTime
A.timestamptz_float Value UTCTime
A.timestamptz_int))
{-# INLINEABLE time #-}
time :: Value TimeOfDay
time :: Value TimeOfDay
time = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a. a -> a -> Bool -> a
Prelude.bool Value TimeOfDay
A.time_float Value TimeOfDay
A.time_int))
{-# INLINEABLE timetz #-}
timetz :: Value (TimeOfDay, TimeZone)
timetz :: Value (TimeOfDay, TimeZone)
timetz = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a. a -> a -> Bool -> a
Prelude.bool Value (TimeOfDay, TimeZone)
A.timetz_float Value (TimeOfDay, TimeZone)
A.timetz_int))
{-# INLINEABLE interval #-}
interval :: Value DiffTime
interval :: Value DiffTime
interval = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a. a -> a -> Bool -> a
Prelude.bool Value DiffTime
A.interval_float Value DiffTime
A.interval_int))
{-# INLINEABLE uuid #-}
uuid :: Value UUID
uuid :: Value UUID
uuid = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a b. a -> b -> a
const Value UUID
A.uuid))
{-# INLINEABLE inet #-}
inet :: Value (NetworkIp.NetAddr NetworkIp.IP)
inet :: Value (NetAddr IP)
inet = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a b. a -> b -> a
const Value (NetAddr IP)
A.inet))
{-# INLINEABLE json #-}
json :: Value Aeson.Value
json :: Value Value
json = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a b. a -> b -> a
const Value Value
A.json_ast))
{-# INLINEABLE jsonBytes #-}
jsonBytes :: (ByteString -> Either Text a) -> Value a
jsonBytes :: forall a. (ByteString -> Either Text a) -> Value a
jsonBytes ByteString -> Either Text a
fn = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a b. a -> b -> a
const (forall a. (ByteString -> Either Text a) -> Value a
A.json_bytes ByteString -> Either Text a
fn)))
{-# INLINEABLE jsonb #-}
jsonb :: Value Aeson.Value
jsonb :: Value Value
jsonb = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a b. a -> b -> a
const Value Value
A.jsonb_ast))
{-# INLINEABLE jsonbBytes #-}
jsonbBytes :: (ByteString -> Either Text a) -> Value a
jsonbBytes :: forall a. (ByteString -> Either Text a) -> Value a
jsonbBytes ByteString -> Either Text a
fn = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a b. a -> b -> a
const (forall a. (ByteString -> Either Text a) -> Value a
A.jsonb_bytes ByteString -> Either Text a
fn)))
{-# INLINEABLE custom #-}
custom :: (Bool -> ByteString -> Either Text a) -> Value a
custom :: forall a. (Bool -> ByteString -> Either Text a) -> Value a
custom Bool -> ByteString -> Either Text a
fn = forall a. Value a -> Value a
Value (forall a. (Bool -> ByteString -> Either Text a) -> Value a
Value.decoderFn Bool -> ByteString -> Either Text a
fn)
{-# INLINEABLE refine #-}
refine :: (a -> Either Text b) -> Value a -> Value b
refine :: forall a b. (a -> Either Text b) -> Value a -> Value b
refine a -> Either Text b
fn (Value Value a
v) = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.Value (\Bool
b -> forall a b. (a -> Either Text b) -> Value a -> Value b
A.refine a -> Either Text b
fn (forall a. Value a -> Bool -> Value a
Value.run Value a
v Bool
b)))
{-# INLINEABLE hstore #-}
hstore :: (forall m. Monad m => Int -> m (Text, Maybe Text) -> m a) -> Value a
hstore :: forall a.
(forall (m :: * -> *).
Monad m =>
Int -> m (Text, Maybe Text) -> m a)
-> Value a
hstore forall (m :: * -> *). Monad m => Int -> m (Text, Maybe Text) -> m a
replicateM = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a b. a -> b -> a
const (forall k v r.
(forall (m :: * -> *). Monad m => Int -> m (k, Maybe v) -> m r)
-> Value k -> Value v -> Value r
A.hstore forall (m :: * -> *). Monad m => Int -> m (Text, Maybe Text) -> m a
replicateM Value Text
A.text_strict Value Text
A.text_strict)))
enum :: (Text -> Maybe a) -> Value a
enum :: forall a. (Text -> Maybe a) -> Value a
enum Text -> Maybe a
mapping = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a b. a -> b -> a
const (forall a. (Text -> Maybe a) -> Value a
A.enum Text -> Maybe a
mapping)))
{-# INLINEABLE array #-}
array :: Array a -> Value a
array :: forall a. Array a -> Value a
array (Array Array a
imp) = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a. Array a -> Bool -> Value a
Array.run Array a
imp))
{-# INLINE listArray #-}
listArray :: NullableOrNot Value element -> Value [element]
listArray :: forall element. NullableOrNot Value element -> Value [element]
listArray = forall a. Array a -> Value a
array forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a b.
(forall (m :: * -> *). Monad m => Int -> m a -> m b)
-> Array a -> Array b
dimension forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. NullableOrNot Value a -> Array a
element
{-# INLINE vectorArray #-}
vectorArray :: GenericVector.Vector vector element => NullableOrNot Value element -> Value (vector element)
vectorArray :: forall (vector :: * -> *) element.
Vector vector element =>
NullableOrNot Value element -> Value (vector element)
vectorArray = forall a. Array a -> Value a
array forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a b.
(forall (m :: * -> *). Monad m => Int -> m a -> m b)
-> Array a -> Array b
dimension forall (m :: * -> *) (v :: * -> *) a.
(Monad m, Vector v a) =>
Int -> m a -> m (v a)
GenericVector.replicateM forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. NullableOrNot Value a -> Array a
element
{-# INLINEABLE composite #-}
composite :: Composite a -> Value a
composite :: forall a. Composite a -> Value a
composite (Composite Composite a
imp) = forall a. Value a -> Value a
Value (forall a. (Bool -> Value a) -> Value a
Value.decoder (forall a. Composite a -> Bool -> Value a
Composite.run Composite a
imp))
newtype Array a = Array (Array.Array a)
deriving (forall a b. a -> Array b -> Array a
forall a b. (a -> b) -> Array a -> Array b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Array b -> Array a
$c<$ :: forall a b. a -> Array b -> Array a
fmap :: forall a b. (a -> b) -> Array a -> Array b
$cfmap :: forall a b. (a -> b) -> Array a -> Array b
Functor)
{-# INLINEABLE dimension #-}
dimension :: (forall m. Monad m => Int -> m a -> m b) -> Array a -> Array b
dimension :: forall a b.
(forall (m :: * -> *). Monad m => Int -> m a -> m b)
-> Array a -> Array b
dimension forall (m :: * -> *). Monad m => Int -> m a -> m b
replicateM (Array Array a
imp) = forall a. Array a -> Array a
Array (forall a b.
(forall (m :: * -> *). Monad m => Int -> m a -> m b)
-> Array a -> Array b
Array.dimension forall (m :: * -> *). Monad m => Int -> m a -> m b
replicateM Array a
imp)
{-# INLINEABLE element #-}
element :: NullableOrNot Value a -> Array a
element :: forall a. NullableOrNot Value a -> Array a
element = \case
NonNullable (Value Value a
imp) -> forall a. Array a -> Array a
Array (forall a. (Bool -> Value a) -> Array a
Array.nonNullValue (forall a. Value a -> Bool -> Value a
Value.run Value a
imp))
Nullable (Value Value a
imp) -> forall a. Array a -> Array a
Array (forall a. (Bool -> Value a) -> Array (Maybe a)
Array.value (forall a. Value a -> Bool -> Value a
Value.run Value a
imp))
newtype Composite a = Composite (Composite.Composite a)
deriving (forall a b. a -> Composite b -> Composite a
forall a b. (a -> b) -> Composite a -> Composite b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Composite b -> Composite a
$c<$ :: forall a b. a -> Composite b -> Composite a
fmap :: forall a b. (a -> b) -> Composite a -> Composite b
$cfmap :: forall a b. (a -> b) -> Composite a -> Composite b
Functor, Functor Composite
forall a. a -> Composite a
forall a b. Composite a -> Composite b -> Composite a
forall a b. Composite a -> Composite b -> Composite b
forall a b. Composite (a -> b) -> Composite a -> Composite b
forall a b c.
(a -> b -> c) -> Composite a -> Composite b -> Composite c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: forall a b. Composite a -> Composite b -> Composite a
$c<* :: forall a b. Composite a -> Composite b -> Composite a
*> :: forall a b. Composite a -> Composite b -> Composite b
$c*> :: forall a b. Composite a -> Composite b -> Composite b
liftA2 :: forall a b c.
(a -> b -> c) -> Composite a -> Composite b -> Composite c
$cliftA2 :: forall a b c.
(a -> b -> c) -> Composite a -> Composite b -> Composite c
<*> :: forall a b. Composite (a -> b) -> Composite a -> Composite b
$c<*> :: forall a b. Composite (a -> b) -> Composite a -> Composite b
pure :: forall a. a -> Composite a
$cpure :: forall a. a -> Composite a
Applicative, Applicative Composite
forall a. a -> Composite a
forall a b. Composite a -> Composite b -> Composite b
forall a b. Composite a -> (a -> Composite b) -> Composite b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: forall a. a -> Composite a
$creturn :: forall a. a -> Composite a
>> :: forall a b. Composite a -> Composite b -> Composite b
$c>> :: forall a b. Composite a -> Composite b -> Composite b
>>= :: forall a b. Composite a -> (a -> Composite b) -> Composite b
$c>>= :: forall a b. Composite a -> (a -> Composite b) -> Composite b
Monad, Monad Composite
forall a. String -> Composite a
forall (m :: * -> *).
Monad m -> (forall a. String -> m a) -> MonadFail m
fail :: forall a. String -> Composite a
$cfail :: forall a. String -> Composite a
MonadFail)
field :: NullableOrNot Value a -> Composite a
field :: forall a. NullableOrNot Value a -> Composite a
field = \case
NonNullable (Value Value a
imp) -> forall a. Composite a -> Composite a
Composite (forall a. (Bool -> Value a) -> Composite a
Composite.nonNullValue (forall a. Value a -> Bool -> Value a
Value.run Value a
imp))
Nullable (Value Value a
imp) -> forall a. Composite a -> Composite a
Composite (forall a. (Bool -> Value a) -> Composite (Maybe a)
Composite.value (forall a. Value a -> Bool -> Value a
Value.run Value a
imp))