classy-prelude-0.12.1.1: A typeclass-based Prelude.

Safe HaskellNone
LanguageHaskell98

ClassyPrelude

Contents

Synopsis

CorePrelude

undefined :: a Source

Deprecated: It is highly recommended that you either avoid partial functions or provide meaningful error messages

We define our own undefined which is marked as deprecated. This makes it useful to use during development, but lets you more easily get notifications if you accidentally ship partial code in production.

The classy prelude recommendation for when you need to really have a partial function in production is to use error with a very descriptive message so that, in case an exception is thrown, you get more information than Prelude.undefined.

Since 0.5.5

Standard

Monoid

(++) :: Monoid m => m -> m -> m infixr 5 Source

Semigroup

class Semigroup a where

Minimal complete definition

Nothing

Methods

(<>) :: a -> a -> a infixr 6

An associative operation.

(a <> b) <> c = a <> (b <> c)

If a is also a Monoid we further require

(<>) = mappend

sconcat :: NonEmpty a -> a

Reduce a non-empty list with <>

The default definition should be sufficient, but this can be overridden for efficiency.

times1p :: Natural -> a -> a

Repeat a value (n + 1) times.

times1p n a = a <> a <> ... <> a  -- using <> n times

The default definition uses peasant multiplication, exploiting associativity to only require O(log n) uses of <>.

See also timesN.

data WrappedMonoid m :: * -> *

Provide a Semigroup for an arbitrary Monoid.

Instances

Generic1 WrappedMonoid 
Bounded a => Bounded (WrappedMonoid a) 
Enum a => Enum (WrappedMonoid a) 
Eq m => Eq (WrappedMonoid m) 
Data m => Data (WrappedMonoid m) 
Ord m => Ord (WrappedMonoid m) 
Read m => Read (WrappedMonoid m) 
Show m => Show (WrappedMonoid m) 
Generic (WrappedMonoid m) 
Monoid m => Monoid (WrappedMonoid m) 
Hashable a => Hashable (WrappedMonoid a) 
NFData m => NFData (WrappedMonoid m) 
Monoid m => Semigroup (WrappedMonoid m) 
Typeable (* -> *) WrappedMonoid 
type Rep1 WrappedMonoid = D1 D1WrappedMonoid (C1 C1_0WrappedMonoid (S1 S1_0_0WrappedMonoid Par1)) 
type Rep (WrappedMonoid m) = D1 D1WrappedMonoid (C1 C1_0WrappedMonoid (S1 S1_0_0WrappedMonoid (Rec0 m))) 

Functor

Applicative

Monad

whenM :: Monad m => m Bool -> m () -> m () Source

Only perform the action if the predicate returns True.

Since 0.9.2

unlessM :: Monad m => m Bool -> m () -> m () Source

Only perform the action if the predicate returns False.

Since 0.9.2

Mutable references

atomically :: MonadIO m => STM a -> m a Source

Generalized version of atomically.

alwaysSTM :: STM Bool -> STM () Source

Synonym for always.

retrySTM :: STM a Source

Synonym for retry.

orElseSTM :: STM a -> STM a -> STM a Source

Synonym for orElse.

checkSTM :: Bool -> STM () Source

Synonym for check.

Primitive (exported since 0.9.4)

class Monad m => PrimMonad m

Class of monads which can perform primitive state-transformer actions

Minimal complete definition

primitive

Associated Types

type PrimState m :: *

State token type

Instances

type family PrimState m :: *

State token type

Instances

type PrimState IO = RealWorld 
type PrimState (ST s) = s 
type PrimState (IdentityT m) = PrimState m 
type PrimState (ListT m) = PrimState m 
type PrimState (MaybeT m) = PrimState m 
type PrimState (ReaderT r m) = PrimState m 
type PrimState (StateT s m) = PrimState m 
type PrimState (StateT s m) = PrimState m 
type PrimState (ExceptT e m) = PrimState m 
type PrimState (ErrorT e m) = PrimState m 
type PrimState (WriterT w m) = PrimState m 
type PrimState (WriterT w m) = PrimState m 
type PrimState (RWST r w s m) = PrimState m 
type PrimState (RWST r w s m) = PrimState m 

