{-# LANGUAGE PackageImports, NoImplicitPrelude #-} module Prelude ( -- * Standard types, classes and related functions -- ** Basic data types Bool(False, True), (&&), (||), not, otherwise, Maybe(Nothing, Just), maybe, Either(Left, Right), either, Ordering(LT, EQ, GT), Char, String, -- *** Tuples fst, snd, curry, uncurry, -- ** Basic type classes -- removed: Eq((==), (/=)), (==), (/=), -- removed: Ord(compare, (<), (<=), (>=), (>), max, min), compare, (<), (<=), (>=), (>), max, min, Enum(succ, pred, toEnum, fromEnum, enumFrom, enumFromThen, enumFromTo, enumFromThenTo), Bounded(minBound, maxBound), -- ** Numbers -- *** Numeric types -- removed: Int, Integer, Float, Double, -- removed: Rational, Integer, -- *** Numeric type classes -- removed: Num((+), (-), (*), negate, abs, signum, fromInteger), (+), (-), (*), negate, abs, signum, fromInteger, -- removed: Real(toRational), -- removed: Integral(quot, rem, div, mod, quotRem, divMod, toInteger), quot, rem, div, mod, quotRem, divMod, toInteger, -- removed: Fractional((/), recip, fromRational), -- removed: Floating(pi, exp, log, sqrt, (**), logBase, sin, cos, tan, -- removed: asin, acos, atan, sinh, cosh, tanh, asinh, acosh, atanh), -- removed: RealFrac(properFraction, truncate, round, ceiling, floor), -- removed: RealFloat(floatRadix, floatDigits, floatRange, decodeFloat, -- removed: encodeFloat, exponent, significand, scaleFloat, isNaN, -- removed: isInfinite, isDenormalized, isIEEE, isNegativeZero, atan2), -- *** Numeric functions subtract, even, odd, gcd, lcm, (^), fromIntegral, -- removed: realToFrac, (^^), -- ** Monads and functors Monad((>>=), (>>), return, fail), Functor(fmap), mapM, mapM_, sequence, sequence_, (=<<), -- ** Miscellaneous functions id, const, (.), flip, ($), until, asTypeOf, error, undefined, seq, ($!), -- * List operations map, (++), filter, head, last, tail, init, null, length, (!!), reverse, -- ** Reducing lists (folds) foldl, foldl1, foldr, foldr1, -- *** Special folds and, or, any, all, sum, product, concat, concatMap, maximum, minimum, -- ** Building lists -- *** Scans scanl, scanl1, scanr, scanr1, -- *** Infinite lists iterate, repeat, replicate, cycle, -- ** Sublists take, drop, splitAt, takeWhile, dropWhile, span, break, -- ** Searching lists elem, notElem, lookup, -- ** Zipping and unzipping lists zip, zip3, zipWith, zipWith3, unzip, unzip3, -- ** Functions on strings lines, words, unlines, unwords, -- * Converting to and from @String@ -- ** Converting to @String@ ShowS, Show(showsPrec, showList, show), shows, showChar, showString, showParen, -- ** Converting from @String@ ReadS, Read(readsPrec, readList), reads, readParen, read, lex, -- * Basic Input and output IO, -- ** Simple I\/O operations -- All I/O functions defined here are character oriented. The -- treatment of the newline character will vary on different systems. -- For example, two characters of input, return and linefeed, may -- read as a single newline character. These functions cannot be -- used portably for binary I/O. -- *** Output functions putChar, putStr, putStrLn, print, -- *** Input functions getChar, getLine, getContents, interact, -- *** Files FilePath, readFile, writeFile, appendFile, readIO, readLn, -- ** Exception handling in the I\/O monad IOError, ioError, userError, catch ) where import "base" Prelude hiding ( Num(..), Integral(..), subtract, even , odd, gcd, lcm, (^) , length, (!!), sum, product , take, drop , Ord(..), Eq(..) ) import qualified "base" Prelude as P import qualified Data.List as L -- ------- -- - Num - -- ------- (+), (-), (*) :: Integer -> Integer -> Integer (+) = (P.+) (-) = (P.-) (*) = (P.*) negate, abs, signum, fromInteger :: Integer -> Integer negate = P.negate abs = P.abs signum = P.signum fromInteger = P.fromInteger -- ------------ -- - Integral - -- ------------ quot, rem, div, mod :: Integer -> Integer -> Integer quot = P.quot rem = P.rem div = P.div mod = P.mod quotRem, divMod :: Integer -> Integer -> (Integer, Integer) quotRem = P.quotRem divMod = P.divMod toInteger :: Integer -> Integer toInteger = P.toInteger -- --------------------- -- - numeric functions - -- --------------------- subtract, gcd, lcm, (^) :: Integer -> Integer -> Integer subtract = P.subtract gcd = P.gcd lcm = P.lcm (^) = (P.^) even, odd :: Integer -> Bool even = P.even odd = P.odd -- ------------------ -- - list functions - -- ------------------ length :: [a] -> Integer length = L.genericLength (!!) :: [a] -> Integer -> a (!!) = L.genericIndex sum, product :: [Integer] -> Integer sum = P.sum product = P.product take, drop :: Integer -> [a] -> [a] take = L.genericTake drop = L.genericDrop -- ------- -- - Ord - -- ------- compare :: Integer -> Integer -> Ordering compare = P.compare (<), (<=), (>=), (>) :: Integer -> Integer -> Bool (<) = (P.<) (<=) = (P.<=) (>=) = (P.>=) (>) = (P.>) max, min :: Integer -> Integer -> Integer max = P.max min = P.min -- ------ -- - Eq - -- ------ (==), (/=) :: Integer -> Integer -> Bool (==) = (P.==) (/=) = (P./=)