data Maybe a = Nothing | Just a deriving (Eq, Ord, Read, Show) data Either a b = Left a | Right b deriving (Eq, Ord, Read, Show) data Void -- No constructor, not in any classes
if x == y then ... else if x < y then ... else ...Even a standard two way branch can be inefficient - here's the default definition of "<" in the standard prelude:
x < y = x <= y && x /= yInstead of defining a <= operator which returns just two values, it is almost as easy to define an operator which returns three different values:
case compare x y of EQ -> ... LT -> ... GT -> ...The constructors EQ , LT ,and GT belong to a new type: Ordering. In addition to this efficiency problem, many uses of Ord such as sorting or operations on ordered binary trees assume total ordering. The compare operation formalizes this concept: it can not return a value which indicates that its arguments are unordered. Programmers are free to define a class for partial orderings; here, we simply state that Ord is reserved for total orderings.
Proposed Changes:
data Ordering = LT | EQ | GT deriving (Eq,Ord,Ix,Enum,Read, Show)
class Eq a => Ord a where compare :: a -> a -> Ordering (<), (<=), (>=), (>):: a -> a -> Bool max, min :: a -> a -> a -- circular default definition: -- either <= or compare must be explicitly provided x < y = compare x y == LT x <= y = compare x y /= GT x > y = compare x y == GT x >= y = compare x y /= LT compare x y | x == y = EQ | x <= y = LT | otherwise = GT max x y = case compare x y of LT -> x _ -> y min x y = case compare x y of LT -> y _ -> x
Proposed changes:
toEnum :: Int -> a fromEnum :: a -> IntInformally, given an enumeration:
data T = C0 | C1 | ... Cmwe have:
toEnum i | 0 <= i && i <= m = Ci | otherwise = error "Prelude.toEnum: result out of range" fromEnum Ci = iFor example, given the datatype:
data Colour = Red | Orange | Yellow | Green | Blue | Indigo | Violetwe would have:
toEnum 0 = Red toEnum 1 = Orange ... toEnum 6 = Violet toEnum _ = error "Prelude.toEnum: result out of range"and
fromEnum Red = 0 fromEnum Orange = 1 ... fromEnum Violet = 6
succ, pred :: Enum a => a -> a succ = toEnum . (+1) . fromEnum pred = toEnum . (+(-1)) . fromEnum
toEnum :: Integer -> a fromEnum :: a -> IntegerThis would allow correct operation across the full range of integers, floats and doubles - but it's not clear that that is useful or necessary. The fact that toNum and fromEnum will fail in some instances doesn't bother us.
[True..] = True : error "succ{Prelude}: result out of range" [maxChar..] = maxChar : error "succ{Prelude}: result out of range"This problem is present in Haskell 1.2 for the types Int, Float and Double where it doesn't seem to be troubling anyone.
Whereas changing the strictness of lists or integers would break many programs, only the most contrived programs will be affected by this change.
Proposed changes:
data (RealFloat a) => Complex a = !a :+ !a deriving (Eq, Binary, Read, Show) data (Integral a) => Ratio a = !a :% !a deriving (Eq, Binary)
head (take (toInteger maxInt * 2) [1..]) == 1
Proposed changes:
take, drop :: Int -> [b] -> [b] splitAt :: Int -> [b] -> ([b]. [b]) !! :: [a] -> Int -> a
Proposed Changes:
replicate :: Int -> a -> [a] replicate n x = take n . repeat x lookup :: Eq a => a -> [(a,b)] -> Maybe b lookup key [] = Nothing lookup key ((x,y):xys) | key == x = Just y | otherwise = lookup key xys
curry :: ((a, b) -> c) -> a -> b -> c curry f x y = f (x,y) uncurry :: (a -> b -> c) -> (a, b) -> c uncurry f p = f (fst p) (snd p)
In previous discussion, the name assoc was preferred to lookup to avoid stealing a useful name from the user. The library proposal also defines LibFiniteMap.lookup and LibHashTable.lookup - we feel that stealing the one name for three purposes is reasonable.
uncurry f (x, y) = f x yWhich is slightly stricter. Does this matter?
It is possible to have our cake and eat it by simply moving rarely used functions into standard libraries (the language size remains the same but the "core language" gets smaller).
The following changes are based on counting how many times certain functions are used in a large body of Haskell programs (i.e. the Glasgow Haskell repository).
Many functions have been moved: see the new prelude to find out what
remains.
The Bounded class
Add the class
class Bounded a where
minBound, maxBound :: a
This class provides a convenient name for the minimum and maximum
values in a type. Instances for Int and Char
replace maxInt, minInt, maxChar,
minChar. No instance will be defined for floats since it's
not obvious whether to use infinity or the greatest finite value.
Bounded is intended for carrying the range in enumerated classes or
for verifying maps from Integers onto a type.
The bounded
class will be derivable for enumerations and tuples only. Note these
class methods take no argument: you use
minBound :: Char instead of minBound 'x'. This is
inconsistant with the treatment of class-wide parameters (for example,
floatRadix) elsewhere but seems to be a cleaner design.
Numeric Issues
Haskell 1.2 provides no way to detect IEEE arithmetic values
such as "NaN" or "Infinity".
This seemed reasonable since Haskell 1.2 (and 1.3) doesn't
require IEEE arithmetic.
Providing everything numerical analysts could ask for requires a large amount of work, especially since the basic operations do not fit into the existing numeric classes (Num, Ord, ...). We are planning to create a library which will provide strict LIA conformance. However, a few simple additions to the numerics will make it possible to take advantage of some features of IEEE floating point operations.
Proposed Changes:
isNaN, isInfinite, isDenormalized, isIEEE, isNegativeZero :: RealFloat a => a -> BoolIn non-IEEE implementations, these all return False. In IEEE implementations, isIEEE returns True and all others return appropriate responses.
showFloat x = if isNaN x then showString "<<NaN>>" else if isInfinite x then if x < 0 then showString "<<-Infinity>>" else showString "<<Infinity>>" else if isNegativeZero x then showString ("-0." ++ take (m-2) (repeat '0') else if x == 0 then then showString ("0." ++ take (m-1) (repeat '0')) else if e >= m-1 || e < 0 then showSci else showFix where -- remainder of function is unchanged
read "2" :: Doublecauses a run-time error; with the new prelude, the result is just 2.0 :: Double.
Proposed Changes:
readsPrec d r = readCon K1 k1 "K1" r ++ readCon K2 k2 "K2" r ++ ... readCon Km km "Km" rIn order to successfully parse a string starting with "Km", readsPrec will call the lex function m times. If lex were separated from read by preprocessing the input into a token stream, lex would only have to be called once.
undefined = error "undefined{Prelude}"It is expected that compilers will recognize this and insert error messages which are more appropriate to the context in which undefined appears.
Proposed Changes: Add these classes to Prelude:
infixr 1 >>, >>= class Functor where map :: (a -> b) -> m a -> m b class Monad m where (>>=) :: m a -> (a -> m b) -> m b (>>) :: m a -> m b -> m b return :: a -> m a class Monad m => MonadZero m where zero :: m a class MonadZero m => MonadPlus m where (++) :: m a -> m a -> m awith Monad instances for [], Maybe, and IO; MonadZero and MonadPlus instances for [] and Maybe.
maximum [] = error "maximum{PreludeList}: empty list" maximum l = foldl1 max l minimum [] = error "minimum{PreludeList}: empty list" minimum l = foldl1 min lThe error messages for head, tail, init and last use "[]" in their error messages; these will be changed to "empty list" for consistency.
take _ _ = error "take{PreludeList}: negative argument" drop _ _ = error "drop{PreludeList}: negative argument" splitAt _ _ = error "splitAt{PreludeList}: negative argument"
maximum [] = error "PreludeList.maximum: empty list"