module Hasql.Decoders.Composite where import Hasql.Prelude import qualified PostgreSQL.Binary.Decoding as A newtype Composite a = Composite (ReaderT Bool A.Composite a) deriving ((forall a b. (a -> b) -> Composite a -> Composite b) -> (forall a b. a -> Composite b -> Composite a) -> Functor Composite 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 $cfmap :: forall a b. (a -> b) -> Composite a -> Composite b fmap :: forall a b. (a -> b) -> Composite a -> Composite b $c<$ :: forall a b. a -> Composite b -> Composite a <$ :: forall a b. a -> Composite b -> Composite a Functor, Functor Composite Functor Composite => (forall a. a -> Composite a) -> (forall a b. Composite (a -> b) -> Composite a -> Composite b) -> (forall a b c. (a -> b -> c) -> Composite a -> Composite b -> Composite c) -> (forall a b. Composite a -> Composite b -> Composite b) -> (forall a b. Composite a -> Composite b -> Composite a) -> Applicative 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 $cpure :: forall a. a -> Composite a pure :: forall a. a -> Composite a $c<*> :: forall a b. Composite (a -> b) -> Composite a -> Composite b <*> :: forall a b. Composite (a -> b) -> Composite a -> Composite b $cliftA2 :: forall a b c. (a -> b -> c) -> Composite a -> Composite b -> Composite c liftA2 :: forall a b c. (a -> b -> c) -> Composite a -> Composite b -> Composite c $c*> :: forall a b. Composite a -> Composite b -> Composite b *> :: forall a b. Composite a -> Composite b -> Composite b $c<* :: forall a b. Composite a -> Composite b -> Composite a <* :: forall a b. Composite a -> Composite b -> Composite a Applicative, Applicative Composite Applicative Composite => (forall a b. Composite a -> (a -> Composite b) -> Composite b) -> (forall a b. Composite a -> Composite b -> Composite b) -> (forall a. a -> Composite a) -> Monad 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 $c>>= :: forall a b. Composite a -> (a -> Composite b) -> Composite b >>= :: forall a b. Composite a -> (a -> Composite b) -> Composite b $c>> :: forall a b. Composite a -> Composite b -> Composite b >> :: forall a b. Composite a -> Composite b -> Composite b $creturn :: forall a. a -> Composite a return :: forall a. a -> Composite a Monad, Monad Composite Monad Composite => (forall a. String -> Composite a) -> MonadFail Composite forall a. String -> Composite a forall (m :: * -> *). Monad m => (forall a. String -> m a) -> MonadFail m $cfail :: forall a. String -> Composite a fail :: forall a. String -> Composite a MonadFail) {-# INLINE run #-} run :: Composite a -> Bool -> A.Value a run :: forall a. Composite a -> Bool -> Value a run (Composite ReaderT Bool Composite a imp) Bool env = Composite a -> Value a forall a. Composite a -> Value a A.composite (ReaderT Bool Composite a -> Bool -> Composite a forall r (m :: * -> *) a. ReaderT r m a -> r -> m a runReaderT ReaderT Bool Composite a imp Bool env) {-# INLINE value #-} value :: (Bool -> A.Value a) -> Composite (Maybe a) value :: forall a. (Bool -> Value a) -> Composite (Maybe a) value Bool -> Value a decoder' = ReaderT Bool Composite (Maybe a) -> Composite (Maybe a) forall a. ReaderT Bool Composite a -> Composite a Composite (ReaderT Bool Composite (Maybe a) -> Composite (Maybe a)) -> ReaderT Bool Composite (Maybe a) -> Composite (Maybe a) forall a b. (a -> b) -> a -> b $ (Bool -> Composite (Maybe a)) -> ReaderT Bool Composite (Maybe a) forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a ReaderT ((Bool -> Composite (Maybe a)) -> ReaderT Bool Composite (Maybe a)) -> (Bool -> Composite (Maybe a)) -> ReaderT Bool Composite (Maybe a) forall a b. (a -> b) -> a -> b $ Value a -> Composite (Maybe a) forall a. Value a -> Composite (Maybe a) A.nullableValueComposite (Value a -> Composite (Maybe a)) -> (Bool -> Value a) -> Bool -> Composite (Maybe a) forall b c a. (b -> c) -> (a -> b) -> a -> c forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . Bool -> Value a decoder' {-# INLINE nonNullValue #-} nonNullValue :: (Bool -> A.Value a) -> Composite a nonNullValue :: forall a. (Bool -> Value a) -> Composite a nonNullValue Bool -> Value a decoder' = ReaderT Bool Composite a -> Composite a forall a. ReaderT Bool Composite a -> Composite a Composite (ReaderT Bool Composite a -> Composite a) -> ReaderT Bool Composite a -> Composite a forall a b. (a -> b) -> a -> b $ (Bool -> Composite a) -> ReaderT Bool Composite a forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a ReaderT ((Bool -> Composite a) -> ReaderT Bool Composite a) -> (Bool -> Composite a) -> ReaderT Bool Composite a forall a b. (a -> b) -> a -> b $ Value a -> Composite a forall a. Value a -> Composite a A.valueComposite (Value a -> Composite a) -> (Bool -> Value a) -> Bool -> Composite a forall b c a. (b -> c) -> (a -> b) -> a -> c forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . Bool -> Value a decoder'