[Hat] failure w/ simple example
Isaac Jones
hat@haskell.org
19 May 2003 17:57:30 -0400
Greetings :)
I have the following simple program for which Hat does not seem to
produce compilable code.
I'm using hat 2.02 which I built from source.
I'm using ghc 5.04.2 from a Debian package.
I'm using hmake 3.07 from a Debian package.
Any suggestions?
peace,
isaac
--------------- Program
module Main where
main = putStr (show $ 4 ^ 2)
--------------- GHC Error:
% hmake -hat Approach
hat-trans Approach.hs
Wrote Hat/Approach.hs
ghc -c -package hat -o Hat/Approach.o Hat/Approach.hs
Hat/Approach.hs:13:
Ambiguous type variable(s) `a' in the constraint `Num a'
arising from use of `gfromInteger' at Hat/Approach.hs:13
In the third argument of `Hat.Hat.ap1', namely
`(gfromInteger p3v23 p)'
In the fifth argument of `Hat.Hat.uapp2', namely
`(Hat.Hat.ap1 p3v23
p
(gfromInteger p3v23 p)
(Hat.Hat.conInteger p3v23 p 4))'
Hat/Approach.hs:13:
Ambiguous type variable(s) `a1' in the constraint `Integral a1'
arising from use of `*^' at Hat/Approach.hs:13
In the fourth argument of `Hat.Hat.uapp2', namely `(*^)'
In the sixth argument of `Hat.Hat.uapp2', namely
`(Hat.Hat.uapp2 p3v25
p
(+^)
(*^)
(Hat.Hat.ap1 p3v23
p
(gfromInteger p3v23 p)
(Hat.Hat.conInteger p3v23 p 4))
(Hat.Hat.ap1 p3v27
p
(gfromInteger p3v27 p)
(Hat.Hat.conInteger p3v27 p 2)))'
--------------- Generated Code
module Main where
import qualified Prelude
import qualified Hat.Hat as T
import qualified Hat.PreludeBasic
import Hat.Prelude
gmain pmain p = T.constUse pmain p smain
smain =
T.constDef T.mkRoot amain
(\ p ->
T.uapp1 p3v8 p aputStr hputStr
(T.uapp2 p3v21 p (+$) (*$) (gshow p3v16 p)
(T.uapp2 p3v25 p (+^) (*^)
(T.ap1 p3v23 p (Hat.PreludeBasic.gfromInteger p3v23 p)
(T.conInteger p3v23 p 4))
(T.ap1 p3v27 p (Hat.PreludeBasic.gfromInteger p3v27 p)
(T.conInteger p3v27 p 2)))))
tMain = T.mkModule "Main" "Approach.hs" Prelude.True
amain = T.mkVariable tMain 30001 3 0 "main" Prelude.False
p3v1 = T.mkSrcPos tMain 30001
p3v8 = T.mkSrcPos tMain 30008
p3v21 = T.mkSrcPos tMain 30021
p3v16 = T.mkSrcPos tMain 30016
p3v25 = T.mkSrcPos tMain 30025
p3v23 = T.mkSrcPos tMain 30023
p3v27 = T.mkSrcPos tMain 30027
main = T.traceIO "Approach" (Main.gmain T.mkNoSrcPos T.mkRoot)