haxl-0.5.1.0: A Haskell library for efficient, concurrent, and concise data access.

Safe HaskellNone
LanguageHaskell2010

Haxl.Prelude

Contents

Description

Support for using Haxl as a DSL. This module provides most of the standard Prelude, plus a selection of stuff that makes Haxl client code cleaner and more concise.

We intend Haxl client code to:

  • Import Haxl.Prelude
  • Use RebindableSyntax. This implies NoImplicitPrelude, and allows if-then-else to be used with a monadic condition.
  • Use OverloadedStrings (we use Text a lot)

Synopsis

The Standard Haskell Prelude

Everything from Prelude except mapM, mapM_, sequence, and sequence

module Prelude

Haxl and Fetching data

data GenHaxl u a Source #

The Haxl monad, which does several things:

  • It is a reader monad for Env and IORef RequestStore, The latter is the current batch of unsubmitted data fetch requests.
  • It is a concurrency, or resumption, monad. A computation may run partially and return Blocked, in which case the framework should perform the outstanding requests in the RequestStore, and then resume the computation.
  • The Applicative combinator <*> explores both branches in the event that the left branch is Blocked, so that we can collect multiple requests and submit them as a batch.
  • It contains IO, so that we can perform real data fetching.

Instances

Monad (GenHaxl u) Source # 

Methods

(>>=) :: GenHaxl u a -> (a -> GenHaxl u b) -> GenHaxl u b #

(>>) :: GenHaxl u a -> GenHaxl u b -> GenHaxl u b #

return :: a -> GenHaxl u a #

fail :: String -> GenHaxl u a #

Functor (GenHaxl u) Source # 

Methods

fmap :: (a -> b) -> GenHaxl u a -> GenHaxl u b #

(<$) :: a -> GenHaxl u b -> GenHaxl u a #

Applicative (GenHaxl u) Source # 

Methods

pure :: a -> GenHaxl u a #

(<*>) :: GenHaxl u (a -> b) -> GenHaxl u a -> GenHaxl u b #

(*>) :: GenHaxl u a -> GenHaxl u b -> GenHaxl u b #

(<*) :: GenHaxl u a -> GenHaxl u b -> GenHaxl u a #

MonadThrow (GenHaxl u) Source #

Since: 0.3.1.0

Methods

throwM :: Exception e => e -> GenHaxl u a

MonadCatch (GenHaxl u) Source #

Since: 0.3.1.0

Methods

catch :: Exception e => GenHaxl u a -> (e -> GenHaxl u a) -> GenHaxl u a

IsString a => IsString (GenHaxl u a) Source # 

Methods

fromString :: String -> GenHaxl u a #

(~) * u1 u2 => IfThenElse (GenHaxl u1 Bool) (GenHaxl u2 a) Source # 

Methods

ifThenElse :: GenHaxl u1 Bool -> GenHaxl u2 a -> GenHaxl u2 a -> GenHaxl u2 a Source #

dataFetch :: (DataSource u r, Request r a) => r a -> GenHaxl u a Source #

Performs actual fetching of data for a Request from a DataSource.

class (DataSourceName req, StateKey req, ShowP req) => DataSource u req Source #

The class of data sources, parameterised over the request type for that data source. Every data source must implement this class.

A data source keeps track of its state by creating an instance of StateKey to map the request type to its state. In this case, the type of the state should probably be a reference type of some kind, such as IORef.

For a complete example data source, see Examples.

Minimal complete definition

fetch

memo :: (Typeable a, Typeable k, Hashable k, Eq k) => k -> GenHaxl u a -> GenHaxl u a Source #

Memoize a computation using an arbitrary key. The result will be calculated once; the second and subsequent time it will be returned immediately. It is the caller's responsibility to ensure that for every two calls memo key haxl, if they have the same key then they compute the same result.

memoize :: GenHaxl u a -> GenHaxl u a Source #

Transform a Haxl computation into a memoized version of itself.

Given a Haxl computation, memoize creates a version which stores its result in a MemoVar (which memoize creates), and returns the stored result on subsequent invocations. This permits the creation of local memos, whose lifetimes are scoped to the current function, rather than the entire request.

memoize1 :: (Eq a, Hashable a) => (a -> GenHaxl u b) -> GenHaxl u (a -> GenHaxl u b) Source #

Transform a 1-argument function returning a Haxl computation into a memoized version of itself.

Given a function f of type a -> GenHaxl u b, memoize1 creates a version which memoizes the results of f in a table keyed by its argument, and returns stored results on subsequent invocations with the same argument.

e.g.:

allFriends :: [Int] -> GenHaxl u [Int] allFriends ids = do memoizedFriendsOf <- memoize1 friendsOf concat $ mapM memoizeFriendsOf ids

The above implementation will not invoke the underlying friendsOf repeatedly for duplicate values in ids.

memoize2 :: (Eq a, Hashable a, Eq b, Hashable b) => (a -> b -> GenHaxl u c) -> GenHaxl u (a -> b -> GenHaxl u c) Source #

Transform a 2-argument function returning a Haxl computation, into a memoized version of itself.

The 2-ary version of memoize1, see its documentation for details.

Extra Monad and Applicative things

class Functor f => Applicative f where #

A functor with application, providing operations to

  • embed pure expressions (pure), and
  • sequence computations and combine their results (<*>).

A minimal complete definition must include implementations of these functions satisfying the following laws:

identity
pure id <*> v = v
composition
pure (.) <*> u <*> v <*> w = u <*> (v <*> w)
homomorphism
pure f <*> pure x = pure (f x)
interchange
u <*> pure y = pure ($ y) <*> u

The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:

As a consequence of these laws, the Functor instance for f will satisfy

If f is also a Monad, it should satisfy

(which implies that pure and <*> satisfy the applicative functor laws).

Minimal complete definition

pure, (<*>)

Methods

pure :: a -> f a #

Lift a value.

(<*>) :: f (a -> b) -> f a -> f b infixl 4 #

Sequential application.

(*>) :: f a -> f b -> f b infixl 4 #

Sequence actions, discarding the value of the first argument.

(<*) :: f a -> f b -> f a infixl 4 #

Sequence actions, discarding the value of the second argument.

Instances

Applicative [] 

Methods

pure :: a -> [a] #

(<*>) :: [a -> b] -> [a] -> [b] #

(*>) :: [a] -> [b] -> [b] #

(<*) :: [a] -> [b] -> [a] #

Applicative Maybe 

Methods

pure :: a -> Maybe a #

(<*>) :: Maybe (a -> b) -> Maybe a -> Maybe b #

(*>) :: Maybe a -> Maybe b -> Maybe b #

(<*) :: Maybe a -> Maybe b -> Maybe a #

Applicative IO 

Methods

pure :: a -> IO a #

(<*>) :: IO (a -> b) -> IO a -> IO b #

(*>) :: IO a -> IO b -> IO b #

(<*) :: IO a -> IO b -> IO a #

Applicative U1 

Methods

pure :: a -> U1 a #

(<*>) :: U1 (a -> b) -> U1 a -> U1 b #

(*>) :: U1 a -> U1 b -> U1 b #

(<*) :: U1 a -> U1 b -> U1 a #

Applicative Par1 

Methods

pure :: a -> Par1 a #

(<*>) :: Par1 (a -> b) -> Par1 a -> Par1 b #

(*>) :: Par1 a -> Par1 b -> Par1 b #

(<*) :: Par1 a -> Par1 b -> Par1 a #

Applicative Q 

Methods

pure :: a -> Q a #

(<*>) :: Q (a -> b) -> Q a -> Q b #

(*>) :: Q a -> Q b -> Q b #

(<*) :: Q a -> Q b -> Q a #

Applicative Id 

Methods

pure :: a -> Id a #

(<*>) :: Id (a -> b) -> Id a -> Id b #

(*>) :: Id a -> Id b -> Id b #

(<*) :: Id a -> Id b -> Id a #

Applicative Identity 

Methods

pure :: a -> Identity a #

(<*>) :: Identity (a -> b) -> Identity a -> Identity b #

(*>) :: Identity a -> Identity b -> Identity b #

(<*) :: Identity a -> Identity b -> Identity a #

Applicative Min 

Methods

pure :: a -> Min a #

(<*>) :: Min (a -> b) -> Min a -> Min b #

(*>) :: Min a -> Min b -> Min b #

(<*) :: Min a -> Min b -> Min a #

Applicative Max 

Methods

pure :: a -> Max a #

(<*>) :: Max (a -> b) -> Max a -> Max b #

(*>) :: Max a -> Max b -> Max b #

(<*) :: Max a -> Max b -> Max a #

Applicative First 

Methods

pure :: a -> First a #

(<*>) :: First (a -> b) -> First a -> First b #

(*>) :: First a -> First b -> First b #

(<*) :: First a -> First b -> First a #

Applicative Last 

Methods

pure :: a -> Last a #

(<*>) :: Last (a -> b) -> Last a -> Last b #

(*>) :: Last a -> Last b -> Last b #

(<*) :: Last a -> Last b -> Last a #

Applicative Option 

Methods

pure :: a -> Option a #

(<*>) :: Option (a -> b) -> Option a -> Option b #

(*>) :: Option a -> Option b -> Option b #

(<*) :: Option a -> Option b -> Option a #

Applicative NonEmpty 

Methods

pure :: a -> NonEmpty a #

(<*>) :: NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b #

