There will be some incompatibilities with Haskell 1.2. These should not be serious and implementors are encouraged to provide a Haskell 1.2 compatibility mode. In brief, the following incompatible changes are being made:
An initial Haskell library report is available at
.
Constructor Classes
We have observed that many programmers use Gofer instead of Haskell
to use Gofer's constructor classes. Since constructor
classes are well understood, widely used, and easily implemented we
have added these to Haskell. Briefly, constructor classes
remove the restriction that types be `first order'. That is, `T
a' is a valid Haskell type, but `t a' is not since
`t' is a type variable.
Constructor classes increase the power of the class system. For
example, this class definition uses constructor classes:
class Monad m where (>>=) :: m a -> (a -> m b) -> m b return :: a -> m aHere, the type variable `m' must be instantiated to a polymorphic data type, as in
instance Monad [] where f >>= g = concat (map g f) return x = [x]No changes to the expression language are necessary; constructor classes are an extension of the type language only.
Constructor classes require an extra level of type information called `kinds'. Before type inference, the compiler must perform kind inference to compute a kinding for each type constructor. Kinds are much simpler than types and are not ordinarily noticed by the programmer.
The changes to Haskell required to support constructor classes are:
x :: C(a b) => a b
The addition of monad syntax should improve the
improve the readability of programs that make heavy use of I/O.
Strictness Annotations
To achieve reasonable efficiency, Haskell programmers often use
implementation-specific annotations to mark fields of data structures as
strict. These strict components are evaluated when the structure is
created instead of delayed until demanded. This avoids the extra
overhead involved with delays and can result in much more compact
structures. To help improve efficiency, we now supply a
simple strictness annotation on the types in a data declaration.
Using `!' in front of a type in a
data declaration marks a structure component as strict. (The `!'
symbol is not a keyword; it has no special meaning outside data
declarations). Only data types may be marked as strict; using
`!' in other type signatures is not allowed. Any or all of the
conponents of a type may be marked as strict.
data Foo a = F Int !Bool a aThis declares F as a constructor containing four fields: a (non-strict) Int, a strict Bool, and two non-strict polymorphic fields.
Fully polymorphic strictness implies that values of any type may be evaluated when placed into a strict data structure. There are compelling arguments for marking operations which use polymorphic strictness. We use a special class, Eval, to explicitly designate the useage of polymorphicly strict operations. Every data type is a member of the Eval class. If we want to make a polymorphic component strict, we must add a "Eval" context to the declaration:
data Eval a => Foo a = F Int !Bool !a a
The libraries will use strictness annotations in the definition of Ratio and Complex, making these numeric types much more efficient. To avoid unnecessary propagation of the Eval class, it is a superclass of Num.
The functions `strict' and `seq' have been added to to give the user additional control over evaluation. While no strictness annotations have been proposed for functions, these primitives can be used to implement strict evaluation when needed.
seq :: Eval a => a -> b -> b strict :: Eval a => (a -> b) -> (a -> b) strict f = \x -> seq x (f x)The seq function evaluates its first argument before returning the second one. strict turns an ordinary function into a strict one.
Strict data constructors accumulate all arguments before evaluating them:
data R = R !Int !Int R x y = seq x (seq y (makeR x y)) -- just to show the semantics of R y = R undefined -- Not an error
All datatypes, including functions, are (implicitly) members of the Eval class. Adding functions to the the Eval class means that all types are in the class. It is tempting then to omit the Eval class altogether and drop the Eval context from seq and strict. We chose not to do so because the context provides useful information. For example, a function of type a -> b is certain to be lazy in its first argument whereas a function of type Eval a => a -> b may be strict in its first argument.
Haskell 1.3 will not provide strictness annotations for functions.
These can be constructed explicitly using seq if needed.
We decided we do not yet know what the best way to handle annotations
for function strictness so (at least for now) these are not ready for
Haskell 1.3.
Labeled Fields
The individual components of data types in Haskell 1.2 are completely
anonymous: the type definition only names the type and the
constructors, not the fields of a constructor. It is inconvenient to
select from, construct, or modify values associated with a constructor
which has many components. A number of more general record structures
have been proposed and implemented. After much discussion, we have
decided to avoid the issues of inheritance or object oriented
programming for the moment and provide a simple syntax which will
allow the fields of a data type to be referred to by name.
We have decided to use the term `field labels' in the Haskell report instead `records'. The terminology used here is not consistant with the report.
Haskell 1.3 provides a special syntax for declaring field names for data types, and for the selection, construction, and update of values with named fields. There are no new types or new semantics; all new constructs have a simple translation to core Haskell. Strictness annotations can be used in the obvious way with the obvious meaning. A small change is required in the definition of import-export lists to accomodate field names.
data List a = Cons {hd::a, tl::List a} | Nil data Tree a = Node {label::a, subtrees :: [Tree a]} data Date = Date {day, month, year :: Int} data NonEmpty a = Head {head :: a} | Cons {head :: a, tail :: NonEmpty a} -- example taken from page 82 of Simon Peyton Jones and David Lester's -- book "Implementing Functional Languages -- A Tutorial" data GMState = GMState { code :: GMCode, stack :: GMStack, heap :: GMHeap, globals :: GMGlobals, stats :: GMStats}Notes:
data F = A {x::Int} | B {x :: Float} -- ILLEGAL data G = C {x::Int, x::Int} -- ILLEGALIt is also be illegal to use the same field name in scope from more than one type.
let list42 = Cons 42 Nil treeabc = Node 'b' [Node 'a' [], Node 'c' []] today = Date 11 10 1995 in show (list, treeabc, today)But, especially for larger records, it may be more convenient or reliable to use the fieldnames:
let today = Date{day = 11, month = 10, year = 1995} other_day = Date{day = 10, month = 11, year = 1995} state = GMState{ code = [], stack = emptyStack, heap = emptyHeap, globals = preludeGlobals, stats = initStats} in show (today, other_day, state)Fields not named during construction are undefined. It is a compile time error to omit a strict field during construction.
Syntacticly, the braces in records bind more tightly than any other operator, including application. Thus, f C {x = 1} is parsed as f (C {x = 1}). We omit the space before `{' to highlight the way this parses: f C{x = 1} .
len :: NonEmpty a -> Int len (Head _) = 1 len (Cons x xs) = 1 + length xs labels (Node l ns) = l : concat (map labels ns) (Date d1 m1 y1) <= (Date d2 m2 y2) = y1 < y2 || (y1 == y2 && (m1 < m2 || (m1 == m2 && d1 <= d2)))But, especially for larger records, it may be more convenient or reliable to use the fieldnames:
showsPrec d (Date{day = d, month = m, year = y}) = shows d . ('/':) . shows m . ('/':) . shows y showsPrec d (GMState{code, stack, heap, globals, stats}) = ('<':) . shows code . (' ':) . shows stack . (' ':) . shows heap . (' ':) . shows globals . (' ':) . shows stats . ('>':)The first example shows how you can bind arbitrary variables to the fields. The second example demonstrates "punning". With punning, the same name is used in two different name spaces. The contents of a field named `f' is associated with a value in variable `f'. If you write field anywhere that field = var is expected, it is treated as an abbreviation for field = field. Thus the example is just an abbreviation of:
showsPrec d (GMState {code=code, stack=stack, heap=heap, globals=globals, stats=stats}) = ('<':) . shows code . (' ':) . shows stack . (' ':) . shows heap . (' ':) . shows globals . (' ':) . shows stats . ('>':)and is equivalent (modulo alpha-conversion) to
showsPrec d (GMState {code=c; stack=s; heap=h; globals=g; stats=s}) = ('<':) . shows c . (' ':) . shows s . (' ':) . shows h . (' ':) . shows g . (' ':) . shows s . ('>':)(We could also have used "punning" in the creation examples; it is used in the same way for record construction but it's probably most useful for pattern matching and updates.)
data Date = Date {day, month, year :: Int}defines the following (global) selector functions:
day, month, year :: Date -> Int day (Date{day = d}) = d month (Date{month = m}) = m year (Date{year = y}) = yIt is a runtime error to select a field from a value which does not have that field (this happens only when the type has more than one constructor).
Note: Since selector functions are just ordinary functions, they can get "shadowed" if you have local variables of the same name. For example, the following has a type error because a local variable "shadows" the global selector function:
daysSinceStart d@(Date {day, month, year) = day + sum [ daysInMonth m | m = [1..month-1] ] where daysInMonth m | m `elem` [9,4,6,11] = 30 daysInMonth 2 | isLeapYear (year d) = 29 -- WRONG: year is shadowed | otherwise = 28 daysInMonth _ = 31The correct (and more obvious!) way to write this example is to use the value "year" from the pattern match rather than using the selector.
Only these selector functions are shadowed: field names used within braces are never shadowed by ordinary variables.
putCode :: GMCode -> GMState -> GMState putCode code' (GMCode {code, stack, heap, globals, stats} = (GMCode {code = code', stack, heap, globals, stats} = putStack :: GMStack -> GMState -> GMState putStack stack' (GMCode {code, stack, heap, globals, stats} = (GMCode {code, stack = stack', heap, globals, stats} = putStats :: GMStats -> GMState -> GMState putStats stats' (GMCode with {code; stack; heap; globals; stats} = (GMCode {code, stack, heap, globals, stats = stats'} =(These are taken from pages 83-85 and adapted to use record pattern matching and construction.)
Using Haskell 1.3's update expressions, these could be rewritten:
putCode :: GMCode -> GMState -> GMState putCode code' s = s{code = code'} putStack :: GMStack -> GMState -> GMState putStack stack' s = s{stack = stack'} putStats :: GMStats -> GMState -> GMState putStats stats' s = s{stats = stats'}or, using puns:
putCode :: GMCode -> GMState -> GMState putCode code s = s{code} putStack :: GMStack -> GMState -> GMState putStack stack s = s {stack} putStats :: GMStats -> GMState -> GMState putStats stats s = s {stats}However, these functions are now so trivial that one wouldn't normally bother to write them - you'd just use update expressions directly in your code. For example, Peyton Jones and Lester define a function to increment a counter by:
doAdmin :: GMState -> GMState doAdmin s = putStats (statIncSteps (getStats s)) swhich can be easily defined using selection and updates by:
doAdmin :: GMState -> GMState doAdmin s = s{stats = statIncSteps (stats s)}or (clumsily) defined using pattern matching and updates
doAdmin :: GMState -> GMState doAdmin s@GMState{stats} = s{stats = statIncSteps stats}
Simultaneous updates are also allowed. For example, if an American had (incorrectly) entered the date "25th January 1996" as "1/25/1996", one could use the following function to fix the record:
fixUSDate :: Date -> Date fixUSDate d = d{day = month d, month = day d}(Obviously, it's a (compile time) error to simultaneously update fields from different constructors; and a (runtime) error to update a field in a value built with a constructor which doesn't have that field.)
show (Date{day = 25, month = 1, year = 1996}) = "Date{day = 25, month = 1, year = 1996}"and will (only!) accept input in the same format.
import Prelude(Maybe)or they can import the datatype and its constructors (allowing construction and pattern matching) by writing:
import Prelude(Maybe(..))which is an abbreviation for:
import Prelude(Maybe(Just,Nothing))The only difference under Haskell 1.3 is that the field names must be listed along with the constructor names in the unabbreviated form:
import Prelude(List(Cons,head,tail,Nil))There is no way to selectively hide field names: they must always accompany their associated constructor.
(All the above examples work for export too - just replace "import" by
"export" throughout.)
Renaming Existing Types
Haskell users have often needed to declare a new name for an existing
type. There were two ways of doing this: declaring a synonym, as in
type Foo = Intor creating a type wrapper, as in
data Foo = Foo IntThis first approach has no runtime overhead, but does not distinguish the new type from the old. More seriously, instances cannot be attached to the new type, only the old one. The other approach incurs an additional overhead in the representation. An additional type declaration will provide a more efficient way of creating a new type from an existing one:
newtype context => simple = con type [deriving classes]Examples:
newtype Foo = Foo Int deriving Show newtype Bar a = Bar [a] deriving (Show,Eq) newtype LongName = L IntThis new type is used in the same manner as a wrapper type and, similarly, the type name need not match the constructor name. The constructor is used for explicit coercion between the new and existing types. Derived instances simply re-use instances already attached to the existing type (except for Read and Show, which use the constructor as it would for a wrapper type).
At first glance, it looks as though the newtype "Foo" could have been defined using normal data types and strictness annotations.
data Foo = Foo !Int deriving ShowThe difference between the two is rather subtle (but important):
case Foo undefined of Foo _ -> True = undefined
case Foo undefined of Foo _ -> True = True
Syntax: Expansion: exp -> do {stmt} stmt -> exp exp stmt -> exp ; stmt exp >> do stmt stmt -> let decls ; stmt let decls in do stmt stmt -> pat <- exp ; stmt <see below>
The Haskell layout rules already allow you to write:
let x = 1 y = 2 in x + yas an abbreviation for:
let { x = 1; y = 2 } in x + yBy the same rules, it is possible to write:
do x <- getInt y <- getInt return (x + y)as an abbreviation for:
do { x <- getInt; y <- getInt; return (x + y) }C programmers might prefer the latter.
As in a list comprehension, variables bound by patterns are scoped over the following statements in the do. The do has the same type as the last statement.
The translation of pat <- exp; stmt depends on the pattern pat.
exp >>= \pat -> do stmtIn fact, this translation is used for any failure-free pattern such as "x", "~(x:xs)", "~(Just 3)". A pattern is failure-free when it is either irrefutable or consists of a constructor from a single-constructor data type applied to failure-free patterns.
For example, do (x,y) <- getPair; return (x+y) is translated to
getPair >>= \(x,y) -> return (x+y)
exp >>= \ x -> case x of { pat -> do stmt; _ -> zero }(where x is free in stmt).
For example, do Just x <- getOpt "x"; foo x is translated to
getOpt >>= \ z -> case z of { Just x -> foo x; _ -> zero }
Note that using this translation results in monad expressions of type MonadZero m => m a instead of Monad m => m a. The above special cases are included to reduce the clutter in IO monad expressions.
A let in a do is scoped over all remaining statements. Note there is no in; this distinguishes this from an ordinary let.
H Haskell 1.3 omits several features from earlier proposals and the Gofer implementation. In particular, there is no support for "guards".
do x <- foo if even x barThe problem is that in some monads, guard failure should yield a zero while in others it should cause an exception or even an error (with an appropriate error message). Fortunately, there's no need to wrestle with these thorny semantic issues since it's trivial for programmers to define and use their own "guard functions".
-- raise an error if condition fails. assert :: Monad m => Bool -> String -> m () assert p msg = if p then return () else error ("Assertion failed: " ++ msg) -- return a zero if condition fails. -- Similar to guards in list comprehensions. guard :: MonadZero m => Bool -> m () guard p = if p then return () else zero do x <- foo assert (even x) "foo didn't return an even result at line 32 of Bar.lhs" y <- bar x guard (x `elem` y) return y
By default, the name of the imported module is used as the qualifier in a qualified name. An import declaration may contain an as clause to specify a different qualifier.
Qualified names are defined in the lexical syntax. Thus, `Foo.a' and `Foo . a' are quite different. No whitespace is permitted in a qualified name. Symbols may also be qualified: `Prelude.+' is an operator which can be used in exactly the same manner as `+'.
Note that the `.' operator presents a syntactic problem. It causes `Foo..', which was used in export lists (this syntax has changed) and occasionally in arithmetic sequences, to parse as a qualified name instead of a usage of the `..' token. Inserting a space before the `..' will resolve this problem.
Qualifiers are prohibited in definitions:
M.x = 1is not allowed. In all other contexts, names may be qualified. It is an error to export more than one entity with the same name:
module M3(M1.x,M2.x) where -- an error import qualified M1(x) import qualified M2(x)
Although as appears in the syntax for imports, it is not
treated as a keyword in other contexts.
Redefinable Names
A complaint about Haskell has been that names defined in
PreludeCore cannot be redefined in any way. Since many operators,
like +, -, >, and ==, are defined in PreludeCore this has made some
users deeply unhappy -- this restriction prevents any sort of
alternative numeric class structure which uses the standard symbols, for example.
There is no real reason for stealing all these names from the user; in
Haskell 1.3 PreludeCore is no longer special: all ordinary names are
redefinable. Special syntax will remain attached to Prelude names;
thus `[x]' would always refer to lists as defined in the Prelude.
As before, the Prelude module is implicitly
imported (in unqualified form) unless an explicit import is found.
There is also an implicit (and unavoidable) qualified import of the
Prelude which is used to define the meaning of various pieces of
syntactic sugar. This eliminates the need to make PreludeCore symbols
immutable.
Since qualified names can always be used for imported entities,
any Prelude entities that the programmer has chosen to shadow
can still be referred to using
`Prelude.'.
Unfortunately, while Prelude names are redefinable, translations of special syntax yield fixed definitions in the Prleude. Although subtraction (-) can be redefined, negation is a special syntax and always refers to the negate defined in the Prelude. Similarly, numeric constants have an implicit fromInteger / fromRational. This implicit function is always as defined in the Prelude even when fromInteger is redefined.
The visibility of instance declarations presents a problem. Unlike classes or types, instances cannot be mentioned explicitly in export lists. Instead of changing the syntax of the export list, we have adopted a simple rule: all instances are exported regardless of the export list. All imports bring in the full set of instances from the imported module. An instance is in scope when a chainof import statements leads to the module defining the instance.
f x y = if f True False then x else ythe type of f would normally be inferred as `Bool -> Bool -> Bool'. However, polymorphic recursion allows the user to add a type signature to f such as `f :: a -> a -> a' to give it a more general type. While polymorphic recursion is not likely to be needed by the average Haskell user, it occasionally will prevent the type checker from complaining about a quite sensible looking program.
qual -> let {decls}(The absence of `in' distinguishes this from a "let"-expression in a guard). These decls are scoped over the remaining qualifiers and the generated expression. Binding is irrefutable: pattern match failure is a program error. The expansion of this is trivial: it expands directly into a conventional let.
n+k patterns are still present, but their use is oficially discouraged.