On 12 March 2011 21:53, Adam Megacz <[email protected]> wrote:
> Did HelloWorld work?  See the commands here

I'm not sure what you mean by HelloWorld - it doesn't seem to be
mentioned on that page. However, I have just tried out "pow" and had
exactly the same problem.

The pow example on your page doesn't work as stated. I think that you instead of

  (*) :: forall a. <[ Int -> Int -> Int ]>@a

You need

  <[ (*) ]> :: forall a. <[ Int -> Int -> Int ]>@a

And you also need something like this declaration:

  <[ fromInteger ]> :: forall a. <[ Integer -> Int ]>@a

However, it's easier just to use GHC.HetMet.CodeTypes for these
definitions. Here is the complete example:


{{{
{-# LANGUAGE ModalTypes, FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Foo where

import Control.Arrow

import Prelude

import GHC.HetMet.CodeTypes hiding ((-)) -- For code-typed fromInteger
and friends
import GHC.HetMet.GArrow


-- Included so I can actually run some code (in theory), and my build
doesn't have your newly-added instances
instance GArrow (->) (,) where
  ga_id        =  arr Prelude.id
  ga_comp      =  (>>>)
  ga_first     =  first
  ga_second    =  second
  ga_cancell   =  arr (\((),x) -> x)
  ga_cancelr   =  arr (\(x,()) -> x)
  ga_uncancell =  arr (\x -> ((),x))
  ga_uncancelr =  arr (\x -> (x,()))
  ga_assoc     =  arr (\((x,y),z) -> (x,(y,z)))
  ga_unassoc   =  arr (\(x,(y,z)) -> ((x,y),z))

instance GArrowDrop (->) (,) where
  ga_drop      =  arr (\x -> ())

instance GArrowCopy (->) (,) where
  ga_copy      =  arr (\x -> (x,x))

instance GArrowSwap (->) (,) where
  ga_swap      =  arr (\(x,y) -> (y,x))

instance GArrowLoop (->) (,) where
  ga_loop      =  loop


pow :: forall a. (GuestLanguageFromInteger a Int, GuestLanguageMult a
Int) => Int -> <[ Int -> Int ]>@a
pow n =
  if n==0
  then <[ \x -> 1 ]>
  else <[ \x -> x * ~~(pow $ n-1) x ]>


ifThenElse :: Bool -> a -> a -> a
ifThenElse True x y = x
ifThenElse False x y = y


-- Should print 4^3 == 64
main = print i
  where
    i :: Int
    i = flatten (pow 3) 4
}}}

This doesn't compile because the "flatten" function you claim is
exported from GHC.HetMet.CodeTypes doesn't exist. There is a
hetmet_flatten but it is commented out for some reason.

Even if you remove the "main" definition, I get exactly the same error
as before:

{{{
$ ~/Programming/Checkouts/ghc-garrows/inplace/bin/ghc-stage2
-ddump-types GArrows-Pow.hs -dcoqpass -fforce-recomp
[1 of 1] Compiling Foo              ( GArrows-Pow.hs, GArrows-Pow.o )
TYPE SIGNATURES
    ifThenElse :: forall a. Bool -> a -> a -> a
    pow :: forall a.
           (GuestLanguageFromInteger a Int, GuestLanguageMult a Int) =>
           Int -> <[Int -> Int]>@a
TYPE CONSTRUCTORS
INSTANCES
  instance GArrowLoop (->) (,) -- Defined at GArrows-Pow.hs:34:10-28
  instance GArrowSwap (->) (,) -- Defined at GArrows-Pow.hs:31:10-28
  instance GArrowCopy (->) (,) -- Defined at GArrows-Pow.hs:28:10-28
  instance GArrowDrop (->) (,) -- Defined at GArrows-Pow.hs:25:10-28
  instance GArrow (->) (,) -- Defined at GArrows-Pow.hs:13:10-24
Dependent modules: []
Dependent packages: [base, ghc-prim, integer-gmp]

==================== Coq Pass Output ====================ghc-stage2:
panic! (the 'impossible' happened)
  (GHC version 7.1.20110308 for i386-apple-darwin):
        unable to convert HaskWeak to HaskStrong due to:\n  type mismatch in
HaskWeak ELet: a and GHC.Types.Bool

Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
}}}

What am I doing wrong?

Cheers,
Max

_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to