basic-prelude-0.3.11: An enhanced core prelude; a common foundation for alternate preludes.

Safe HaskellNone
LanguageHaskell98

BasicPrelude

Contents

Description

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.

Synopsis

Module exports

module Data.List

Enhanced exports

Simpler name for a typeclassed operation

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

map = fmap

empty :: Monoid w => w Source

empty = mempty

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

(++) = mappend

concat :: Monoid w => [w] -> w Source

concat = mconcat

intercalate :: Monoid w => w -> [w] -> w Source

intercalate = mconcat .: intersperse

Strict implementation

sum :: Num a => [a] -> a Source

Compute the sum of a finite list of numbers.

product :: Num a => [a] -> a Source

Compute the product of a finite list of numbers.

Text for Read and Show operations

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

Convert a value to readable Text

read :: Read a => Text -> a Source

Parse Text to a value

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)

lines :: Text -> [Text]

words :: Text -> [Text]

unlines :: [Text] -> Text

unwords :: [Text] -> Text

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

interact :: (Text -> Text) -> IO ()

Miscellaneous prelude re-exports

Math

gcd :: Integral a => a -> a -> a

gcd x y is the non-negative factor of both x 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 4 = 4. gcd 0 0 = 0. (That is, the common divisor that is "greatest" in the divisibility preordering.)

Note: Since for signed fixed-width integer types, abs minBound < 0, the result may be negative if one of the arguments is minBound (and necessarily is if the other is 0 or minBound) for such types.

lcm :: Integral a => a -> a -> a

lcm x y is the smallest positive integer that both x and y divide.

Show and Read

type ShowS = String -> String

The shows functions return a function that prepends the output String to an existing String. This allows constant-time concatenation of results using function composition.

showsPrec

Arguments

:: Show a 
=> 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.

showList :: Show a => [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.

shows :: Show a => a -> ShowS

equivalent to showsPrec with a precedence of 0.

showChar :: Char -> 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.

showParen :: Bool -> ShowS -> ShowS

utility function that surrounds the inner show function with parentheses when the Bool parameter is True.

type ReadS a = String -> [(a, String)]

A parser for a type a, represented as a function that takes a String and returns a list of possible parses as (a,String) pairs.

Note that this kind of backtracking parser is very inefficient; reading a large structure may be quite slow (cf ReadP).

readsPrec

Arguments

:: Read a 
=> Int

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

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

readList :: Read a => ReadS [a]

The method readList is provided to allow the programmer to give a specialised way of parsing lists of values. For example, this is used by the predefined Read instance of the Char type, where values of type String should be are expected to use double quotes, rather than square brackets.

reads :: Read a => ReadS a

equivalent to readsPrec with a precedence of 0.

readParen :: Bool -> ReadS a -> ReadS a

readParen True p parses what p parses, but surrounded with parentheses.

readParen False p parses what p parses, but optionally surrounded with parentheses.

lex :: ReadS String

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 lex "" = [("","")].) If there is no legal lexeme at the beginning of the input string, 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

IO operations

putChar :: Char -> IO ()

Write a character to the standard output device (same as hPutChar stdout).

getChar :: IO Char

Read a character from the standard input device (same as hGetChar stdin).

readLn :: Read a => IO a

The readLn function combines getLine and readIO.