primToPrim :: (PrimBase m1, PrimMonad m2, (~) * (PrimState m1) (PrimState m2)) => m1 a -> m2 a

Convert a PrimBase to another monad with the same state token.

primToIO :: (PrimBase m, (~) * (PrimState m) RealWorld) => m a -> IO a

Convert a PrimBase with a RealWorld state token to IO

primToST :: PrimBase m => m a -> ST (PrimState m) a

Convert a PrimBase to ST

Debugging

trace :: String -> a -> a

The trace function outputs the trace message given as its first argument, before returning the second argument as its result.

For example, this returns the value of f x but first outputs the message.

trace ("calling f with x = " ++ show x) (f x)

The trace function should only be used for debugging, or for monitoring execution. The function is not referentially transparent: its type indicates that it is a pure function but it has the side effect of outputting the trace message.

traceShow :: Show a => a -> b -> b

Like trace, but uses show on the argument to convert it to a String.

This makes it convenient for printing the values of interesting variables or expressions inside a function. For example here we print the value of the variables x and z:

f x y =
    traceShow (x, z) $ result
  where
    z = ...
    ...

traceId :: String -> String Source

Since 0.5.9

traceM :: Monad m => String -> m () Source

Since 0.5.9

traceShowId :: Show a => a -> a Source

Since 0.5.9

traceShowM :: (Show a, Monad m) => a -> m () Source

Since 0.5.9

assert :: Bool -> a -> a

If the first argument evaluates to True, then the result is the second argument. Otherwise an AssertionFailed exception is raised, containing a String with the source file and line number of the call to assert.

Assertions can normally be turned on or off with a compiler flag (for GHC, assertions are normally on unless optimisation is turned on with -O or the -fignore-asserts option is given). When assertions are turned off, the first argument to assert is ignored, and the second argument is returned as the result.

Time (since 0.6.1)

module Data.Time

Generics (since 0.8.1)

class Generic a

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

Minimal complete definition

from, to

Instances

Generic Bool 
Generic Char 
Generic Double 
Generic Float 
Generic Int 
Generic Ordering 
Generic () 
Generic All 
Generic Any 
Generic Arity 
Generic Fixity 
Generic Associativity 
Generic Void 
Generic [a] 
Generic (U1 p) 
Generic (Par1 p) 
Generic (ZipList a) 
Generic (Dual a) 
Generic (Endo a) 
Generic (Sum a) 
Generic (Product a) 
Generic (First a) 
Generic (Last a) 
Generic (Maybe a) 
Generic (Min a) 
Generic (Max a) 
Generic (First a) 
Generic (Last a) 
Generic (WrappedMonoid m) 
Generic (Option a) 
Generic (NonEmpty a) 
Generic (Either a b) 
Generic (Rec1 f p) 
Generic (a, b) 
Generic (Const a b) 
Generic (WrappedMonad m a) 
Generic (Proxy * t) 
Generic (Arg a b) 
Typeable (* -> Constraint) Generic 
Generic (K1 i c p) 
Generic ((:+:) f g p) 
Generic ((:*:) f g p) 
Generic ((:.:) f g p) 
Generic (a, b, c) 
Generic (WrappedArrow a b c) 
Generic (Tagged k s b) 
Generic (M1 i c f p) 
Generic (a, b, c, d) 
Generic (a, b, c, d, e) 
Generic (a, b, c, d, e, f) 
Generic (a, b, c, d, e, f, g) 

Transformers (since 0.9.4)

class Monad m => MonadReader r m | m -> r where

See examples in Control.Monad.Reader. Note, the partially applied function type (->) r is a simple reader monad. See the instance declaration below.

Minimal complete definition

(ask | reader), local

Methods

ask :: m r

Retrieves the monad environment.

Instances