(*>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

(<*) :: NonEmpty a -> NonEmpty b -> NonEmpty a #

Applicative Complex 

Methods

pure :: a -> Complex a #

(<*>) :: Complex (a -> b) -> Complex a -> Complex b #

(*>) :: Complex a -> Complex b -> Complex b #

(<*) :: Complex a -> Complex b -> Complex a #

Applicative ZipList 

Methods

pure :: a -> ZipList a #

(<*>) :: ZipList (a -> b) -> ZipList a -> ZipList b #

(*>) :: ZipList a -> ZipList b -> ZipList b #

(<*) :: ZipList a -> ZipList b -> ZipList a #

Applicative STM 

Methods

pure :: a -> STM a #

(<*>) :: STM (a -> b) -> STM a -> STM b #

(*>) :: STM a -> STM b -> STM b #

(<*) :: STM a -> STM b -> STM a #

Applicative Dual 

Methods

pure :: a -> Dual a #

(<*>) :: Dual (a -> b) -> Dual a -> Dual b #

(*>) :: Dual a -> Dual b -> Dual b #

(<*) :: Dual a -> Dual b -> Dual a #

Applicative Sum 

Methods

pure :: a -> Sum a #

(<*>) :: Sum (a -> b) -> Sum a -> Sum b #

(*>) :: Sum a -> Sum b -> Sum b #

(<*) :: Sum a -> Sum b -> Sum a #

Applicative Product 

Methods

pure :: a -> Product a #

(<*>) :: Product (a -> b) -> Product a -> Product b #

(*>) :: Product a -> Product b -> Product b #

(<*) :: Product a -> Product b -> Product a #

Applicative First 

Methods

pure :: a -> First a #

(<*>) :: First (a -> b) -> First a -> First b #

(*>) :: First a -> First b -> First b #

(<*) :: First a -> First b -> First a #

Applicative Last 

Methods

pure :: a -> Last a #

(<*>) :: Last (a -> b) -> Last a -> Last b #

(*>) :: Last a -> Last b -> Last b #

(<*) :: Last a -> Last b -> Last a #

Applicative PutM 

Methods

pure :: a -> PutM a #

(<*>) :: PutM (a -> b) -> PutM a -> PutM b #

(*>) :: PutM a -> PutM b -> PutM b #

(<*) :: PutM a -> PutM b -> PutM a #

Applicative Get 

Methods

pure :: a -> Get a #

(<*>) :: Get (a -> b) -> Get a -> Get b #

(*>) :: Get a -> Get b -> Get b #

(<*) :: Get a -> Get b -> Get a #

Applicative Seq 

Methods

pure :: a -> Seq a #

(<*>) :: Seq (a -> b) -> Seq a -> Seq b #

(*>) :: Seq a -> Seq b -> Seq b #

(<*) :: Seq a -> Seq b -> Seq a #

Applicative IResult 

Methods

pure :: a -> IResult a #

(<*>) :: IResult (a -> b) -> IResult a -> IResult b #

(*>) :: IResult a -> IResult b -> IResult b #

(<*) :: IResult a -> IResult b -> IResult a #

Applicative Result 

Methods

pure :: a -> Result a #

(<*>) :: Result (a -> b) -> Result a -> Result b #

(*>) :: Result a -> Result b -> Result b #

(<*) :: Result a -> Result b -> Result a #

Applicative DList 

Methods

pure :: a -> DList a #

(<*>) :: DList (a -> b) -> DList a -> DList b #

(*>) :: DList a -> DList b -> DList b #

(<*) :: DList a -> DList b -> DList a #

Applicative Vector 

Methods

pure :: a -> Vector a #

(<*>) :: Vector (a -> b) -> Vector a -> Vector b #

(*>) :: Vector a -> Vector b -> Vector b #

(<*) :: Vector a -> Vector b -> Vector a #

Applicative Parser 

Methods

pure :: a -> Parser a #

(<*>) :: Parser (a -> b) -> Parser a -> Parser b #

(*>) :: Parser a -> Parser b -> Parser b #

(<*) :: Parser a -> Parser b -> Parser a #

Applicative Array 

Methods

pure :: a -> Array a #

(<*>) :: Array (a -> b) -> Array a -> Array b #

(*>) :: Array a -> Array b -> Array b #

(<*) :: Array a -> Array b -> Array a #

Applicative ((->) a) 

Methods

pure :: a -> a -> a #

(<*>) :: (a -> a -> b) -> (a -> a) -> a -> b #

(*>) :: (a -> a) -> (a -> b) -> a -> b #

(<*) :: (a -> a) -> (a -> b) -> a -> a #

Applicative (Either e) 

Methods

pure :: a -> Either e a #

(<*>) :: Either e (a -> b) -> Either e a -> Either e b #

(*>) :: Either e a -> Either e b -> Either e b #

(<*) :: Either e a -> Either e b -> Either e a #

Applicative f => Applicative (Rec1 f) 

Methods

pure :: a -> Rec1 f a #

(<*>) :: Rec1 f (a -> b) -> Rec1 f a -> Rec1 f b #

(*>) :: Rec1 f a -> Rec1 f b -> Rec1 f b #

(<*) :: Rec1 f a -> Rec1 f b -> Rec1 f a #

Monoid a => Applicative ((,) a) 

Methods

pure :: a -> (a, a) #

(<*>) :: (a, a -> b) -> (a, a) -> (a, b) #

(*>) :: (a, a) -> (a, b) -> (a, b) #

(<*) :: (a, a) -> (a, b) -> (a, a) #

Applicative (ST s) 

Methods

pure :: a -> ST s a #

(<*>) :: ST s (a -> b) -> ST s a -> ST s b #

(*>) :: ST s a -> ST s b -> ST s b #

(<*) :: ST s a -> ST s b -> ST s a #

Applicative (StateL s) 

Methods

pure :: a -> StateL s a #

(<*>) :: StateL s (a -> b) -> StateL s a -> StateL s b #

(*>) :: StateL s a -> StateL s b -> StateL s b #

(<*) :: StateL s a -> StateL s b -> StateL s a #

Applicative (StateR s) 

Methods

pure :: a -> StateR s a #

(<*>) :: StateR s (a -> b) -> StateR s a -> StateR s b #

(*>) :: StateR s a -> StateR s b -> StateR s b #

(<*) :: StateR s a -> StateR s b -> StateR s a #

Monad m => Applicative (WrappedMonad m) 

Methods

pure :: a -> WrappedMonad m a #

(<*>) :: WrappedMonad m (a -> b) -> WrappedMonad m a -> WrappedMonad m b #

(*>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b #

(<*) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m a #

Arrow a => Applicative (ArrowMonad a) 

Methods

pure :: a -> ArrowMonad a a #

(<*>) :: ArrowMonad a (a -> b) -> ArrowMonad a a -> ArrowMonad a b #

(*>) :: ArrowMonad a a -> ArrowMonad a b -> ArrowMonad a b #

(<*) :: ArrowMonad a a -> ArrowMonad a b -> ArrowMonad a a #

Applicative (Proxy *) 

Methods

pure :: a -> Proxy * a #

(<*>) :: Proxy * (a -> b) -> Proxy * a -> Proxy * b #

(*>) :: Proxy * a -> Proxy * b -> Proxy * b #

(<*) :: Proxy * a -> Proxy * b -> Proxy * a #

Applicative (State s) 

Methods

pure :: a -> State s a #

(<*>) :: State s (a -> b) -> State s a -> State s b #

(*>) :: State s a -> State s b -> State s b #

(<*) :: State s a -> State s b -> State s a #

(Functor m, Monad m) => Applicative (MaybeT m) 

Methods

pure :: a -> MaybeT m a #

(<*>) :: MaybeT m (a -> b) -> MaybeT m a -> MaybeT m b #

(*>) :: MaybeT m a -> MaybeT m b -> MaybeT m b #

(<*) :: MaybeT m a -> MaybeT m b -> MaybeT m a #

Applicative m => Applicative (ListT m) 

Methods

pure :: a -> ListT m a #

(<*>) :: ListT m (a -> b) -> ListT m a -> ListT m b #

(*>) :: ListT m a -> ListT m b -> ListT m b #

(<*) :: ListT m a -> ListT m b -> ListT m a #

Applicative (Parser i) 

Methods

pure :: a -> Parser i a #

(<*>) :: Parser i (a -> b) -> Parser i a -> Parser i b #

(*>) :: Parser i a -> Parser i b -> Parser i b #

(<*) :: Parser i a -> Parser i b -> Parser i a #

Applicative (GenHaxl u) # 

Methods

pure :: a -> GenHaxl u a #

(<*>) :: GenHaxl u (a -> b) -> GenHaxl u a -> GenHaxl u b #

(*>) :: GenHaxl u a -> GenHaxl u b -> GenHaxl u b #

(<*) :: GenHaxl u a -> GenHaxl u b -> GenHaxl u a #

(Applicative f, Applicative g) => Applicative ((:*:) f g) 

Methods

pure :: a -> (f :*: g) a #

(<*>) :: (f :*: g) (a -> b) -> (f :*: g) a -> (f :*: g) b #

(*>) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) b #

(<*) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) a #

