module Hasql.Private.Decoders.Value where import Hasql.Private.Prelude import qualified PostgreSQL.Binary.Decoding as A newtype Value a = Value (Bool -> A.Value a) deriving (a -> Value b -> Value a (a -> b) -> Value a -> Value b (forall a b. (a -> b) -> Value a -> Value b) -> (forall a b. a -> Value b -> Value a) -> Functor Value 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 <$ :: a -> Value b -> Value a $c<$ :: forall a b. a -> Value b -> Value a fmap :: (a -> b) -> Value a -> Value b $cfmap :: forall a b. (a -> b) -> Value a -> Value b Functor) {-# INLINE run #-} run :: Value a -> Bool -> A.Value a run :: Value a -> Bool -> Value a run (Value Bool -> Value a imp) Bool integerDatetimes = Bool -> Value a imp Bool integerDatetimes {-# INLINE decoder #-} decoder :: (Bool -> A.Value a) -> Value a decoder :: (Bool -> Value a) -> Value a decoder = {-# SCC "decoder" #-} (Bool -> Value a) -> Value a forall a. (Bool -> Value a) -> Value a Value {-# INLINE decoderFn #-} decoderFn :: (Bool -> ByteString -> Either Text a) -> Value a decoderFn :: (Bool -> ByteString -> Either Text a) -> Value a decoderFn Bool -> ByteString -> Either Text a fn = (Bool -> Value a) -> Value a forall a. (Bool -> Value a) -> Value a Value ((Bool -> Value a) -> Value a) -> (Bool -> Value a) -> Value a forall a b. (a -> b) -> a -> b $ \Bool integerDatetimes -> (ByteString -> Either Text a) -> Value a forall a. (ByteString -> Either Text a) -> Value a A.fn ((ByteString -> Either Text a) -> Value a) -> (ByteString -> Either Text a) -> Value a forall a b. (a -> b) -> a -> b $ Bool -> ByteString -> Either Text a fn Bool integerDatetimes