MonadReader r m => MonadReader r (MaybeT m) 
MonadReader r m => MonadReader r (ListT m) 
MonadReader r m => MonadReader r (IdentityT m) 
MonadReader r ((->) r) 
(Representable f, (~) * (Rep f) a) => MonadReader a (Co f) 
(Monoid w, MonadReader r m) => MonadReader r (WriterT w m) 
(Monoid w, MonadReader r m) => MonadReader r (WriterT w m) 
MonadReader r m => MonadReader r (StateT s m) 
MonadReader r m => MonadReader r (StateT s m) 
Monad m => MonadReader r (ReaderT r m) 
MonadReader r m => MonadReader r (ExceptT e m) 
(Error e, MonadReader r m) => MonadReader r (ErrorT e m) 
MonadReader r' m => MonadReader r' (ContT r m) 
(Monad m, Monoid w) => MonadReader r (RWST r w s m) 
(Monad m, Monoid w) => MonadReader r (RWST r w s m) 

ask :: MonadReader r m => m r

Retrieves the monad environment.

newtype ReaderT r m a :: * -> (* -> *) -> * -> *

The reader monad transformer, which adds a read-only environment to the given monad.

The return function ignores the environment, while >>= passes the inherited environment to both subcomputations.

Constructors

ReaderT 

Fields

runReaderT :: r -> m a
 

Instances

Monad m => MonadReader r (ReaderT r m) 
MonadBaseControl b m => MonadBaseControl b (ReaderT r m) 
MonadTrans (ReaderT r) 
MonadTransControl (ReaderT r) 
Alternative m => Alternative (ReaderT r m) 
Monad m => Monad (ReaderT r m) 
Functor m => Functor (ReaderT r m) 
MonadFix m => MonadFix (ReaderT r m) 
MonadPlus m => MonadPlus (ReaderT r m) 
Applicative m => Applicative (ReaderT r m) 
Representable m => Representable (ReaderT e m) 
MonadIO m => MonadIO (ReaderT r m) 
Zip m => Zip (ReaderT e m) 
MonadThrow m => MonadThrow (ReaderT r m) 
MonadCatch m => MonadCatch (ReaderT r m) 
MonadMask m => MonadMask (ReaderT r m) 
Keyed m => Keyed (ReaderT e m) 
Zip m => Zip (ReaderT e m) 
ZipWithKey m => ZipWithKey (ReaderT e m) 
Indexable m => Indexable (ReaderT e m) 
Lookup m => Lookup (ReaderT e m) 
PrimMonad m => PrimMonad (ReaderT r m) 
Apply m => Apply (ReaderT e m) 
Bind m => Bind (ReaderT e m) 
Functor m => MonoFunctor (ReaderT r m a) 
Applicative m => MonoPointed (ReaderT r m a) 
type StT (ReaderT r) a = a 
type Rep (ReaderT e m) = (e, Rep m) 
type Key (ReaderT e m) = (e, Key m) 
type PrimState (ReaderT r m) = PrimState m 
type StM (ReaderT r m) a = ComposeSt (ReaderT r) m a 
type Element (ReaderT r m a) = a 

type Reader r = ReaderT r Identity

The parameterizable reader monad.

Computations are functions of a shared environment.

The return function ignores the environment, while >>= passes the inherited environment to both subcomputations.

Poly hierarchy

Bifunctor (since 0.10.0)

Mono hierarchy

I/O

data Handle :: *

Haskell defines operations to read and write characters from and to files, represented by values of type Handle. Each value of this type is a handle: a record used by the Haskell run-time system to manage I/O with file system objects. A handle has at least the following properties:

  • whether it manages input or output or both;
  • whether it is open, closed or semi-closed;
  • whether the object is seekable;
  • whether buffering is disabled, or enabled on a line or block basis;
  • a buffer (whose length may be zero).

Most handles will also have a current I/O position indicating where the next input or output operation will occur. A handle is readable if it manages only input or both input and output; likewise, it is writable if it manages only output or both input and output. A handle is open when first allocated. Once it is closed it can no longer be used for either input or output, though an implementation cannot re-use its storage while references remain to it. Handles are in the Show and Eq classes. The string produced by showing a handle is system dependent; it should include enough information to identify the handle for debugging. A handle is equal according to == only to itself; no attempt is made to compare the internal state of different handles for equality.

