Safe Haskell | None |
---|---|
Language | Haskell2010 |
BasicPrelude mostly re-exports several key libraries in their entirety. The exception is Data.List, where various functions are replaced by similar versions that are either generalized, operate on Text, or are implemented strictly.
- module CorePrelude
- module Data.List
- module Control.Monad
- class Foldable t where
- elem :: Foldable t => forall a. Eq a => a -> t a -> Bool
- maximum :: Foldable t => forall a. Ord a => t a -> a
- minimum :: Foldable t => forall a. Ord a => t a -> a
- traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f ()
- sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f ()
- for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f ()
- maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
- minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
- class (Functor t, Foldable t) => Traversable t where
- for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b)
- map :: Functor f => (a -> b) -> f a -> f b
- empty :: Monoid w => w
- (++) :: Monoid w => w -> w -> w
- concat :: Monoid w => [w] -> w
- intercalate :: Monoid w => w -> [w] -> w
- sum :: (Foldable f, Num a) => f a -> a
- product :: (Foldable f, Num a) => f a -> a
- tshow :: Show a => a -> Text
- fromShow :: (Show a, IsString b) => a -> b
- read :: Read a => Text -> a
- readIO :: (MonadIO m, Read a) => Text -> m a
- readFile :: MonadIO m => FilePath -> m Text
- writeFile :: MonadIO m => FilePath -> Text -> m ()
- appendFile :: MonadIO m => FilePath -> Text -> m ()
- lines :: Text -> [Text]
- words :: Text -> [Text]
- unlines :: [Text] -> Text
- unwords :: [Text] -> Text
- textToString :: Text -> String
- ltextToString :: LText -> String
- fpToText :: FilePath -> Text
- fpFromText :: Text -> FilePath
- fpToString :: FilePath -> String
- encodeUtf8 :: Text -> ByteString
- decodeUtf8 :: ByteString -> Text
- getLine :: MonadIO m => m Text
- getContents :: MonadIO m => m LText
- interact :: MonadIO m => (LText -> LText) -> m ()
- gcd :: Integral a => a -> a -> a
- lcm :: Integral a => a -> a -> a
- class Show a where
- type ShowS = String -> String
- shows :: Show a => a -> ShowS
- showChar :: Char -> ShowS
- showString :: String -> ShowS
- showParen :: Bool -> ShowS -> ShowS
- type ReadS a = String -> [(a, String)]
- readsPrec :: Read a => Int -> ReadS a
- readList :: Read a => ReadS [a]
- reads :: Read a => ReadS a
- readParen :: Bool -> ReadS a -> ReadS a
- lex :: ReadS String
- readMay :: Read a => Text -> Maybe a
- getChar :: MonadIO m => m Char
- putChar :: MonadIO m => Char -> m ()
- readLn :: (MonadIO m, Read a) => m a
Module exports
module CorePrelude
module Data.List
module Control.Monad
Folds and traversals
Data structures that can be folded.
For example, given a data type
data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
a suitable instance would be
instance Foldable Tree where foldMap f Empty = mempty foldMap f (Leaf x) = f x foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r
This is suitable even for abstract types, as the monoid is assumed
to satisfy the monoid laws. Alternatively, one could define foldr
:
instance Foldable Tree where foldr f z Empty = z foldr f z (Leaf x) = f x z foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l
Foldable
instances are expected to satisfy the following laws:
foldr f z t = appEndo (foldMap (Endo . f) t ) z
foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
fold = foldMap id
sum
, product
, maximum
, and minimum
should all be essentially
equivalent to foldMap
forms, such as
sum = getSum . foldMap Sum
but may be less defined.
If the type is also a Functor
instance, it should satisfy
foldMap f = fold . fmap f
which implies that
foldMap f . fmap g = foldMap (f . g)
foldMap :: Monoid m => (a -> m) -> t a -> m #
Map each element of the structure to a monoid, and combine the results.
foldr :: (a -> b -> b) -> b -> t a -> b #
Right-associative fold of a structure.
In the case of lists, foldr
, when applied to a binary operator, a
starting value (typically the right-identity of the operator), and a
list, reduces the list using the binary operator, from right to left:
foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)
Note that, since the head of the resulting expression is produced by
an application of the operator to the first element of the list,
foldr
can produce a terminating expression from an infinite list.
For a general Foldable
structure this should be semantically identical
to,
foldr f z =foldr
f z .toList
foldr' :: (a -> b -> b) -> b -> t a -> b #
Right-associative fold of a structure, but with strict application of the operator.
foldl :: (b -> a -> b) -> b -> t a -> b #
Left-associative fold of a structure.
In the case of lists, foldl
, when applied to a binary
operator, a starting value (typically the left-identity of the operator),
and a list, reduces the list using the binary operator, from left to
right:
foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn
Note that to produce the outermost application of the operator the
entire input list must be traversed. This means that foldl'
will
diverge if given an infinite list.
Also note that if you want an efficient left-fold, you probably want to
use foldl'
instead of foldl
. The reason for this is that latter does
not force the "inner" results (e.g. z
in the above example)
before applying them to the operator (e.g. to f
x1(
). This results
in a thunk chain f
x2)O(n)
elements long, which then must be evaluated from
the outside-in.
For a general Foldable
structure this should be semantically identical
to,
foldl f z =foldl
f z .toList
foldl' :: (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
foldr1 :: (a -> a -> a) -> t a -> a #
A variant of foldr
that has no base case,
and thus may only be applied to non-empty structures.
foldr1
f =foldr1
f .toList
foldl1 :: (a -> a -> a) -> t a -> a #
A variant of foldl
that has no base case,
and thus may only be applied to non-empty structures.
foldl1
f =foldl1
f .toList
Test whether the structure is empty. The default implementation is optimized for structures that are similar to cons-lists, because there is no general way to do better.
Returns the size/length of a finite structure as an Int
. The
default implementation is optimized for structures that are similar to
cons-lists, because there is no general way to do better.
elem :: Eq a => a -> t a -> Bool infix 4 #
Does the element occur in the structure?
maximum :: Ord a => t a -> a #
The largest element of a non-empty structure.
minimum :: Ord a => t a -> a #
The least element of a non-empty structure.
traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f () #
Map each element of a structure to an action, evaluate these
actions from left to right, and ignore the results. For a version
that doesn't ignore the results see traverse
.
sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f () #
Evaluate each action in the structure from left to right, and
ignore the results. For a version that doesn't ignore the results
see sequenceA
.
for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f () #
class (Functor t, Foldable t) => Traversable t where #
Functors representing data structures that can be traversed from left to right.
A definition of traverse
must satisfy the following laws:
- naturality
t .
for every applicative transformationtraverse
f =traverse
(t . f)t
- identity
traverse
Identity = Identity- composition
traverse
(Compose .fmap
g . f) = Compose .fmap
(traverse
g) .traverse
f
A definition of sequenceA
must satisfy the following laws:
- naturality
t .
for every applicative transformationsequenceA
=sequenceA
.fmap
tt
- identity
sequenceA
.fmap
Identity = Identity- composition
sequenceA
.fmap
Compose = Compose .fmap
sequenceA
.sequenceA
where an applicative transformation is a function
t :: (Applicative f, Applicative g) => f a -> g a
preserving the Applicative
operations, i.e.
and the identity functor Identity
and composition of functors Compose
are defined as
newtype Identity a = Identity a instance Functor Identity where fmap f (Identity x) = Identity (f x) instance Applicative Identity where pure x = Identity x Identity f <*> Identity x = Identity (f x) newtype Compose f g a = Compose (f (g a)) instance (Functor f, Functor g) => Functor (Compose f g) where fmap f (Compose x) = Compose (fmap (fmap f) x) instance (Applicative f, Applicative g) => Applicative (Compose f g) where pure x = Compose (pure (pure x)) Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)
(The naturality law is implied by parametricity.)
Instances are similar to Functor
, e.g. given a data type
data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
a suitable instance would be
instance Traversable Tree where traverse f Empty = pure Empty traverse f (Leaf x) = Leaf <$> f x traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r
This is suitable even for abstract types, as the laws for <*>
imply a form of associativity.
The superclass instances should satisfy the following:
- In the
Functor
instance,fmap
should be equivalent to traversal with the identity applicative functor (fmapDefault
). - In the
Foldable
instance,foldMap
should be equivalent to traversal with a constant applicative functor (foldMapDefault
).
traverse :: Applicative f => (a -> f b) -> t a -> f (t b) #
Map each element of a structure to an action, evaluate these actions
from left to right, and collect the results. For a version that ignores
the results see traverse_
.
sequenceA :: Applicative f => t (f a) -> f (t a) #
Evaluate each action in the structure from left to right, and
and collect the results. For a version that ignores the results
see sequenceA_
.
mapM :: 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. For
a version that ignores the results see mapM_
.
sequence :: Monad m => t (m a) -> m (t a) #
Evaluate each monadic action in the structure from left to
right, and collect the results. For a version that ignores the
results see sequence_
.
for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b) #
Enhanced exports
Simpler name for a typeclassed operation
intercalate :: Monoid w => w -> [w] -> w Source #
intercalate = mconcat .: intersperse
Strict implementation
Text for Read and Show operations
readIO :: (MonadIO m, Read a) => Text -> m a Source #
The readIO function is similar to read except that it signals parse failure to the IO monad instead of terminating the program.
Since: 0.7.0
FilePath for file operations
readFile :: MonadIO m => FilePath -> m Text Source #
Read a file and return the contents of the file as Text. The entire file is read strictly.
Since: 0.7.0
writeFile :: MonadIO m => FilePath -> Text -> m () Source #
Write Text to a file. The file is truncated to zero length before writing begins.
Since: 0.7.0
appendFile :: MonadIO m => FilePath -> Text -> m () Source #
Write Text to the end of a file.
Since: 0.7.0
Text exports
Text operations (Pure)
textToString :: Text -> String Source #
ltextToString :: LText -> String Source #
fpToText :: FilePath -> Text Source #
Deprecated: Use Data.Text.pack
This function assumes file paths are encoded in UTF8. If it
cannot decode the FilePath
, the result is just an approximation.
Since 0.3.13
fpFromText :: Text -> FilePath Source #
Deprecated: Use Data.Text.unpack
Since 0.3.13
fpToString :: FilePath -> String Source #
Deprecated: Use id
Since 0.3.13
encodeUtf8 :: Text -> ByteString #
Encode text using UTF-8 encoding.
decodeUtf8 :: ByteString -> Text Source #
Note that this is not the standard Data.Text.Encoding.decodeUtf8
. That
function will throw impure exceptions on any decoding errors. This function
instead uses decodeLenient
.
Text operations (IO)
getContents :: MonadIO m => m LText Source #
Since: 0.7.0
Miscellaneous prelude re-exports
Math
gcd :: Integral a => a -> a -> a #
is the non-negative factor of both gcd
x yx
and y
of which
every common factor of x
and y
is also a factor; for example
, gcd
4 2 = 2
, gcd
(-4) 6 = 2
= gcd
0 44
.
= gcd
0 00
.
(That is, the common divisor that is "greatest" in the divisibility
preordering.)
Note: Since for signed fixed-width integer types,
,
the result may be negative if one of the arguments is abs
minBound
< 0
(and
necessarily is if the other is minBound
0
or
) for such types.minBound
lcm :: Integral a => a -> a -> a #
is the smallest positive integer that both lcm
x yx
and y
divide.
Show and Read
Conversion of values to readable String
s.
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 thand
(associativity is ignored). Thus, ifd
is0
then the result is never surrounded in parentheses; ifd
is11
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,
produces the stringshow
(Leaf 1 :^: Leaf 2 :^: Leaf 3)"Leaf 1 :^: (Leaf 2 :^: Leaf 3)"
.
showsPrec :: Int -> a -> 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.
utility function converting a Char
to a show function that
simply prepends the character unchanged.
showString :: String -> ShowS #
utility function converting a String
to a show function that
simply prepends the string unchanged.
readsPrec :: Read a => Int -> ReadS a #
attempts to parse a value from the front of the string, returning a list of (parsed value, remaining string) pairs. If there is no successful parse, the returned list is empty.
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.
The lex
function reads a single lexeme from the input, discarding
initial white space, and returning the characters that constitute the
lexeme. If the input string contains only white space, lex
returns a
single successful `lexeme' consisting of the empty string. (Thus
.) If there is no legal lexeme at the
beginning of the input string, lex
"" = [("","")]lex
fails (i.e. returns []
).
This lexer is not completely faithful to the Haskell lexical syntax in the following respects:
- Qualified names are not handled properly
- Octal and hexadecimal numerics are not recognized as a single token
- Comments are not treated properly