module Hasql.Decoders.Value where import Hasql.Prelude import PostgreSQL.Binary.Decoding qualified as A newtype Value a = Value (Bool -> A.Value a) deriving ((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 $cfmap :: forall a b. (a -> b) -> Value a -> Value b fmap :: forall a b. (a -> b) -> Value a -> Value b $c<$ :: forall a b. a -> Value b -> Value a <$ :: forall a b. a -> Value b -> Value a Functor) {-# INLINE run #-} run :: Value a -> Bool -> A.Value a run :: forall a. 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 :: forall a. (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 :: forall a. (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