stdin :: Handle

A handle managing input from the Haskell program's standard input channel.

stdout :: Handle

A handle managing output to the Haskell program's standard output channel.

stderr :: Handle

A handle managing output to the Haskell program's standard error channel.

Non-standard

List-like classes

map :: Functor f => (a -> b) -> f a -> f b Source

concatMap :: (Monoid m, MonoFoldable c) => (Element c -> m) -> c -> m Source

foldMap :: (Monoid m, MonoFoldable c) => (Element c -> m) -> c -> m Source

pack :: IsSequence c => [Element c] -> c Source

repack :: (MonoFoldable a, IsSequence b, Element a ~ Element b) => a -> b Source

Repack from one type to another, dropping to a list in the middle.

repack = pack . unpack.

mapM_ :: (Monad m, MonoFoldable c) => (Element c -> m ()) -> c -> m () Source

sequence_ :: (Monad m, MonoFoldable mono, Element mono ~ m a) => mono -> m () Source

forM_ :: (Monad m, MonoFoldable c) => c -> (Element c -> m ()) -> m () Source

any :: MonoFoldable c => (Element c -> Bool) -> c -> Bool Source

all :: MonoFoldable c => (Element c -> Bool) -> c -> Bool Source

and :: (MonoFoldable mono, Element mono ~ Bool) => mono -> Bool Source

Since 0.9.2

or :: (MonoFoldable mono, Element mono ~ Bool) => mono -> Bool Source

Since 0.9.2

foldl' :: MonoFoldable c => (a -> Element c -> a) -> a -> c -> a Source

foldr :: MonoFoldable c => (Element c -> b -> b) -> b -> c -> b Source

foldM :: (Monad m, MonoFoldable c) => (a -> Element c -> m a) -> a -> c -> m a Source

readMay :: (Element c ~ Char, MonoFoldable c, Read a) => c -> Maybe a Source

zip :: Zip f => forall a b. f a -> f b -> f (a, b)

zip3 :: Zip3 f => forall a b c. f a -> f b -> f c -> f (a, b, c)

zip4 :: Zip4 f => forall a b c d. f a -> f b -> f c -> f d -> f (a, b, c, d)

zip5 :: Zip5 f => forall a b c d e. f a -> f b -> f c -> f d -> f e -> f (a, b, c, d, e)

zip6 :: Zip6 f => forall a b c d e g. f a -> f b -> f c -> f d -> f e -> f g -> f (a, b, c, d, e, g)

zip7 :: Zip7 f => forall a b c d e g h. f a -> f b -> f c -> f d -> f e -> f g -> f h -> f (a, b, c, d, e, g, h)

unzip :: Zip f => forall a b. f (a, b) -> (f a, f b)

unzip3 :: Zip3 f => forall a b c. f (a, b, c) -> (f a, f b, f c)

unzip4 :: Zip4 f => forall a b c d. f (a, b, c, d) -> (f a, f b, f c, f d)

unzip5 :: Zip5 f => forall a b c d e. f (a, b, c, d, e) -> (f a, f b, f c, f d, f e)

unzip6 :: Zip6 f => forall a b c d e g. f (a, b, c, d, e, g) -> (f a, f b, f c, f d, f e, f g)

unzip7 :: Zip7 f => forall a b c d e g h. f (a, b, c, d, e, g, h) -> (f a, f b, f c, f d, f e, f g, f h)

zipWith :: Zip f => forall a b c. (a -> b -> c) -> f a -> f b -> f c

zipWith3 :: Zip3 f => forall a b c d. (a -> b -> c -> d) -> f a -> f b -> f c -> f d

zipWith4 :: Zip4 f => forall a b c d e. (a -> b -> c -> d -> e) -> f a -> f b -> f c -> f d -> f e

zipWith5 :: Zip5 f => forall a b c d e g. (a -> b -> c -> d -> e -> g) -> f a -> f b -> f c -> f d -> f e -> f g

zipWith6 :: Zip6 f => forall a b c d e g h. (a -> b -> c -> d -> e -> g -> h) -> f a -> f b -> f c -> f d -> f e -> f g -> f h

