Safe Haskell | None |
---|---|
Language | Haskell2010 |
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 impliesNoImplicitPrelude
, and allowsif
-then
-else
to be used with a monadic condition. - Use
OverloadedStrings
(we useText
a lot)
- module Prelude
- data GenHaxl u a
- dataFetch :: (DataSource u r, Request r a) => r a -> GenHaxl u a
- class (DataSourceName req, StateKey req, ShowP req) => DataSource u req
- memo :: (Typeable a, Typeable k, Hashable k, Eq k) => k -> GenHaxl u a -> GenHaxl u a
- memoize :: GenHaxl u a -> GenHaxl u a
- memoize1 :: (Eq a, Hashable a) => (a -> GenHaxl u b) -> GenHaxl u (a -> GenHaxl u b)
- memoize2 :: (Eq a, Hashable a, Eq b, Hashable b) => (a -> b -> GenHaxl u c) -> GenHaxl u (a -> b -> GenHaxl u c)
- class Functor f => Applicative f where
- mapM :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b)
- mapM_ :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f ()
- sequence :: (Traversable t, Applicative f) => t (f a) -> f (t a)
- sequence_ :: (Traversable t, Applicative f) => t (f a) -> f ()
- filterM :: Applicative f => (a -> f Bool) -> [a] -> f [a]
- foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
- forM :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b)
- forM_ :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f ()
- foldl' :: Foldable t => forall b a. (b -> a -> b) -> b -> t a -> b
- sort :: Ord a => [a] -> [a]
- class Monoid a where
- join :: Monad m => m (m a) -> m a
- class IfThenElse a b where
- (.>) :: Ord a => GenHaxl u a -> GenHaxl u a -> GenHaxl u Bool
- (.<) :: Ord a => GenHaxl u a -> GenHaxl u a -> GenHaxl u Bool
- (.>=) :: Ord a => GenHaxl u a -> GenHaxl u a -> GenHaxl u Bool
- (.<=) :: Ord a => GenHaxl u a -> GenHaxl u a -> GenHaxl u Bool
- (.==) :: Eq a => GenHaxl u a -> GenHaxl u a -> GenHaxl u Bool
- (./=) :: Eq a => GenHaxl u a -> GenHaxl u a -> GenHaxl u Bool
- (.&&) :: GenHaxl u Bool -> GenHaxl u Bool -> GenHaxl u Bool
- (.||) :: GenHaxl u Bool -> GenHaxl u Bool -> GenHaxl u Bool
- (.++) :: GenHaxl u [a] -> GenHaxl u [a] -> GenHaxl u [a]
- pair :: GenHaxl u a -> GenHaxl u b -> GenHaxl u (a, b)
- pAnd :: GenHaxl u Bool -> GenHaxl u Bool -> GenHaxl u Bool
- pOr :: GenHaxl u Bool -> GenHaxl u Bool -> GenHaxl u Bool
- data Text :: *
- class IsString a where
- throw :: Exception e => e -> GenHaxl u a
- catch :: Exception e => GenHaxl u a -> (e -> GenHaxl u a) -> GenHaxl u a
- try :: Exception e => GenHaxl u a -> GenHaxl u (Either e a)
- withDefault :: a -> GenHaxl u a -> GenHaxl u a
- catchAny :: GenHaxl u a -> GenHaxl u a -> GenHaxl u a
- data HaxlException = MiddleException e => HaxlException (Maybe Stack) e
- data TransientError = Exception e => TransientError e
- data LogicError = Exception e => LogicError e
- newtype NotFound = NotFound Text
- newtype UnexpectedType = UnexpectedType Text
- newtype FetchError = FetchError Text
- newtype EmptyList = EmptyList Text
- newtype InvalidParameter = InvalidParameter Text
The Standard Haskell Prelude
module Prelude
Haxl and Fetching data
The Haxl monad, which does several things:
- It is a reader monad for
Env
andIORef
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 theRequestStore
, and then resume the computation. - The Applicative combinator
<*>
explores both branches in the event that the left branch isBlocked
, so that we can collect multiple requests and submit them as a batch. - It contains IO, so that we can perform real data fetching.
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.
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
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).
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.
mapM :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) Source #
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
.
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.
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
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 newtype
s and make those instances
of Monoid
, e.g. Sum
and Product
.
Identity of mappend
An associative operation
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.
Monoid Ordering | |
Monoid () | |
Monoid ByteString | |
Monoid Series | |
Monoid Buffer | |
Monoid Buffer | |
Monoid More | |
Monoid All | |
Monoid Any | |
Monoid IntSet | |
Monoid Doc | |
Monoid [a] | |
Monoid a => Monoid (Maybe a) | Lift a semigroup into |
Monoid a => Monoid (IO a) | |
Monoid (IResult a) | |
Monoid (Result a) | |
Monoid (Parser a) | |
Ord a => Monoid (Max a) | |
Ord a => Monoid (Min a) | |
Monoid a => Monoid (Identity a) | |
(Ord a, Bounded a) => Monoid (Min a) | |
(Ord a, Bounded a) => Monoid (Max a) | |
Monoid m => Monoid (WrappedMonoid m) | |
Semigroup a => Monoid (Option a) | |
Monoid a => Monoid (Dual a) | |
Monoid (Endo a) | |
Num a => Monoid (Sum a) | |
Num a => Monoid (Product a) | |
Monoid (First a) | |
Monoid (Last a) | |
Monoid (PutM ()) | |
Monoid (IntMap a) | |
Monoid (Seq a) | |
Ord a => Monoid (Set a) | |
Monoid (DList a) | |
Monoid (Doc a) | |
Monoid (Array a) | |
(Hashable a, Eq a) => Monoid (HashSet a) | |
Monoid (Vector a) | |
Storable a => Monoid (Vector a) | |
Prim a => Monoid (Vector a) | |
Monoid b => Monoid (a -> b) | |
(Monoid a, Monoid b) => Monoid (a, b) | |
(Eq k, Hashable k) => Monoid (HashMap k v) | |
Ord k => Monoid (Map k v) | |
Monoid (Parser i a) | |
Monoid (Proxy k s) | |
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) | |
Monoid a => Monoid (Const k a b) | |
Alternative f => Monoid (Alt * f a) | |
(Semigroup a, Monoid a) => Monoid (Tagged k s a) | |
Monoid a => Monoid (Constant k a b) | |
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) | |
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (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 #
ifThenElse :: a -> b -> b -> 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
A space efficient, packed, unboxed Unicode text type.
Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).
fromString :: String -> a #
IsString ByteString | |
IsString Value | |
IsString Doc | |
(~) * a Char => IsString [a] | |
IsString a => IsString (Identity a) | |
IsString (Seq Char) | |
(~) * a Char => IsString (DList a) | |
(IsString a, Hashable a) => IsString (Hashed a) | |
IsString (Doc a) | |
IsString a => IsString (GenHaxl u a) # | |
IsString a => IsString (Const * a b) | |
IsString a => IsString (Tagged k s a) | |
Exceptions
catch :: Exception e => GenHaxl u a -> (e -> GenHaxl u a) -> GenHaxl u a Source #
Catch an exception in the Haxl monad
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.
:: GenHaxl u a | run this first |
-> GenHaxl u a | if it throws |
-> GenHaxl u a |
Catch LogicError
s and TransientError
s 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 HaxlException
s.
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).
MiddleException e => HaxlException (Maybe Stack) e |
Show HaxlException Source # | |
ToJSON HaxlException Source # | These need to be serializable to JSON to cross FFI boundaries. |
Exception HaxlException Source # | |
Generic "something was not found" exception.
newtype UnexpectedType Source #
Generic "something had the wrong type" exception.
newtype FetchError Source #
Generic transient fetching exceptions.
Generic "input list was empty" exception.
newtype InvalidParameter Source #
Generic "passing some invalid parameter" exception.
Orphan instances
Fractional a => Fractional (GenHaxl u a) Source # | |
Num a => Num (GenHaxl u a) Source # | |