(Applicative f, Applicative g) => Applicative ((:.:) f g) 

Methods

pure :: a -> (f :.: g) a #

(<*>) :: (f :.: g) (a -> b) -> (f :.: g) a -> (f :.: g) b #

(*>) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) b #

(<*) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) a #

Arrow a => Applicative (WrappedArrow a b) 

Methods

pure :: a -> WrappedArrow a b a #

(<*>) :: WrappedArrow a b (a -> b) -> WrappedArrow a b a -> WrappedArrow a b b #

(*>) :: WrappedArrow a b a -> WrappedArrow a b b -> WrappedArrow a b b #

(<*) :: WrappedArrow a b a -> WrappedArrow a b b -> WrappedArrow a b a #

Monoid m => Applicative (Const * m) 

Methods

pure :: a -> Const * m a #

(<*>) :: Const * m (a -> b) -> Const * m a -> Const * m b #

(*>) :: Const * m a -> Const * m b -> Const * m b #

(<*) :: Const * m a -> Const * m b -> Const * m a #

Applicative f => Applicative (Alt * f) 

Methods

pure :: a -> Alt * f a #

(<*>) :: Alt * f (a -> b) -> Alt * f a -> Alt * f b #

(*>) :: Alt * f a -> Alt * f b -> Alt * f b #

(<*) :: Alt * f a -> Alt * f b -> Alt * f a #

(Monoid w, Applicative m) => Applicative (WriterT w m) 

Methods

pure :: a -> WriterT w m a #

(<*>) :: WriterT w m (a -> b) -> WriterT w m a -> WriterT w m b #

(*>) :: WriterT w m a -> WriterT w m b -> WriterT w m b #

(<*) :: WriterT w m a -> WriterT w m b -> WriterT w m a #

(Monoid w, Applicative m) => Applicative (WriterT w m) 

Methods

pure :: a -> WriterT w m a #

(<*>) :: WriterT w m (a -> b) -> WriterT w m a -> WriterT w m b #

(*>) :: WriterT w m a -> WriterT w m b -> WriterT w m b #

(<*) :: WriterT w m a -> WriterT w m b -> WriterT w m a #

(Functor m, Monad m) => Applicative (StateT s m) 

Methods

pure :: a -> StateT s m a #

(<*>) :: StateT s m (a -> b) -> StateT s m a -> StateT s m b #

(*>) :: StateT s m a -> StateT s m b -> StateT s m b #

(<*) :: StateT s m a -> StateT s m b -> StateT s m a #

(Functor m, Monad m) => Applicative (StateT s m) 

Methods

pure :: a -> StateT s m a #

(<*>) :: StateT s m (a -> b) -> StateT s m a -> StateT s m b #

(*>) :: StateT s m a -> StateT s m b -> StateT s m b #

(<*) :: StateT s m a -> StateT s m b -> StateT s m a #

Applicative m => Applicative (IdentityT * m) 

Methods

pure :: a -> IdentityT * m a #