zipWith7 :: Zip7 f => forall a b c d e g h i. (a -> b -> c -> d -> e -> g -> h -> i) -> f a -> f b -> f c -> f d -> f e -> f g -> f h -> f i

hashNub :: (Hashable a, Eq a) => [a] -> [a] Source

same behavior as nub, but requires Hashable & Eq and is O(n log n)

https://github.com/nh2/haskell-ordnub

ordNub :: Ord a => [a] -> [a] Source

same behavior as nub, but requires Ord and is O(n log n)

https://github.com/nh2/haskell-ordnub

ordNubBy :: Ord b => (a -> b) -> (a -> a -> Bool) -> [a] -> [a] Source

same behavior as nubBy, but requires Ord and is O(n log n)

https://github.com/nh2/haskell-ordnub

sortWith :: (Ord a, IsSequence c) => (Element c -> a) -> c -> c Source

Sort elements using the user supplied function to project something out of each element. Inspired by http://hackage.haskell.org/packages/archive/base/latest/doc/html/GHC-Exts.html#v:sortWith.

sum :: (MonoFoldable c, Num (Element c)) => c -> Element c Source

repeat :: a -> [a]

repeat x is an infinite list, with x the value of every element.

Set-like

(\\) :: SetContainer a => a -> a -> a infixl 9 Source

An alias for difference.

intersect :: SetContainer a => a -> a -> a Source

An alias for intersection.

Text-like

class Show a where

Conversion of values to readable Strings.

Minimal complete definition: showsPrec or show.

Derived instances of Show have the following properties, which are compatible with derived instances of Read:

  • The result of show is a syntactically correct Haskell expression containing only constants, given the fixity declarations in force at the point where the type is declared. It contains only the constructor names defined in the data type, parentheses, and spaces. When labelled constructor fields are used, braces, commas, field names, and equal signs are also used.
  • If the constructor is defined to be an infix operator, then showsPrec will produce infix applications of the constructor.
  • the representation will be enclosed in parentheses if the precedence of the top-level constructor in x is less than d (associativity is ignored). Thus, if d is 0 then the result is never surrounded in parentheses; if d is 11 it is always surrounded in parentheses, unless it is an atomic expression.
  • If the constructor is defined using record syntax, then show will produce the record-syntax form, with the fields given in the same order as the original declaration.

For example, given the declarations

infixr 5 :^:
data Tree a =  Leaf a  |  Tree a :^: Tree a

the derived instance of Show is equivalent to

instance (Show a) => Show (Tree a) where

       showsPrec d (Leaf m) = showParen (d > app_prec) $
            showString "Leaf " . showsPrec (app_prec+1) m
         where app_prec = 10

       showsPrec d (u :^: v) = showParen (d > up_prec) $
            showsPrec (up_prec+1) u .
            showString " :^: "      .
            showsPrec (up_prec+1) v
         where up_prec = 5

Note that right-associativity of :^: is ignored. For example,

  • show (Leaf 1 :^: Leaf 2 :^: Leaf 3) produces the string "Leaf 1 :^: (Leaf 2 :^: Leaf 3)".

Minimal complete definition

showsPrec | show

Methods

showsPrec

Arguments

:: Int

the operator precedence of the enclosing context (a number from 0 to 11). Function application has precedence 10.

-> a

the value to be converted to a String

-> ShowS 

Convert a value to a readable String.

showsPrec should satisfy the law

showsPrec d x r ++ s  ==  showsPrec d x (r ++ s)

Derived instances of Read and Show satisfy the following:

That is, readsPrec parses the string produced by showsPrec, and delivers the value that showsPrec started with.

show :: a -> String

A specialised variant of showsPrec, using precedence context zero, and returning an ordinary String.

showList :: [a] -> ShowS

The method showList is provided to allow the programmer to give a specialised way of showing lists of values. For example, this is used by the predefined Show instance of the Char type, where values of type String should be shown in double quotes, rather than between square brackets.

Instances

