Chapter 13. Known bugs and infelicities

Table of Contents

13.1. Haskell standards vs. Glasgow Haskell: language non-compliance
13.1.1. Divergence from Haskell 98 and Haskell 2010
13.1.1.1. Lexical syntax
13.1.1.2. Context-free syntax
13.1.1.3. Expressions and patterns
13.1.1.4. Declarations and bindings
13.1.1.5. Module system and interface files
13.1.1.6. Numbers, basic types, and built-in classes
13.1.1.7. In Prelude support
13.1.1.8. The Foreign Function Interface
13.1.2. GHC's interpretation of undefined behaviour in Haskell 98 and Haskell 2010
13.2. Known bugs or infelicities
13.2.1. Bugs in GHC
13.2.2. Bugs in GHCi (the interactive GHC)

13.1. Haskell standards vs. Glasgow Haskell: language non-compliance

This section lists Glasgow Haskell infelicities in its implementation of Haskell 98 and Haskell 2010. See also the “when things go wrong” section (Chapter 10, What to do when something goes wrong) for information about crashes, space leaks, and other undesirable phenomena.

The limitations here are listed in Haskell Report order (roughly).

13.1.1. Divergence from Haskell 98 and Haskell 2010

By default, GHC mainly aims to behave (mostly) like a Haskell 2010 compiler, although you can tell it to try to behave like a particular version of the language with the -XHaskell98 and -XHaskell2010 flags. The known deviations from the standards are described below. Unless otherwise stated, the deviation applies in Haskell 98, Haskell 2010 and the default modes.

13.1.1.1. Lexical syntax

  • Certain lexical rules regarding qualified identifiers are slightly different in GHC compared to the Haskell report. When you have module.reservedop, such as M.\, GHC will interpret it as a single qualified operator rather than the two lexemes M and .\.

13.1.1.2. Context-free syntax

  • In Haskell 98 mode and by default (but not in Haskell 2010 mode), GHC is a little less strict about the layout rule when used in do expressions. Specifically, the restriction that "a nested context must be indented further to the right than the enclosing context" is relaxed to allow the nested context to be at the same level as the enclosing context, if the enclosing context is a do expression.

    For example, the following code is accepted by GHC:

    main = do args <- getArgs
              if null args then return [] else do
              ps <- mapM process args
              mapM print ps

    This behaviour is controlled by the NondecreasingIndentation extension.

  • GHC doesn't do the fixity resolution in expressions during parsing as required by Haskell 98 (but not by Haskell 2010). For example, according to the Haskell 98 report, the following expression is legal:

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

    and parses as:

        (let x = 42 in x == 42) == True

    because according to the report, the let expression extends as far to the right as possible. Since it can't extend past the second equals sign without causing a parse error (== is non-fix), the let-expression must terminate there. GHC simply gobbles up the whole expression, parsing like this:

        (let x = 42 in x == 42 == True)

13.1.1.3. Expressions and patterns

In its default mode, GHC makes some programs slightly more defined than they should be. For example, consider

f :: [a] -> b -> b
f [] = error "urk"
f (x:xs) = \v -> v

main = print (f [] `seq` True)
    

This should call error but actually prints True. Reason: GHC eta-expands f to

f :: [a] -> b -> b
f []     v = error "urk"
f (x:xs) v = v
    

This improves efficiency slightly but significantly for most programs, and is bad for only a few. To suppress this bogus "optimisation" use -fpedantic-bottoms.

13.1.1.4. Declarations and bindings

In its default mode, GHC does not accept datatype contexts, as it has been decided to remove them from the next version of the language standard. This behaviour can be controlled with the DatatypeContexts extension. See Section 7.4.2, “Data type contexts”.

13.1.1.5. Module system and interface files

GHC requires the use of hs-boot files to cut the recursive loops among mutually recursive modules as described in Section 4.7.9, “How to compile mutually recursive modules”. This more of an infelicity than a bug: the Haskell Report says (Section 5.7) "Depending on the Haskell implementation used, separate compilation of mutually recursive modules may require that imported modules contain additional information so that they may be referenced before they are compiled. Explicit type signatures for all exported values may be necessary to deal with mutual recursion. The precise details of separate compilation are not defined by this Report."

13.1.1.6. Numbers, basic types, and built-in classes

Num superclasses

The Num class does not have Show or Eq superclasses.

