I'm finding that Green Card 0.9 seems to have problems with GHC 2.09 (both
with the cygwin32 version - I haven't checked the solaris one
yet). Essentially functions which return IO types fail type checking. I had a
.ss file which worked OK with 2.08 but does not type check with 2.09. I can't
send you the whole file, so here is a similar one which shows the same
behaviour under 2.09.
-----
module Small
where
import StdDis
import IO
import GlaExts
%fun small1 :: Int -> Int
%code res = small(arg1)
%fun small2 :: Int -> IO Int
%code res = small(arg1)
-----
small1 is OK, small2 is not. green-card generates the following .hs file:
------
module Small
where
import StdDis
import IO
import GlaExts
small1 :: Int -> Int
small1 arg1 =
unsafePerformPrimIO(
_casm_ ``do {int arg1 = %0;
int res;
res = small(arg1);
%r = res ;} while(0);'' arg1 >>= \ res ->
return (res))
small2 :: Int -> IO Int
small2 arg1 =
IO (_casm_ ``do {int arg1 = %0;
int res;
res = small(arg1);
%r = res ;} while(0);'' arg1 >>= \ res ->
return (Right (res)))
-----
ghc 2.09 says this:
-----
The Glorious Glasgow Haskell Compilation System, version 2.09, patchlevel 0
Effective command line: -v -c -fvia-C -fglasgow-exts -i/usr/local/share
Ineffective C pre-processor:
echo '{-# LINE 1 "Small.hs" -}' > /tmp/ghc1031.cpp && cat Small.hs >>
/tmp/ghc1031.cpp
0.00user 0.00system 0:00.33elapsed 0%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+0minor)pagefaults 0swaps
ghc:compile:Output file Small.o doesn't exist
ghc:compile:Interface file Small.hi doesn't exist
ghc:recompile:Input file Small.hs newer than Small.o
Haskell compiler:
/usr/local/lib/ghc-2.09/hsc ,-N ,-W ,/tmp/ghc1031.cpp -fglasgow-exts
-fignore-interface-pragmas -fomit-interface-pragmas -fsimplify [
-ffloat-lets-exposing-whnf -ffloat-primops-ok -fcase-of-case -fdo-case-elim
-freuse-con -fpedantic-bottoms -fsimpl-uf-use-threshold3 -fmax-simplifier-iterations4
] -fwarn-overlapping-patterns -fwarn-missing-methods -fwarn-duplicate-exports
-himap=/usr/local/share%.hi:.%.hi:/usr/local/lib/ghc-2.09/imports%.hi -v
-hifile=/tmp/ghc1031.hi -C=/tmp/ghc1031.hc +RTS -H6000000 -K1000000
Glasgow Haskell Compiler, version 2.09, for Haskell 1.4
Small.hs:21: Couldn't match the type
`-> (State# RealWorld)' against `IO'
Expected: `IO taLu'
Inferred: `State# RealWorld -> taLv'
In the first argument of `>>=', namely
`_casm_ ``do {int arg1 = %0;
int res;
res = small(arg1);
%r = res ;} while(0);''
arg1'
In the first argument of `IO', namely
`((_casm_ ``do {int arg1 = %0;
int res;
res = small(arg1);
%r = res ;} while(0);''
arg1)
>>= (\ res -> return (Right (res))))'
In an equation for function `small2':
`small2 arg1
= IO ((_casm_ ``do {int arg1 = %0;
int res;
res = small(arg1);
%r = res ;} while(0);''
arg1)
>>= (\ res -> return (Right (res))))'
Compilation had errors
Command exited with non-zero status 1
0.00user 0.00system 0:08.61elapsed 0%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+0minor)pagefaults 0swaps
deleting... /tmp/ghc1031.cpp /tmp/ghc1031.hi /tmp/ghc1031.hc
rm -f /tmp/ghc1031*
-----
I've tried putting in explicit %result lines to now avail: neither %result
(int x), nor %result (iO (int x)) are any good.
Any ideas?
-- David
_______________________________________________________________________
David Elworthy <[EMAIL PROTECTED]>
Canon Research Centre Europe Ltd., Guildford, Surrey, UK
URL: http://www.cre.canon.co.uk/
Phone: +44 1483 448844; Fax: +44 1483 448845