Show Bool 
Show Char 
Show Double 
Show Float 
Show Int 
Show Int8 
Show Int16 
Show Int32 
Show Int64 
Show Integer 
Show Ordering 
Show Word 
Show Word8 
Show Word16 
Show Word32 
Show Word64 
Show () 
Show Handle 
Show ThreadId 
Show HandleType 
Show SomeNat 
Show SomeSymbol 
Show HandlePosn 
Show BlockReason 
Show ThreadStatus 
Show BlockedIndefinitelyOnMVar 
Show BlockedIndefinitelyOnSTM 
Show Deadlock 
Show AssertionFailed 
Show SomeAsyncException 
Show AsyncException 
Show ArrayException 
Show ExitCode 
Show IOErrorType 
Show BufferMode 
Show Newline 
Show NewlineMode 
Show GeneralCategory 
Show MaskingState 
Show IOException 
Show ErrorCall 
Show ArithException 
Show All 
Show Any 
Show Arity 
Show Fixity 
Show Associativity 
Show TypeRep 
Show TyCon 
Show SomeException 
Show Text 
Show IntSet 
Show ByteString 
Show ByteString 
Show Text 
Show ShortByteString 
Show TimeLocale 
Show FilePath 
Show Padding 
Show DateFormatSpec 
Show LocalTime 
Show ZonedTime 
Show UTCTime 
Show Day 
Show Void 
Show a => Show [a] 
(Integral a, Show a) => Show (Ratio a) 
Show (U1 p) 
Show p => Show (Par1 p) 
Show a => Show (ZipList a) 
Show a => Show (Dual a) 
Show a => Show (Sum a) 
Show a => Show (Product a) 
Show a => Show (First a) 
Show a => Show (Last a) 
Show a => Show (Down a) 
Show a => Show (Maybe a) 
Show a => Show (Vector a) 
Show a => Show (HashSet a) 
Show a => Show (Seq a) 
Show a => Show (Set a) 
Show a => Show (IntMap a) 
Show a => Show (Identity a) 
Show a => Show (Tree a) 
Show a => Show (ViewL a) 
Show a => Show (ViewR a) 
Show a => Show (DList a) 
(Show a, Storable a) => Show (Vector a) 
Show a => Show (Min a) 
Show a => Show (Max a) 
Show a => Show (First a) 
Show a => Show (Last a) 
Show m => Show (WrappedMonoid m) 
Show a => Show (Option a) 
Show a => Show (NonEmpty a) 
(Show a, Unbox a) => Show (Vector a) 
(Show a, Prim a) => Show (Vector a) 
(Show a, Show b) => Show (Either a b) 
Show (f p) => Show (Rec1 f p) 
(Show a, Show b) => Show (a, b) 
Show (ST s a) 
Show a => Show (Const a b) 
(Show k, Show v) => Show (HashMap k v) 
(Show k, Show a) => Show (Map k a) 
(Show1 f, Show a) => Show (IdentityT f a) 
Show mono => Show (MinLen nat mono) 
(Show1 m, Show a) => Show (ListT m a) 
(Show a, Show b) => Show (Arg a b) 
(Show1 g, Show a) => Show (Apply g a) 
(Show1 m, Show a) => Show (MaybeT m a) 
Typeable (* -> Constraint) Show 
Show c => Show (K1 i c p) 
(Show (f p), Show (g p)) => Show ((:+:) f g p) 
(Show (f p), Show (g p)) => Show ((:*:) f g p) 
Show (f (g p)) => Show ((:.:) f g p) 
(Show a, Show b, Show c) => Show (a, b, c) 
Show (Coercion k a b) 
Show ((:~:) k a b) 
(Show (f a), Show (g a)) => Show (Coproduct f g a) 
(Show e, Show1 m, Show a) => Show (ExceptT e m a) 
(Show e, Show1 m, Show a) => Show (ErrorT e m a) 
(Show w, Show1 m, Show a) => Show (WriterT w m a) 
(Show w, Show1 m, Show a) => Show (WriterT w m a) 
(Functor f, Show1 f, Show1 g, Show a) => Show (Compose f g a) 
Show b => Show (Tagged k s b) 
(Show1 f, Show1 g, Show a) => Show (Product f g a) 
Show (f p) => Show (M1 i c f p) 
(Show a, Show b, Show c, Show d) => Show (a, b, c, d) 
(Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e) 
(Show a, Show b, Show c, Show d, Show e, Show f) => Show (a, b, c, d, e, f) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g) => Show (a, b, c, d, e, f, g) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h) => Show (a, b, c, d, e, f, g, h) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i) => Show (a, b, c, d, e, f, g, h, i) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j) => Show (a, b, c, d, e, f, g, h, i, j) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k) => Show (a, b, c, d, e, f, g, h, i, j, k) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l) => Show (a, b, c, d, e, f, g, h, i, j, k, l) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n, Show o) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 

