#4181: Template Haskell + -fdicts-strict fails
-------------------------------+--------------------------------------------
    Reporter:  LouisWasserman  |       Owner:                                   
 
        Type:  bug             |      Status:  new                              
 
    Priority:  normal          |   Component:  Compiler                         
 
     Version:  6.12.3          |    Keywords:  template haskell strict 
dictionary
          Os:  Linux           |    Testcase:                                   
 
Architecture:  x86_64 (amd64)  |     Failure:  Compile-time crash               
 
-------------------------------+--------------------------------------------

Comment(by LouisWasserman):

 From the beginning, now:

 {{{
 module Foo where

 import Language.Haskell.TH

 foo :: Q ()
 foo = return (TupE []) >>= const (return ())
 }}}

 ghc-core'ing Foo with -XTemplateHaskell -fdicts-strict yields

 {{{
 Foo.foo3 :: forall (m_aKr :: * -> *). Functor m_aKr
 GblId

 Foo.foo3 =
   \ (@ m_aKr::* -> *) ->
     Control.Exception.Base.runtimeError
       @ Functor m_aKr
       "Oops!  Entered absent arg ww_sL6{v} [lid] <pred>base:Functor{tc 2a}
 m{tv aKr} [tv]"
 }}}

 which certainly seems incorrect.  To get GHC to actually crash,

 {{{
 module Bar where

 import Foo
 import Language.Haskell.TH

 bar :: ()
 bar = $(do      x <- foo
                 x `seq` return (TupE []))
 }}}

 The following is verbatim from my command line:

 {{{
 lowas...@lowasser:~$ ghc --make Bar -fdicts-strict -XTemplateHaskell
 -fforce-recomp
 [1 of 2] Compiling Foo              ( Foo.hs, Foo.o )
 [2 of 2] Compiling Bar              ( Bar.hs, Bar.o )
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 Loading package ffi-1.0 ... linking ... done.
 Loading package pretty-1.0.1.1 ... linking ... done.
 Loading package array-0.3.0.1 ... linking ... done.
 Loading package containers-0.3.0.0 ... linking ... done.
 Loading package template-haskell ... linking ... done.
 lowas...@lowasser:~$ ghc --make Bar -fdicts-strict -XTemplateHaskell
 -fforce-recomp -O
 [1 of 2] Compiling Foo              ( Foo.hs, Foo.o )
 [2 of 2] Compiling Bar              ( Bar.hs, Bar.o )
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 Loading package ffi-1.0 ... linking ... done.
 Loading package pretty-1.0.1.1 ... linking ... done.
 Loading package array-0.3.0.1 ... linking ... done.
 Loading package containers-0.3.0.0 ... linking ... done.
 Loading package template-haskell ... linking ... done.

 Bar.hs:7:8:
     Exception when trying to run compile-time code:
       Oops!  Entered absent arg ww_sL3{v} [lid]
 <pred>base:GHC.Base.Functor{tc 2a} m{tv aKo} [tv]
       Code: let
               >>= = (>>=)
               $dMonad = Language.Haskell.TH.Syntax.$fMonadQ
               return = return
               ....
             in
               do { x <- foo;
                    seq x return (Language.Haskell.TH.Syntax.TupE
 (GHC.Types.[])) }
     In the expression:
         $(do { x <- foo;
                  x `seq` return (TupE []) })
     In the definition of `bar':
         bar = $(do { x <- foo;
                        x `seq` return (TupE []) })
 lowas...@lowasser:~$ ghci Bar -fdicts-strict -XTemplateHaskell -fforce-
 recomp -O
 GHCi, version 6.12.3: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 Loading package ffi-1.0 ... linking ... done.
 [1 of 2] Compiling Foo              ( Foo.hs, interpreted )
 [2 of 2] Compiling Bar              ( Bar.hs, interpreted )
 Loading package pretty-1.0.1.1 ... linking ... done.
 Loading package array-0.3.0.1 ... linking ... done.
 Loading package containers-0.3.0.0 ... linking ... done.
 Loading package template-haskell ... linking ... done.
 Ok, modules loaded: Bar, Foo.
 *Bar>
 Leaving GHCi.
 }}}

 That is, it fails with ghc --make -O, but not with ghci -O or ghc --make
 -O0.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4181#comment:7>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to