[Haskell-beginners] "stage restriction" when using Data.Heap

Daniel Fischer daniel.is.fischer at googlemail.com
Tue Jan 8 18:40:27 CET 2013


On Tuesday 08 January 2013, 12:02:45, Brent Yorgey wrote:
> Twan's analysis is correct.  But wow, that's a horrible error
> message.  Do you by any chance have the TemplateHaskell extension
> enabled (either with {-# LANGUAGE TemplateHaskell #-} at the top or
> your file, or with :set -XTemplateHaskell in a .ghci file, or anything
> like that)?

Must be:

module Naked where

start :: Int
start = 13

start + 5

======

$ ghci Naked
GHCi, version 7.6.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Naked            ( Naked.hs, interpreted )

Naked.hs:6:1: Parse error: naked expression at top level
Failed, modules loaded: none.

======

$ ghci -XTemplateHaskell Naked
GHCi, version 7.6.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Naked            ( Naked.hs, interpreted )

Naked.hs:6:1:
    GHC stage restriction:
      `start' is used in a top-level splice or annotation,
      and must be imported, not defined locally
    In the first argument of `(+)', namely `start'
    In the expression: start + 5
Failed, modules loaded: none.

The message without TH is clear and good.

> If not this should really be filed as a bug, GHC has no
> business giving TH-related error messages without TH being turned on.
> 
> -Brent



More information about the Beginners mailing list