tshow :: Show a => a -> Text Source

tlshow :: Show a => a -> LText Source

Case conversion

charToLower :: Char -> Char Source

Convert a character to lower case.

Character-based case conversion is lossy in comparison to string-based toLower. For instance, İ will be converted to i, instead of i̇.

charToUpper :: Char -> Char Source

Convert a character to upper case.

Character-based case conversion is lossy in comparison to string-based toUpper. For instance, ß won't be converted to SS.

IO

class IsSequence a => IOData a where

Data which can be read to and from files and handles.

Note that, for lazy sequences, these operations may perform lazy I/O.

Methods

readFile :: MonadIO m => FilePath -> m a

writeFile :: MonadIO m => FilePath -> a -> m ()

getLine :: MonadIO m => m a

hGetContents :: MonadIO m => Handle -> m a

hGetLine :: MonadIO m => Handle -> m a

hPut :: MonadIO m => Handle -> a -> m ()

hPutStrLn :: MonadIO m => Handle -> a -> m ()

hGetChunk :: MonadIO m => Handle -> m a

print :: (Show a, MonadIO m) => a -> m () Source

hClose :: Handle -> IO ()

Computation hClose hdl makes handle hdl closed. Before the computation finishes, if hdl is writable its buffer is flushed as for hFlush. Performing hClose on a handle that has already been closed has no effect; doing so is not an error. All other operations on a closed handle will fail. If hClose fails for any reason, any further operations (apart from hClose) on the handle will still fail as if hdl had been successfully closed.

FilePath

fpToString :: FilePath -> String Source

Deprecated: Now same as id

fpFromString :: String -> FilePath Source

Deprecated: Now same as id

fpToText :: FilePath -> Text Source

Deprecated: Use pack

Translates a FilePath to a Text This translation is not correct for a (unix) filename which can contain arbitrary (non-unicode) bytes: those bytes will be discarded.

This means you cannot translate the Text back to the original file name.

If you control or otherwise understand the filenames and believe them to be unicode valid consider using fpToTextEx or fpToTextWarn

fpFromText :: Text -> FilePath Source

Deprecated: Use unpack

fpToTextWarn :: Monad m => FilePath -> m Text Source

Deprecated: Use pack

Translates a FilePath to a Text

Warns if there are non-unicode sequences in the file name

fpToTextEx :: FilePath -> Text Source

Deprecated: Use pack

Translates a FilePath to a Text

Throws an exception if there are non-unicode sequences in the file name

Use this to assert that you know a filename will translate properly into a Text. If you created the filename, this should be the case.

Difference lists

data DList a :: * -> *

A difference list is a function that, given a list, returns the original contents of the difference list prepended to the given list.

This structure supports O(1) append and snoc operations on lists, making it very useful for append-heavy uses (esp. left-nested uses of ++), such as logging and pretty printing.

Here is an example using DList as the state type when printing a tree with the Writer monad:

import Control.Monad.Writer
import Data.DList

data Tree a = Leaf a | Branch (Tree a) (Tree a)

flatten_writer :: Tree x -> DList x
flatten_writer = snd . runWriter . flatten
    where
      flatten (Leaf x)     = tell (singleton x)
      flatten (Branch x y) = flatten x >> flatten y

asDList :: DList a -> DList a Source

Force type to a DList

Since 0.11.0

applyDList :: DList a -> [a] -> [a] Source