You can make code that works with both Haskell98/Haskell2010 and GHC by:

  • Whenever you make a Num instance of a type, also make Show and Eq instances, and

  • Whenever you give a function, instance or class a Num t constraint, also give it Show t and Eq t constraints.

Bits superclasses

The Bits class does not have a Num superclasses. It therefore does not have default methods for the bit, testBit and popCount methods.

You can make code that works with both Haskell2010 and GHC by:

  • Whenever you make a Bits instance of a type, also make a Num instance, and

  • Whenever you give a function, instance or class a Bits t constraint, also give it a Num t constraint, and

  • Always define the bit, testBit and popCount methods in Bits instances.

Extra instances

The following extra instances are defined:

instance Functor ((->) r)
instance Monad ((->) r)
instance Functor ((,) a)
instance Functor (Either a)
instance Monad (Either e)
Multiply-defined array elements—not checked:

This code fragment should elicit a fatal error, but it does not:

main = print (array (1,1) [(1,2), (1,3)])

GHC's implementation of array takes the value of an array slot from the last (index,value) pair in the list, and does no checking for duplicates. The reason for this is efficiency, pure and simple.

13.1.1.7. In Prelude support

Arbitrary-sized tuples

Tuples are currently limited to size 100. HOWEVER: standard instances for tuples (Eq, Ord, Bounded, Ix Read, and Show) are available only up to 16-tuples.

This limitation is easily subvertible, so please ask if you get stuck on it.

splitAt semantics
Reading integers

GHC's implementation of the Read class for integral types accepts hexadecimal and octal literals (the code in the Haskell 98 report doesn't). So, for example,

read "0xf00" :: Int

works in GHC.

A possible reason for this is that readLitChar accepts hex and octal escapes, so it seems inconsistent not to do so for integers too.

isAlpha

The Haskell 98 definition of isAlpha is:

isAlpha c = isUpper c || isLower c

GHC's implementation diverges from the Haskell 98 definition in the sense that Unicode alphabetic characters which are neither upper nor lower case will still be identified as alphabetic by isAlpha.

hGetContents

Lazy I/O throws an exception if an error is encountered, in contrast to the Haskell 98 spec which requires that errors are discarded (see Section 21.2.2 of the Haskell 98 report). The exception thrown is the usual IO exception that would be thrown if the failing IO operation was performed in the IO monad, and can be caught by System.IO.Error.catch or Control.Exception.catch.

13.1.1.8. The Foreign Function Interface

hs_init() not allowed after hs_exit()

The FFI spec requires the implementation to support re-initialising itself after being shut down with hs_exit(), but GHC does not currently support that.

13.1.2. GHC's interpretation of undefined behaviour in Haskell 98 and Haskell 2010

This section documents GHC's take on various issues that are left undefined or implementation specific in Haskell 98.

The Char type

Following the ISO-10646 standard, maxBound :: Char in GHC is 0x10FFFF.

Sized integral types

In GHC the Int type follows the size of an address on the host architecture; in other words it holds 32 bits on a 32-bit machine, and 64-bits on a 64-bit machine.

Arithmetic on Int is unchecked for overflow, so all operations on Int happen modulo 2n where n is the size in bits of the Int type.

The fromInteger function (and hence also fromIntegral) is a special case when converting to Int. The value of fromIntegral x :: Int is given by taking the lower n bits of (abs x), multiplied by the sign of x (in 2's complement n-bit arithmetic). This behaviour was chosen so that for example writing 0xffffffff :: Int preserves the bit-pattern in the resulting Int.

Negative literals, such as -3, are specified by (a careful reading of) the Haskell Report as meaning Prelude.negate (Prelude.fromInteger 3). So -2147483648 means negate (fromInteger 2147483648). Since fromInteger takes the lower 32 bits of the representation, fromInteger (2147483648::Integer), computed at type Int is -2147483648::Int. The negate operation then overflows, but it is unchecked, so negate (-2147483648::Int) is just -2147483648. In short, one can write minBound::Int as a literal with the expected meaning (but that is not in general guaranteed).

The fromIntegral function also preserves bit-patterns when converting between the sized integral types (Int8, Int16, Int32, Int64 and the unsigned Word variants), see the modules Data.Int and Data.Word in the library documentation.

Unchecked float arithmetic

Operations on Float and Double numbers are unchecked for overflow, underflow, and other sad occurrences. (note, however, that some architectures trap floating-point overflow and loss-of-precision and report a floating-point exception, probably terminating the program).