hasql/library/Hasql/Private/Decoders/Array.hs

31 lines
802 B
Haskell
Raw Normal View History

module Hasql.Private.Decoders.Array where
2015-11-08 21:09:42 +03:00
import Hasql.Private.Prelude
2017-03-20 23:13:21 +03:00
import qualified PostgreSQL.Binary.Decoding as A
2015-11-08 21:09:42 +03:00
newtype Array a =
2017-03-20 23:13:21 +03:00
Array (ReaderT Bool A.Array a)
2015-11-08 21:09:42 +03:00
deriving (Functor)
{-# INLINE run #-}
2017-03-20 23:13:21 +03:00
run :: Array a -> Bool -> A.Value a
2015-11-08 21:09:42 +03:00
run (Array imp) env =
2017-03-20 23:13:21 +03:00
A.array (runReaderT imp env)
2015-11-08 21:09:42 +03:00
{-# INLINE dimension #-}
dimension :: (forall m. Monad m => Int -> m a -> m b) -> Array a -> Array b
dimension replicateM (Array imp) =
2017-03-20 23:13:21 +03:00
Array $ ReaderT $ \env -> A.dimensionArray replicateM (runReaderT imp env)
2015-11-08 21:09:42 +03:00
{-# INLINE value #-}
2017-03-20 23:13:21 +03:00
value :: (Bool -> A.Value a) -> Array (Maybe a)
2015-11-08 21:09:42 +03:00
value decoder' =
2017-03-20 23:13:21 +03:00
Array $ ReaderT $ A.nullableValueArray . decoder'
2015-11-08 21:09:42 +03:00
{-# INLINE nonNullValue #-}
2017-03-20 23:13:21 +03:00
nonNullValue :: (Bool -> A.Value a) -> Array a
2015-11-08 21:09:42 +03:00
nonNullValue decoder' =
2017-03-20 23:13:21 +03:00
Array $ ReaderT $ A.valueArray . decoder'
2015-11-08 21:09:42 +03:00