-- Sorry, but if ghc tells me to report it..
--
-- Using :The Glorious Glasgow Haskell Compilation System, version 4.08.1
-- (if this is also needed) : gcc 2.95.2 ( also egcs 1.1.2)
-- ghc -v -fglasgow-exts -i/usr/local/lib/ghc-4.08.1/imports/lang/  \
-- -o bug bug.hs -lHSlang 
--
-- message by ghc (ghc -v in attachment) : 
--      panic! (the `impossible' happened):
--      tcLookupGlobalValue: <THIS>.PrelIOBase.returnIO{-0B,s-}
--    Please report it as a compiler bug to [EMAIL PROTECTED]

module Main where

import Foreign

foreign export ccall "gccd" mygcd :: Int -> Int -> Int 
main =
    do
    putStrLn "No bug"

mygcd  a b = if (a==b) then a 
                else if (a<b) then mygcd a (b-a)
                else mygcd (a-b) a



-- Bye Axel
The Glorious Glasgow Haskell Compilation System, version 4.08.1

Effective command line: -v -fglasgow-exts 
-i/home/cip/krauth//lib/ghc-4.08.1/imports/lang/ -o bug -lHSlang

Ineffective C pre-processor:
        echo '{-# LINE 1 "bug.hs" -}' > /tmp/ghc7909.cpp && cat bug.hs >> 
/tmp/ghc7909.cpp
0.00user 0.00system 0:00.00elapsed 0%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (107major+15minor)pagefaults 0swaps
ghc:compile:Output file bug.o doesn't exist
ghc:compile:Interface file bug.hi doesn't exist
ghc:recompile:Input file bug.hs newer than bug.o

Haskell compiler:
        /home/cip/krauth//lib/ghc-4.08.1/hsc /tmp/ghc7909.cpp  -fglasgow-exts 
-fignore-interface-pragmas -fomit-interface-pragmas -fsimplify [ 
-fmax-simplifier-iterations4 ]   -fwarn-overlapping-patterns -fwarn-missing-methods 
-fwarn-missing-fields -fwarn-deprecations -fwarn-duplicate-exports -fhi-version=408 
-static 
"-himap=/home/cip/krauth//lib/ghc-4.08.1/imports/lang/%.hi:.%.hi:/home/cip/krauth//lib/ghc-4.08.1/imports/lang%.hi:/home/cip/krauth//lib/ghc-4.08.1/imports/lang%.hi:/home/cip/krauth//lib/ghc-4.08.1/imports/std%.hi"
 "-himap-sep=:"    -v -hifile=/tmp/ghc7909.hi -olang=asm -ofile=/tmp/ghc7909.s 
-F=/tmp/ghc7909_stb.c -FH=/tmp/ghc7909_stb.h +RTS -H6000000 -K1000000
Glasgow Haskell Compiler, version 4.08, for Haskell 98, compiled by GHC version 4.08

panic! (the `impossible' happened):
        tcLookupGlobalValue: <THIS>.PrelIOBase.returnIO{-0B,s-}

Please report it as a compiler bug to [EMAIL PROTECTED]


Command exited with non-zero status 1
0.89user 0.06system 0:01.00elapsed 94%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (1344major+1811minor)pagefaults 0swaps
deleting... /tmp/ghc7909.cpp /tmp/ghc7909.hi /tmp/ghc7909.s /tmp/ghc7909_stb.c 
/tmp/ghc7909_stb.h

rm -f /tmp/ghc7909*

Reply via email to