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

Safe HaskellNone

ClassyPrelude

Contents

Synopsis

CorePrelude

undefined :: aSource

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 let's you more easily getting notification 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 -> mSource

Semigroup

class Semigroup a where

Methods

(<>) :: a -> a -> a

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 :: Whole n => n -> 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 times.

data WrappedMonoid m

Provide a Semigroup for an arbitrary Monoid.

Monad

Mutable references

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 -> StringSource

Since 0.5.9

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

Since 0.5.9

traceShowId :: Show a => a -> aSource

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.

Poly hierarchy

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 bSource

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

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

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

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

repack = pack . unpack.

mapM :: Traversable t => forall a m b. Monad m => (a -> m b) -> t a -> m (t b)

Map each element of a structure to a monadic action, evaluate these actions from left to right, and collect the results.

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

forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)

forM is mapM with its arguments flipped.

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

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

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

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

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

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

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

zip :: CanZip c1 c2 withRes t => c1 -> c2 -> t (Element c1, Element c2)Source

zip3 :: CanZip3 t a b c d => t a -> t b -> t c -> t (a, b, c)Source

zip4 :: CanZip4 t a b c d e => t a -> t b -> t c -> t d -> t (a, b, c, d)Source

zip5 :: CanZip5 t a b c d e f => t a -> t b -> t c -> t d -> t e -> t (a, b, c, d, e)Source

zip6 :: CanZip6 t a b c d e f g => t a -> t b -> t c -> t d -> t e -> t f -> t (a, b, c, d, e, f)Source

zip7 :: CanZip7 t a b c d e f g h => t a -> t b -> t c -> t d -> t e -> t f -> t g -> t (a, b, c, d, e, f, g)Source

unzip :: CanZip c1 c2 withRes t => t (Element c1, Element c2) -> (c1, c2)Source

unzip3 :: CanZip3 t a b c d => t (a, b, c) -> (t a, t b, t c)Source

unzip4 :: CanZip4 t a b c d e => t (a, b, c, d) -> (t a, t b, t c, t d)Source

unzip5 :: CanZip5 t a b c d e f => t (a, b, c, d, e) -> (t a, t b, t c, t d, t e)Source

unzip6 :: CanZip6 t a b c d e f g => t (a, b, c, d, e, f) -> (t a, t b, t c, t d, t e, t f)Source

unzip7 :: CanZip7 t a b c d e f g h => t (a, b, c, d, e, f, g) -> (t a, t b, t c, t d, t e, t f, t g)Source

zipWith :: CanZip c1 c2 withRes t => (Element c1 -> Element c2 -> Element withRes) -> c1 -> c2 -> withResSource

zipWith3 :: CanZip3 t a b c d => (a -> b -> c -> d) -> t a -> t b -> t c -> t dSource

zipWith4 :: CanZip4 t a b c d e => (a -> b -> c -> d -> e) -> t a -> t b -> t c -> t d -> t eSource

zipWith5 :: CanZip5 t a b c d e f => (a -> b -> c -> d -> e -> f) -> t a -> t b -> t c -> t d -> t e -> t fSource

zipWith6 :: CanZip6 t a b c d e f g => (a -> b -> c -> d -> e -> f -> g) -> t a -> t b -> t c -> t d -> t e -> t f -> t gSource

zipWith7 :: CanZip7 t a b c d e f g h => (a -> b -> c -> d -> e -> f -> g -> h) -> t a -> t b -> t c -> t d -> t e -> t f -> t g -> t hSource

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

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 cSource

repeat :: a -> [a]

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

Set-like

(\\) :: Container a => a -> a -> aSource

An alias for difference.