(<*>) :: IdentityT * m (a -> b) -> IdentityT * m a -> IdentityT * m b #

(*>) :: IdentityT * m a -> IdentityT * m b -> IdentityT * m b #

(<*) :: IdentityT * m a -> IdentityT * m b -> IdentityT * m a #

(Functor m, Monad m) => Applicative (ExceptT e m) 

Methods

pure :: a -> ExceptT e m a #

(<*>) :: ExceptT e m (a -> b) -> ExceptT e m a -> ExceptT e m b #

(*>) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m b #

(<*) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m a #

(Functor m, Monad m) => Applicative (ErrorT e m) 

Methods

pure :: a -> ErrorT e m a #

(<*>) :: ErrorT e m (a -> b) -> ErrorT e m a -> ErrorT e m b #

(*>) :: ErrorT e m a -> ErrorT e m b -> ErrorT e m b #

(<*) :: ErrorT e m a -> ErrorT e m b -> ErrorT e m a #

Monoid a => Applicative (Constant * a) 

Methods

pure :: a -> Constant * a a #

(<*>) :: Constant * a (a -> b) -> Constant * a a -> Constant * a b #

(*>) :: Constant * a a -> Constant * a b -> Constant * a b #

(<*) :: Constant * a a -> Constant * a b -> Constant * a a #

Applicative (Tagged k s) 

Methods

pure :: a -> Tagged k s a #

(<*>) :: Tagged k s (a -> b) -> Tagged k s a -> Tagged k s b #

(*>) :: Tagged k s a -> Tagged k s b -> Tagged k s b #

(<*) :: Tagged k s a -> Tagged k s b -> Tagged k s a #

Applicative f => Applicative (M1 i c f) 

Methods

pure :: a -> M1 i c f a #

(<*>) :: M1 i c f (a -> b) -> M1 i c f a -> M1 i c f b #

(*>) :: M1 i c f a -> M1 i c f b -> M1 i c f b #

(<*) :: M1 i c f a -> M1 i c f b -> M1 i c f a #

(Applicative f, Applicative g) => Applicative (Product * f g) 

Methods

pure :: a -> Product * f g a #

(<*>) :: Product * f g (a -> b) -> Product * f g a -> Product * f g b #

(*>) :: Product * f g a -> Product * f g b -> Product * f g b #

(<*) :: Product * f g a -> Product * f g b -> Product * f g a #

Applicative m => Applicative (ReaderT * r m) 

Methods

pure :: a -> ReaderT * r m a #

(<*>) :: ReaderT * r m (a -> b) -> ReaderT * r m a -> ReaderT * r m b #

(*>) :: ReaderT * r m a -> ReaderT * r m b -> ReaderT * r m b #

(<*) :: ReaderT * r m a -> ReaderT * r m b -> ReaderT * r m a #

(Applicative f, Applicative g) => Applicative (Compose * * f g) 

Methods

pure :: a -> Compose * * f g a #

(<*>) :: Compose * * f g (a -> b) -> Compose * * f g a -> Compose * * f g b #

(*>) :: Compose * * f g a -> Compose * * f g b -> Compose * * f g b #

(<*) :: Compose * * f g a -> Compose * * f g b -> Compose * * f g a #

(Monoid w, Functor m, Monad m) => Applicative (RWST r w s m) 

Methods

pure :: a -> RWST r w s m a #

(<*>) :: RWST r w s m (a -> b) -> RWST r w s m a -> RWST r w s m b #

(*>) :: RWST r w s m a -> RWST r w s m b -> RWST r w s m b #

(<*) :: RWST r w s m a -> RWST r w s m b -> RWST r w s m a #

(Monoid w, Functor m, Monad m) => Applicative (RWST r w s m) 

Methods

pure :: a -> RWST r w s m a #

(<*>) :: RWST r w s m (a -> b) -> RWST r w s m a -> RWST r w s m b #

(*>) :: RWST r w s m a -> RWST r w s m b -> RWST r w s m b #

(<*) :: RWST r w s m a -> RWST r w s m b -> RWST r w s m a #

mapM :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) Source #

We don't want the monadic mapM, because that doesn't do batching. There doesn't seem to be a way to make mapM have the right behaviour when used with Haxl, so instead we define mapM to be traverse in Haxl code.

mapM_ :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f () Source #

See mapM.

sequence :: (Traversable t, Applicative f) => t (f a) -> f (t a) Source #

See mapM.

sequence_ :: (Traversable t, Applicative f) => t (f a) -> f () Source #

See mapM.

filterM :: Applicative f => (a -> f Bool) -> [a] -> f [a] Source #

See mapM.

foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b #

