Chapter 5. Hugs vs Haskell 98 and addenda

In +98 mode, Hugs supports Haskell 98 and some standardized extensions (described by addenda to the Haskell 98 report).

5.1. Haskell 98 non-compliance

Hugs deviates from Haskell 98 in a few minor ways, listed here corresponding to the relevant sections of the Report.

5.1.1. Lexical structure

Restricted character set

The Haskell report specifies that programs may be written using Unicode. Hugs permits Unicode in strings and comments (in the appropriate locale, see Section 3.3), but identifiers are limited to the ISO8859-1 (Latin-1) subset at the moment.

Limited lookahead

Hugs is confused by such things as "Just.if", "0xy", "0oy", "9e+y" and "9.0e+y", because it doesn't look far enough ahead.

5.1.2. Expressions

Interaction of fixities with the let/lambda meta-rule

Hugs doesn't use the fixity of operators until after parsing, and so fails to accept legal (but weird) Haskell 98 expressions like

let x = True in x == x == True

Restricted syntax for left sections

In Hugs, the expression must be an fexp (or case or do). Legal expressions like (a+b+) and (a*b+) are rejected.

5.1.3. Declarations and bindings

Slight relaxation of polymorphic recursion

Hugs's treatment of polymorphic recursion is less restrictive than Haskell 98 when the functions involved are mutually recursive. Consider the following example:

data BalancedTree a = Zero a | Succ (BalancedTree (a,a))

zig :: BalancedTree a -> a
zig (Zero a) = a
zig (Succ t) = fst (zag t)

zag (Zero a) = a
zag (Succ t) = snd (zig t)
As with many operations on non-regular (or nested) types, zig and zag need to be polymorphic in the element type. In Haskell 98, the bindings of the two functions are interdependent, and thus constitute a single binding group. When type inference is performed on this group, zig may be used at different types, because it has a user-supplied polymorphic signature. However, zag may not, and the example is rejected, unless we add an explicit type signature for zag. (It could be argued that this is a bug in Haskell 98.)

In Hugs, the binding of zig depends on that of zag, but not vice versa. (The binding of zag is considered to depend only on the explicit signature of zig.) It is possible to infer a polymorphic type for zag, and from that for zig. This type matches the declared signature, so Hugs accepts this example.

Relaxation of type classes

Contrary to the the Report (4.3.1), Hugs allows the types of the member functions of a class C a to impose further constraints on a, as in

class Foo a where
    op :: Num a => a -> a -> a

Different implementation of the monomorphism restriction for top-level bindings

For example, Hugs rejects the following example from the Haskell 98 Report, 4.5.5:

module M where
import List
len1 = genericLength "Hello"
len2 = (2*len1) :: Rational
This module consists of two binding groups, containing len1 and len2 respectively. Type inference on the first (len1) triggers the monomorphism restriction, so that len1 is assigned the monomorphic type (Num a => a). The next step differs between Haskell 98 and Hugs:

  • In Haskell 98, type inference is then performed on len2, resolving the type variable a to Rational, and the module is legal.

  • In Hugs, the defaulting rule is applied to len1, instantiating the type variable a to Integer. Then type inference on len2 fails.

5.1.4. Modules

Implicit module header

In Haskell 98, if the module header is omitted, it defaults to "module Main(main) where". In Hugs it defaults to "module Main where", because many people test small modules without module headers.

Implicit export list

In Haskell 98, a missing export list means all names defined in the current module. In Hugs, it is treated as "(module M)", where M is the current module. This is almost the same, differing only when an imported module is aliased as M.

Type synonyms in export and import lists

Hugs allows the T(..) syntax for type synonyms in export and import lists. It also allows the form T() for type synonyms in import lists.

Mutually recursive modules are not supported

Note that although the Haskell 98 specification of the Prelude and library modules is recursive, Hugs achieves the same effect by putting most of these definitions in a module Hugs.Prelude that these modules import.

Weird treatment of (:)

The Hugs prelude exports (:) as if it were an identifier, even though this is not permitted in user-defined modules. This means that Hugs incorrectly rejects the following:

module Foo where
import Prelude()
cs = 'a':cs

5.1.5. Predefined types and classes

Rational literals lose precision

In Haskell 98, a floating point literal like 1.234e-5 stands for "fromRational (1234 % 100000000)". In particular, if the literal is of Rational type, the fraction is exact. In Hugs such literals are stored as double precision floating point numbers before being converted to the appropriate type. If the literal is of Rational type, it usually denotes the same number, but some precision may be lost.

Floating point values are printed differently

Haskell 98 specifies that show for floating point numbers is the function Numeric.showFloat, but Hugs uses an internal function with slightly different semantics.

Derived instances for large tuples are not supplied

In Haskell 98, all tuple types are instances of Eq, Ord, Bounded, Read, and Show if all their component types are. Hugs defines these instances only for tuple types of size 5 or less (3 or less in the small Hugs configuration).

File locking

Hugs does not attempt attempt to enforce the multiple-reader single-writer locking on files required by Haskell 98. Thus under Hugs programs that read and write the same file at the same time may see an inconsistent state, and programs that write to the same file more than once may produce corrupt output. Under Haskell 98, both kinds of program would fail at runtime.

5.1.6. Other bugs in Hugs

Here are other known bugs in Hugs, in addition to the deviations listed above. If you find a bug that is not listed here, please report it either by using the bug tracking system on the Hugs development page or by sending email to hugs-bugs@haskell.org.

Crashes on some infinite computations

Normally, an infinite computation will either exhaust the Hugs heap:

ERROR - Garbage collection fails to reclaim sufficient space
overflow the Hugs stack:
ERROR - Control stack overflow
or just run indefinitely. Occasionally, depending on the relative sizes of your heap, Hugs stack and C stack, such expressions can overflow the C stack before exhausting the other two. On Unix, this usually causes a segmentation fault and causes Hugs to abort.

Space leaks from top-level pattern bindings

This expression runs in constant space

mapM_ putStrLn (repeat "y")
but this program does not:
main = mapM_ putStrLn (repeat "y")
This is caused by CAF-leaks — a long-standing problem for Haskell implementations. The problem is that main (a Constant Applicative Form) is being updated with an expression of the form:
putChar 'y' >> putChar '\n' >> mapM_ putStrLn (repeat "y")
and so on. In the former case the outer putChar expressions become garbage after use, but now they are referenced by main. Some day, we hope to fix this by using a smarter garbage collector. In the meantime, you can avoid the problem by making the troublesome CAFs non-updatable. For example, you could rewrite main as the more convoluted:
main = return () >>= \ _ -> mapM_ putStrLn (repeat "y")
Because the problematic expression is now inside a lambda that is not reduced, its expansion will not be reachable from main, and will thus be garbage-collected as before.