intersect :: Container a => a -> a -> aSource

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)".

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 HandlePosn 
Show BlockReason 
Show ThreadStatus 
Show BlockedIndefinitelyOnMVar 
Show BlockedIndefinitelyOnSTM 
Show Deadlock 
Show AssertionFailed 
Show AsyncException 
Show ArrayException 
Show ExitCode 
Show IOErrorType 
Show BufferMode 
Show Newline 
Show NewlineMode 
Show All 
Show Any 
Show Arity 
Show Fixity 
Show Associativity 
Show MaskingState 
Show IOException 
Show SomeException 
Show ErrorCall 
Show ArithException 
Show FilePath 
Show Text 
Show ByteString 
Show ByteString 
Show IntSet 
Show Text 
Show a => Show [a] 
(Integral a, Show a) => Show (Ratio 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 (Maybe a) 
Show a => Show (Vector a) 
Show a => Show (HashSet a) 
Show a => Show (Set a) 
Show a => Show (Seq a) 
Show a => Show (Tree a) 
Show a => Show (ViewL a) 
Show a => Show (ViewR a) 
Show a => Show (IntMap 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 (Rules a) 
(Show a, Unbox a) => Show (Vector a) 
(Show a, Storable a) => Show (Vector a) 
(Show a, Prim a) => Show (Vector a) 
(Show a, Show b) => Show (Either a b) 
(Show a, Show b) => Show (a, b) 
Show (ST s a) 
(Ix a, Show a, Show b) => Show (Array a b) 
(Show k, Show v) => Show (HashMap k v) 
(Show k, Show a) => Show (Map k a) 
(Show (f (Cofree f a)), Show a) => Show (Cofree f a) 
(Show (f (Free f a)), Show a) => Show (Free f a) 
(Show a, Show b, Show c) => Show (a, b, c) 
(Show (f a), Show (g a)) => Show (Coproduct f g a) 
(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 -> TextSource

tlshow :: Show a => a -> LTextSource

IO

class IsSequence a => IOData a whereSource

Methods

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

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

getLine :: MonadIO m => m aSource

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

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

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

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

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

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

Exceptions

catchAny :: MonadBaseControl IO m => m a -> (SomeException -> m a) -> m aSource

A version of catch which is specialized for any exception. This simplifies usage as no explicit type signatures are necessary.

Note that since version 0.5.9, this function now has proper support for asynchronous exceptions, by only catching exceptions generated by the internal action.

Since 0.5.6

handleAny :: MonadBaseControl IO m => (SomeException -> m a) -> m a -> m aSource

A version of handle which is specialized for any exception. This simplifies usage as no explicit type signatures are necessary.

Note that since version 0.5.9, this function now has proper support for asynchronous exceptions, by only catching exceptions generated by the internal action.

Since 0.5.6

tryAny :: MonadBaseControl IO m => m a -> m (Either SomeException a)Source

A version of try which is specialized for any exception. This simplifies usage as no explicit type signatures are necessary.

Note that since version 0.5.9, this function now has proper support for asynchronous exceptions, by only catching exceptions generated by the internal action.

Since 0.5.6

catchAnyDeep :: (NFData a, MonadBaseControl IO m) => m a -> (SomeException -> m a) -> m aSource

An extension to catchAny which ensures that the return value is fully evaluated. See tryAnyDeep.

Since 0.5.9

handleAnyDeep :: (NFData a, MonadBaseControl IO m) => (SomeException -> m a) -> m a -> m aSource

flip catchAnyDeep

Since 0.5.6

tryAnyDeep :: (NFData a, MonadBaseControl IO m) => m a -> m (Either SomeException a)Source

An extension to tryAny which ensures that the return value is fully evaluated. In other words, if you get a Right response here, you can be confident that using it will not result in another exception.

Since 0.5.9

catchIO :: MonadBaseControl IO m => m a -> (IOException -> m a) -> m aSource

A version of catch which is specialized for IO exceptions. This simplifies usage as no explicit type signatures are necessary.

Since 0.5.6

handleIO :: MonadBaseControl IO m => (IOException -> m a) -> m a -> m aSource

A version of handle which is specialized for IO exceptions. This simplifies usage as no explicit type signatures are necessary.

Since 0.5.6

tryIO :: MonadBaseControl IO m => m a -> m (Either IOException a)Source

A version of try which is specialized for IO exceptions. This simplifies usage as no explicit type signatures are necessary.

Since 0.5.6

Force types

Helper functions for situations where type inferer gets confused.

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

asMap :: Map k v -> Map k vSource

asSet :: Set a -> Set aSource