The foldM function is analogous to foldl, except that its result is encapsulated in a monad. Note that foldM works from left-to-right over the list arguments. This could be an issue where (>>) and the `folded function' are not commutative.

      foldM f a1 [x1, x2, ..., xm]

==

      do
        a2 <- f a1 x1
        a3 <- f a2 x2
        ...
        f am xm

If right-to-left evaluation is required, the input list should be reversed.

Note: foldM is the same as foldlM

forM :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b) Source #

forM_ :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f () Source #

foldl' :: Foldable t => forall b a. (b -> a -> b) -> b -> t a -> b #

Left-associative fold of a structure but with strict application of the operator.

This ensures that each step of the fold is forced to weak head normal form before being applied, avoiding the collection of thunks that would otherwise occur. This is often what you want to strictly reduce a finite list to a single, monolithic result (e.g. length).

For a general Foldable structure this should be semantically identical to,

foldl f z = foldl' f z . toList

sort :: Ord a => [a] -> [a] #

The sort function implements a stable sorting algorithm. It is a special case of sortBy, which allows the programmer to supply their own comparison function.

class Monoid a where #

The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:

  • mappend mempty x = x
  • mappend x mempty = x
  • mappend x (mappend y z) = mappend (mappend x y) z
  • mconcat = foldr mappend mempty

The method names refer to the monoid of lists under concatenation, but there are many other instances.

Some types can be viewed as a monoid in more than one way, e.g. both addition and multiplication on numbers. In such cases we often define newtypes and make those instances of Monoid, e.g. Sum and Product.

Minimal complete definition

mempty, mappend

Methods

mempty :: a #

Identity of mappend

mappend :: a -> a -> a #

An associative operation

mconcat :: [a] -> a #

Fold a list using the monoid. For most types, the default definition for mconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types.

Instances

Monoid Ordering 
Monoid () 

Methods

mempty :: () #

mappend :: () -> () -> () #

mconcat :: [()] -> () #

Monoid All 

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Monoid Any 

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Monoid ByteString 
Monoid IntSet 
Monoid Doc 

Methods

mempty :: Doc #

mappend :: Doc -> Doc -> Doc #

mconcat :: [Doc] -> Doc #

Monoid More 

Methods

mempty :: More #

mappend :: More -> More -> More #

mconcat :: [More] -> More #

Monoid Series 

Methods

mempty :: Series #

mappend :: Series -> Series -> Series #

mconcat :: [Series] -> Series #

Monoid Buffer 

Methods

mempty :: Buffer #

mappend :: Buffer -> Buffer -> Buffer #

mconcat :: [Buffer] -> Buffer #

Monoid Buffer 

Methods

mempty :: Buffer #

mappend :: Buffer -> Buffer -> Buffer #

mconcat :: [Buffer] -> Buffer #

Monoid [a] 

Methods

mempty :: [a] #

mappend :: [a] -> [a] -> [a] #

mconcat :: [[a]] -> [a] #

Monoid a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S." Since there is no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

Monoid a => Monoid (IO a) 

Methods

mempty :: IO a #

mappend :: IO a -> IO a -> IO a #

mconcat :: [IO a] -> IO a #

Ord a => Monoid (Max a) 

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

Ord a => Monoid (Min a) 

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

Monoid a => Monoid (Identity a) 

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

(Ord a, Bounded a) => Monoid (Min a) 

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

(Ord a, Bounded a) => Monoid (Max a) 

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

Monoid m => Monoid (WrappedMonoid m) 
Semigroup a => Monoid (Option a) 

Methods

mempty :: Option a #

mappend :: Option a -> Option a -> Option a #

mconcat :: [Option a] -> Option a #

Monoid a => Monoid (Dual a) 

Methods

mempty :: Dual a #

mappend :: Dual a -> Dual a -> Dual a #

mconcat :: [Dual a] -> Dual a #

Monoid (Endo a) 

Methods

mempty :: Endo a #

mappend :: Endo a -> Endo a -> Endo a #

mconcat :: [Endo a] -> Endo a #

Num a => Monoid (Sum a) 

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

Num a => Monoid (Product a) 

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

Monoid (First a) 

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

mconcat :: [First a] -> First a #

Monoid (Last a) 

Methods

mempty :: Last a #

mappend :: Last a -> Last a -> Last a #

mconcat :: [Last a] -> Last a #

Monoid (PutM ()) 

Methods

mempty :: PutM () #

mappend :: PutM () -> PutM () -> PutM () #

mconcat :: [PutM ()] -> PutM () #

Monoid (IntMap a) 

Methods

mempty :: IntMap a #

mappend :: IntMap a -> IntMap a -> IntMap a #

mconcat :: [IntMap a] -> IntMap a #

Monoid (Seq a) 

Methods

mempty :: Seq a #

mappend :: Seq a -> Seq a -> Seq a #

mconcat :: [Seq a] -> Seq a #

Ord a => Monoid (Set a) 

Methods

mempty :: Set a #

mappend :: Set a -> Set a -> Set a #

mconcat :: [Set a] -> Set a #

Monoid (Doc a) 

Methods

mempty :: Doc a #

mappend :: Doc a -> Doc a -> Doc a #

mconcat :: [Doc a] -> Doc a #

Monoid (IResult a) 

Methods

mempty :: IResult a #

mappend :: IResult a -> IResult a -> IResult a #

mconcat :: [IResult a] -> IResult a #

Monoid (Result a) 

Methods

mempty :: Result a #

mappend :: Result a -> Result a -> Result a #

mconcat :: [Result a] -> Result a #

Storable a => Monoid (Vector a) 

Methods

mempty :: Vector a #

mappend :: Vector a -> Vector a -> Vector a #

mconcat :: [Vector a] -> Vector a #

Prim a => Monoid (Vector a) 

Methods

mempty :: Vector a #

mappend :: Vector a -> Vector a -> Vector a #

mconcat :: [Vector a] -> Vector a #

(Hashable a, Eq a) => Monoid (HashSet a) 

Methods

mempty :: HashSet a #

mappend :: HashSet a -> HashSet a -> HashSet a #

mconcat :: [HashSet a] -> HashSet a #

Monoid (DList a) 

Methods

mempty :: DList a #

mappend :: DList a -> DList a -> DList a #

mconcat :: [DList a] -> DList a #

Monoid (Vector a) 

Methods

mempty :: Vector a #

mappend :: Vector a -> Vector a -> Vector a #

mconcat :: [Vector a] -> Vector a #

Monoid (Parser a) 

Methods

mempty :: Parser a #

mappend :: Parser a -> Parser a -> Parser a #

mconcat :: [Parser a] -> Parser a #

Monoid (Array a) 

Methods

mempty :: Array a #

mappend :: Array a -> Array a -> Array a #

mconcat :: [Array a] -> Array a #

Monoid b => Monoid (a -> b) 

Methods

mempty :: a -> b #

mappend :: (a -> b) -> (a -> b) -> a -> b #

mconcat :: [a -> b] -> a -> b #

(Monoid a, Monoid b) => Monoid (a, b) 

Methods

mempty :: (a, b) #

mappend :: (a, b) -> (a, b) -> (a, b) #

mconcat :: [(a, b)] -> (a, b) #

Monoid (Proxy k s) 

Methods

mempty :: Proxy k s #

mappend :: Proxy k s -> Proxy k s -> Proxy k s #

mconcat :: [Proxy k s] -> Proxy k s #

Ord k => Monoid (Map k v) 

Methods

mempty :: Map k v #

mappend :: Map k v -> Map k v -> Map k v #

mconcat :: [Map k v] -> Map k v #

Monoid (Parser i a) 

Methods

mempty :: Parser i a #

mappend :: Parser i a -> Parser i a -> Parser i a #

mconcat :: [Parser i a] -> Parser i a #

(Eq k, Hashable k) => Monoid (HashMap k v) 

Methods

mempty :: HashMap k v #

mappend :: HashMap k v -> HashMap k v -> HashMap k v #

mconcat :: [HashMap k v] -> HashMap k v #

(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) 

Methods

mempty :: (a, b, c) #

mappend :: (a, b, c) -> (a, b, c) -> (a, b, c) #

mconcat :: [(a, b, c)] -> (a, b, c) #

Monoid a => Monoid (Const k a b) 

Methods

mempty :: Const k a b #

mappend :: Const k a b -> Const k a b -> Const k a b #

mconcat :: [Const k a b] -> Const k a b #

Alternative f => Monoid (Alt * f a) 

Methods

mempty :: Alt * f a #

mappend :: Alt * f a -> Alt * f a -> Alt * f a #

mconcat :: [Alt * f a] -> Alt * f a #

Monoid a => Monoid (Constant k a b) 

Methods

mempty :: Constant k a b #

mappend :: Constant k a b -> Constant k a b -> Constant k a b #

mconcat :: [Constant k a b] -> Constant k a b #

(Semigroup a, Monoid a) => Monoid (Tagged k s a) 

Methods

mempty :: Tagged k s a #

mappend :: Tagged k s a -> Tagged k s a -> Tagged k s a #

mconcat :: [Tagged k s a] -> Tagged k s a #

(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) 

Methods

mempty :: (a, b, c, d) #

mappend :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

mconcat :: [(a, b, c, d)] -> (a, b, c, d) #

(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) 

Methods

mempty :: (a, b, c, d, e) #

mappend :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e) #

join :: Monad m => m (m a) -> m a #

The join function is the conventional monad join operator. It is used to remove one level of monadic structure, projecting its bound argument into the outer level.

Lifted operations

class IfThenElse a b where Source #

Minimal complete definition

ifThenElse

Methods

ifThenElse :: a -> b -> b -> b Source #

Instances

IfThenElse Bool a Source # 

Methods

ifThenElse :: Bool -> a -> a -> a Source #

(~) * u1 u2 => IfThenElse (GenHaxl u1 Bool) (GenHaxl u2 a) Source # 

Methods

ifThenElse :: GenHaxl u1 Bool -> GenHaxl u2 a -> GenHaxl u2 a -> GenHaxl u2 a Source #

(.>) :: Ord a => GenHaxl u a -> GenHaxl u a -> GenHaxl u Bool infix 4 Source #

(.<) :: Ord a => GenHaxl u a -> GenHaxl u a -> GenHaxl u Bool infix 4 Source #

(.>=) :: Ord a => GenHaxl u a -> GenHaxl u a -> GenHaxl u Bool infix 4 Source #

(.<=) :: Ord a => GenHaxl u a -> GenHaxl u a -> GenHaxl u Bool infix 4 Source #

(.==) :: Eq a => GenHaxl u a -> GenHaxl u a -> GenHaxl u Bool infix 4 Source #

(./=) :: Eq a => GenHaxl u a -> GenHaxl u a -> GenHaxl u Bool infix 4 Source #

(.&&) :: GenHaxl u Bool -> GenHaxl u Bool -> GenHaxl u Bool infixr 3 Source #

(.||) :: GenHaxl u Bool -> GenHaxl u Bool -> GenHaxl u Bool infixr 2 Source #

(.++) :: GenHaxl u [a] -> GenHaxl u [a] -> GenHaxl u [a] Source #

pair :: GenHaxl u a -> GenHaxl u b -> GenHaxl u (a, b) Source #

pAnd :: GenHaxl u Bool -> GenHaxl u Bool -> GenHaxl u Bool infixr 5 Source #

Parallel version of '(.&&)'. Both arguments are evaluated in parallel, and if either returns False then the other is not evaluated any further.

WARNING: exceptions may be unpredictable when using pAnd. If one argument returns False before the other completes, then pAnd returns False immediately, ignoring a possible exception that the other argument may have produced if it had been allowed to complete.

pOr :: GenHaxl u Bool -> GenHaxl u Bool -> GenHaxl u Bool infixr 4 Source #

Parallel version of '(.||)'. Both arguments are evaluated in parallel, and if either returns True then the other is not evaluated any further.

WARNING: exceptions may be unpredictable when using pOr. If one argument returns True before the other completes, then pOr returns True immediately, ignoring a possible exception that the other argument may have produced if it had been allowed to complete.

Text things

data Text :: * #

Instances

ToJSONKey Text 

Methods

toJSONKey :: ToJSONKeyFunction Text

toJSONKeyList :: ToJSONKeyFunction [Text]

ToJSON Text 

Methods

toJSON :: Text -> Value

toEncoding :: Text -> Encoding

toJSONList :: [Text] -> Value

toEncodingList :: [Text] -> Encoding

KeyValue Pair 

Methods

(.=) :: ToJSON v => Text -> v -> Pair

Hashable Text 

Methods

hashWithSalt :: Int -> Text -> Int

hash :: Text -> Int

Chunk Text 

Associated Types

type ChunkElem Text :: *

Methods

nullChunk :: Text -> Bool

pappendChunk :: State Text -> Text -> State Text

atBufferEnd :: Text -> State Text -> Pos

bufferElemAt :: Text -> Pos -> State Text -> Maybe (ChunkElem Text, Int)

chunkElemToChar :: Text -> ChunkElem Text -> Char

ToJSON v => GKeyValue v (DList Pair) 

Methods

gPair :: String -> v -> DList Pair

FromPairs Value (DList Pair) 

Methods

fromPairs :: DList Pair -> Value

type Item Text 
type Item Text = Char
type State Text 
type State Text = Buffer
type ChunkElem Text 
type ChunkElem Text = Char

class IsString a where #

Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).

Minimal complete definition

fromString

Methods

fromString :: String -> a #

Instances

IsString ByteString 
IsString Doc 

Methods

fromString :: String -> Doc #

IsString Value 

Methods

fromString :: String -> Value #

(~) * a Char => IsString [a] 

Methods

fromString :: String -> [a] #

IsString a => IsString (Identity a) 

Methods

fromString :: String -> Identity a #

IsString (Seq Char) 

Methods

fromString :: String -> Seq Char #

IsString (Doc a) 

Methods

fromString :: String -> Doc a #

(~) * a Char => IsString (DList a) 

Methods

fromString :: String -> DList a #

(IsString a, Hashable a) => IsString (Hashed a) 

Methods

fromString :: String -> Hashed a #

IsString a => IsString (GenHaxl u a) # 

Methods

fromString :: String -> GenHaxl u a #

IsString a => IsString (Const * a b) 

Methods

fromString :: String -> Const * a b #

IsString a => IsString (Tagged k s a) 

Methods

fromString :: String -> Tagged k s a #

Exceptions

throw :: Exception e => e -> GenHaxl u a Source #

Throw an exception in the Haxl monad

catch :: Exception e => GenHaxl u a -> (e -> GenHaxl u a) -> GenHaxl u a Source #

Catch an exception in the Haxl monad

try :: Exception e => GenHaxl u a -> GenHaxl u (Either e a) Source #

Returns Left e if the computation throws an exception e, or Right a if it returns a result a.

withDefault :: a -> GenHaxl u a -> GenHaxl u a Source #

Runs the given GenHaxl computation, and if it throws a TransientError or LogicError exception (see Haxl.Core.Exception), the exception is ignored and the supplied default value is returned instead.

catchAny Source #

Arguments

:: GenHaxl u a

run this first

-> GenHaxl u a

if it throws LogicError or TransientError, run this

-> GenHaxl u a 

Catch LogicErrors and TransientErrors and perform an alternative action

data HaxlException Source #

We have a 3-tiered hierarchy of exceptions, with HaxlException at the top, and all Haxl exceptions as children of this. Users should never deal directly with HaxlExceptions.

The main types of exceptions are:

InternalError
Something is wrong with Haxl core.
LogicBug
Something is wrong with Haxl client code.
LogicError
Things that really should be return values, e.g. NotFound.
TransientError
Something is temporarily failing (usually in a fetch).

These are not meant to be thrown (but likely be caught). Thrown exceptions should be a subclass of one of these. There are some generic leaf exceptions defined below this, such as FetchError (generic transient failure) or CriticalError (internal failure).

Constructors

MiddleException e => HaxlException (Maybe Stack) e 

Orphan instances

Fractional a => Fractional (GenHaxl u a) Source # 

Methods

(/) :: GenHaxl u a -> GenHaxl u a -> GenHaxl u a #

recip :: GenHaxl u a -> GenHaxl u a #

fromRational :: Rational -> GenHaxl u a #

Num a => Num (GenHaxl u a) Source # 

Methods

(+) :: GenHaxl u a -> GenHaxl u a -> GenHaxl u a #

(-) :: GenHaxl u a -> GenHaxl u a -> GenHaxl u a #

(*) :: GenHaxl u a -> GenHaxl u a -> GenHaxl u a #

negate :: GenHaxl u a -> GenHaxl u a #

abs :: GenHaxl u a -> GenHaxl u a #

signum :: GenHaxl u a -> GenHaxl u a #

fromInteger :: Integer -> GenHaxl u a #