Synonym for apply

Since 0.11.0

Exceptions

class Monad m => MonadThrow m where

A class for monads in which exceptions may be thrown.

Instances should obey the following law:

throwM e >> x = throwM e

In other words, throwing an exception short-circuits the rest of the monadic computation.

Methods

throwM :: Exception e => e -> m a

Throw an exception. Note that this throws when this action is run in the monad m, not when it is applied. It is a generalization of Control.Exception's throwIO.

Should satisfy the law:

throwM e >> f = throwM e

Instances

MonadThrow [] 
MonadThrow IO 
MonadThrow STM 
MonadThrow Maybe 
(~) * e SomeException => MonadThrow (Either e) 
MonadThrow m => MonadThrow (IdentityT m) 
MonadThrow m => MonadThrow (ListT m) 
MonadThrow m => MonadThrow (MaybeT m)

Throws exceptions into the base monad.

MonadThrow m => MonadThrow (ContT r m) 
MonadThrow m => MonadThrow (ReaderT r m) 
MonadThrow m => MonadThrow (StateT s m) 
MonadThrow m => MonadThrow (StateT s m) 
MonadThrow m => MonadThrow (ExceptT e m)

Throws exceptions into the base monad.

(Error e, MonadThrow m) => MonadThrow (ErrorT e m)

Throws exceptions into the base monad.

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 
(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 
(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 
(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 

class MonadThrow m => MonadCatch m

A class for monads which allow exceptions to be caught, in particular exceptions which were thrown by throwM.

Instances should obey the following law:

catch (throwM e) f = f e

Note that the ability to catch an exception does not guarantee that we can deal with all possible exit points from a computation. Some monads, such as continuation-based stacks, allow for more than just a success/failure strategy, and therefore catch cannot be used by those monads to properly implement a function such as finally. For more information, see MonadMask.

Minimal complete definition

catch

Instances

MonadCatch IO 
MonadCatch STM 
MonadCatch m => MonadCatch (IdentityT m) 
MonadCatch m => MonadCatch (ListT m) 
MonadCatch m => MonadCatch (MaybeT m)

Catches exceptions from the base monad.

MonadCatch m => MonadCatch (ReaderT r m) 
MonadCatch m => MonadCatch (StateT s m) 
MonadCatch m => MonadCatch (StateT s m) 
MonadCatch m => MonadCatch (ExceptT e m)

Catches exceptions from the base monad.

(Error e, MonadCatch m) => MonadCatch (ErrorT e m)

Catches exceptions from the base monad.

(MonadCatch m, Monoid w) => MonadCatch (WriterT w m) 
(MonadCatch m, Monoid w) => MonadCatch (WriterT w m) 
(MonadCatch m, Monoid w) => MonadCatch (RWST r w s m) 
(MonadCatch m, Monoid w) => MonadCatch (RWST r w s m) 

class MonadCatch m => MonadMask m

A class for monads which provide for the ability to account for all possible exit points from a computation, and to mask asynchronous exceptions. Continuation-based monads, and stacks such as ErrorT e IO which provide for multiple failure modes, are invalid instances of this class.

Note that this package does provide a MonadMask instance for CatchT. This instance is only valid if the base monad provides no ability to provide multiple exit. For example, IO or Either would be invalid base monads, but Reader or State would be acceptable.

Instances should ensure that, in the following code:

f `finally` g

The action g is called regardless of what occurs within f, including async exceptions.

Minimal complete definition

mask, uninterruptibleMask

Instances

MonadMask IO 
MonadMask m => MonadMask (IdentityT m) 
MonadMask m => MonadMask (ReaderT r m) 
MonadMask m => MonadMask (StateT s m) 
MonadMask m => MonadMask (StateT s m) 
(MonadMask m, Monoid w) => MonadMask (WriterT w m) 
(MonadMask m, Monoid w) => MonadMask (WriterT w m) 
(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 
(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 

Force types

Helper functions for situations where type inferer gets confused.

asList :: [a] -> [a] Source

asMap :: Map k v -> Map k v Source

asSet :: Set a -> Set a Source