Safe Haskell | None |
---|---|
Language | Haskell98 |
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, Eq a) => a -> t a -> Bool
- maximum :: (Foldable t, Ord a) => t a -> a
- minimum :: (Foldable t, Ord a) => t a -> a
- class (Functor t, Foldable t) => Traversable t where
- traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
- sequenceA :: Applicative f => t (f a) -> f (t a)
- mapM :: Monad m => (a -> m b) -> t a -> m (t b)
- sequence :: Monad m => t (m a) -> m (t a)
- 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 :: Num a => [a] -> a
- product :: Num a => [a] -> a
- show :: Show a => a -> Text
- fromShow :: (Show a, IsString b) => a -> b
- read :: Read a => Text -> a
- readIO :: Read a => Text -> IO a
- readFile :: FilePath -> IO Text
- writeFile :: FilePath -> Text -> IO ()
- appendFile :: FilePath -> Text -> IO ()
- 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 :: IO Text
- getContents :: IO Text
- interact :: (Text -> Text) -> IO ()
- gcd :: Integral a => a -> a -> a
- lcm :: Integral a => a -> a -> a
- type ShowS = String -> String
- showsPrec :: Show a => Int -> a -> ShowS
- showList :: Show a => [a] -> ShowS
- 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
- putChar :: Char -> IO ()
- getChar :: IO Char
- readLn :: Read a => IO a
Module exports
module CorePrelude
module Data.List
module Control.Monad
Folds and traversals
class Foldable t where
Data structures that can be folded.
Minimal complete definition: foldMap
or foldr
.
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
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
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
foldl' :: (b -> a -> b) -> b -> t a -> b
Left-associative fold of a structure. but with strict application of the operator.
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
Foldable [] | |
Foldable Maybe | |
Foldable Digit | |
Foldable Node | |
Foldable Elem | |
Foldable FingerTree | |
Foldable IntMap | |
Foldable Set | |
Foldable Seq | |
Foldable ViewL | |
Foldable ViewR | |
Foldable Identity | |
Foldable HashSet | |
Foldable Vector | |
Foldable (Either a) | |
Foldable ((,) a) | |
Ix i => Foldable (Array i) | |
Foldable (Const m) | |
Foldable (Proxy *) | |
Foldable (Map k) | |
Foldable f => Foldable (MaybeT f) | |
Foldable f => Foldable (ListT f) | |
Foldable f => Foldable (IdentityT f) | |
Foldable (HashMap k) | |
Foldable f => Foldable (WriterT w f) | |
Foldable f => Foldable (WriterT w f) | |
Foldable f => Foldable (ErrorT e f) | |
Foldable f => Foldable (ExceptT e f) |
class (Functor t, Foldable t) => Traversable t where
Functors representing data structures that can be traversed from left to right.
Minimal complete definition: traverse
or sequenceA
.
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 Indentity 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.
sequenceA :: Applicative f => t (f a) -> f (t a)
Evaluate each action in the structure from left to right, and collect the results.
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.
sequence :: Monad m => t (m a) -> m (t a)
Evaluate each monadic action in the structure from left to right, and collect the results.
Traversable [] | |
Traversable Maybe | |
Traversable Digit | |
Traversable Node | |
Traversable Elem | |
Traversable FingerTree | |
Traversable IntMap | |
Traversable Seq | |
Traversable ViewL | |
Traversable ViewR | |
Traversable Identity | |
Traversable Vector | |
Traversable (Either a) | |
Traversable ((,) a) | |
Ix i => Traversable (Array i) | |
Traversable (Const m) | |
Traversable (Proxy *) | |
Traversable (Map k) | |
Traversable f => Traversable (MaybeT f) | |
Traversable f => Traversable (ListT f) | |
Traversable f => Traversable (IdentityT f) | |
Traversable (HashMap k) | |
Traversable f => Traversable (WriterT w f) | |
Traversable f => Traversable (WriterT w f) | |
Traversable f => Traversable (ErrorT e f) | |
Traversable f => Traversable (ExceptT e f) |
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 :: Read a => Text -> IO a Source
The readIO function is similar to read except that it signals parse failure to the IO monad instead of terminating the program.
FilePath for file operations
readFile :: FilePath -> IO Text Source
Read a file and return the contents of the file as Text. The entire file is read strictly.
writeFile :: FilePath -> Text -> IO () Source
Write Text to a file. The file is truncated to zero length before writing begins.
appendFile :: FilePath -> Text -> IO () Source
Write Text to the end of a file.
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 :: IO Text
Lazily read all user input on stdin
as a single string.
interact :: (Text -> Text) -> IO ()
The interact
function takes a function of type Text -> Text
as its argument. The entire input from the standard input device is
passed (lazily) to this function as its argument, and the resulting
string is output on the standard output device.
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
Show and Read
:: Show a | |
=> Int | the operator precedence of the enclosing
context (a number from |
-> a | the value to be converted to a |
-> ShowS |
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.
:: Read a | |
=> Int | the operator precedence of the enclosing
context (a number from |
-> 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