Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        [EMAIL PROTECTED]

You can reach the person managing the list at
        [EMAIL PROTECTED]

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  what type is 'Val 9' when 'Val Int' a ctor   for 'Expr e'?
      (Jason Dusek)
   2. Re:  what type is 'Val 9' when 'Val Int' a ctor   for 'Expr e'?
      (Antoine Latter)
   3. Re:  A Pascal-like Language Compiler (Pranesh Srinivasan)
   4. Re:  what type is 'Val 9' when 'Val Int' a ctor   for 'Expr e'?
      (Daniel Fischer)
   5.  Type problems with IOArray (Xuan Luo)
   6. Re:  Type problems with IOArray (Alexander Dunlap)
   7. Re:  what type is 'Val 9' when 'Val Int' a ctor   for 'Expr e'?
      (Larry Evans)


----------------------------------------------------------------------

Message: 1
Date: Wed, 22 Oct 2008 14:10:05 -0700
From: "Jason Dusek" <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] what type is 'Val 9' when 'Val Int' a
        ctor    for 'Expr e'?
To: "Larry Evans" <[EMAIL PROTECTED]>
Cc: Beginners@haskell.org
Message-ID:
        <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=UTF-8

  Can you explain why you think you need that annotation? I
  can't see an ambiguous interpretation of your code.

--
_jsn


------------------------------

Message: 2
Date: Wed, 22 Oct 2008 16:44:07 -0500
From: "Antoine Latter" <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] what type is 'Val 9' when 'Val Int' a
        ctor    for 'Expr e'?
To: "Jason Dusek" <[EMAIL PROTECTED]>
Cc: Beginners@haskell.org
Message-ID:
        <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=ISO-8859-1

On Wed, Oct 22, 2008 at 4:10 PM, Jason Dusek <[EMAIL PROTECTED]> wrote:
>  Can you explain why you think you need that annotation? I
>  can't see an ambiguous interpretation of your code.
>

The confusion is that the 'Val' constructor is for the 'Expr' type,
which has a phantom type parameter in its type constructor.

Can you load that up into GHCi and type:

> :t val_9

which should cause GHCi to print out what it thinks the type of that
expression is.

-Antoine


------------------------------

Message: 3
Date: Thu, 23 Oct 2008 03:48:24 +0530
From: "Pranesh Srinivasan" <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] A Pascal-like Language Compiler
To: " Joel Bj?rnson " <[EMAIL PROTECTED]>
Cc: Hasekll - Beginners <beginners@haskell.org>
Message-ID:
        <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=ISO-8859-1

Hey all,

Thanks to everyone for replying. I was severly caught up with work for
the last two days.

The link Larry gave for the lookahead states seems very nice :). But I
am not sure if Ill be looking to calculate the lookahead states myself,
or let BNFC do the job? In either case, I think merely printing the line
number where the error occured should do in the worse case. It will be
exciting to have nice error messages though.

I am starting to reliase the advantage of pattern matching being
present, like Chris had said. I mean it definitely beats maintaining
and checking a flag, the way you would do it in C :)

> Definitely not, just go for it. In the IPL course @ UU we implemented
Thanks, Chris :).

> 1. Parse input file into an abstract syntax tree representation.
> 2. Perform type checking on your syntax tree.
> 3. Transform the syntax tree using re-write rules and optimisations.
> 4. Pretty print the syntax tree in order to output code of your target 
> language.

That seems like a very nice scheme to follow. I had a similar method in
mind. Step 3 is what I am really worried about. How easy/difficult will
it be in a pure func language, to "transform" the sytnax tree.

I have to take a deeper look at BNFC. But from an initial look, it seems
way too powerful for me to use? At least as powerful as yacc. And that
with Haskell, should give me a very good toolset-advantage?

@Chris : The ipl course website, seems very helpful, especially some of
the lectures on abstract syntax.

-- 
Pranesh Srinivasan,
Third Year Student,
Computer Science & Engineering,
Indian Institute of Technology - Madras.

http://spranesh.googlepages.com
http://www.cse.iitm.ac.in/~spranesh/


------------------------------

Message: 4
Date: Thu, 23 Oct 2008 02:52:39 +0200
From: Daniel Fischer <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] what type is 'Val 9' when 'Val Int' a
        ctor    for 'Expr e'?
To: "Antoine Latter" <[EMAIL PROTECTED]>,       "Jason Dusek"
        <[EMAIL PROTECTED]>
Cc: Beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain;  charset="iso-8859-1"

Am Mittwoch, 22. Oktober 2008 23:44 schrieb Antoine Latter:
> On Wed, Oct 22, 2008 at 4:10 PM, Jason Dusek <[EMAIL PROTECTED]> wrote:
> >  Can you explain why you think you need that annotation? I
> >  can't see an ambiguous interpretation of your code.
>
> The confusion is that the 'Val' constructor is for the 'Expr' type,
> which has a phantom type parameter in its type constructor.
>
> Can you load that up into GHCi and type:
> > :t val_9
>
> which should cause GHCi to print out what it thinks the type of that
> expression is.
>
> -Antoine

ghci correctly thinks that has the type Expr e. Much like
*Main> :t []
[] :: [a]

I think what goes on here is defaulting (deviating from Section 4.3.4 of the 
report, but it's the same deviation that allows [] to be printed). To print 
it, ghci picks some default type for e, probably Integer, as the defaut 
default is (Integer, Double), doesn't influence the result of show.
If you muck around with the Show instance, you can easily get compilation 
errors like "Ambiguous type variable..." (e.g. if you add a (Show e) 
constraint to the Show instance for (Expr e), but not if you add a (Num e) or 
an (Integral e) constraint).


------------------------------

Message: 5
Date: Wed, 22 Oct 2008 19:26:15 -0700
From: "Xuan Luo" <[EMAIL PROTECTED]>
Subject: [Haskell-beginners] Type problems with IOArray
To: beginners@haskell.org
Message-ID:
        <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=ISO-8859-1

I am having lots of trouble using polymorphic mutable IOArrays. Here
is an example program:

import Data.Array.MArray
import Data.Array.IO

foo x = do a <- newArray (0, 4) x
           readArray a 2

main = foo 42 >>= print

So there is a function "foo" which makes an array of polymorphic type
initialized with a value, then returns one of the elements of the
array. So here "foo x" essentially does the same as "return x"; but it
demonstrates problems I am having.

So the above program fails with:
testarray.hs:7:7:
    No instance for (MArray a t IO)
      arising from a use of `foo' at testarray.hs:7:7-12
    Possible fix: add an instance declaration for (MArray a t IO)
    In the first argument of `(>>=)', namely `foo 42'
    In the expression: foo 42 >>= print
    In the definition of `main': main = foo 42 >>= print

Okay; so the problem is that "newArray" is a function that creates
MArrays in general; but there is no function to specifically create
IOArrays in particular, and it doesn't know I want to use IOArrays. In
fact, all the other functions that are used to operate on mutable
arrays are generic MArray functions too, and there is basically
nothing that is specific to IOArrays, so it is not as if the compiler
can "figure it out from context". This is bad design. I wish it could
just decide to default to IOArrays or something, since IOArrays of any
type already are instances of MArray, so it would be natural.

Okay so the general way to resolve this is to add signatures to tell
it that it is an IOArray. But when I give the type for IOArray I also
have to tell it what type its contents are, and I want it to work
polymorphically over any type, so the array has to be of a polymorphic
type:

foo x = do a <- newArray (0, 4) x :: IO (IOArray Int a)
           readArray a 2

But of course it doesn't know what "a" is, so maybe I am forced to
also add a signature for the function "foo" itself, which the compiler
should really be able to figure out for me:

import Data.Array.MArray
import Data.Array.IO

foo :: a -> IO a
foo x = do a <- newArray (0, 4) x :: IO (IOArray Int a)
           readArray a 2

main = foo 42 >>= print

Okay, now the real problems begin:
testarray.hs:5:32:
    Couldn't match expected type `a1' against inferred type `a'
      `a1' is a rigid type variable bound by
           the polymorphic type `forall a1. IO (IOArray Int a1)'
             at testarray.hs:5:16
      `a' is a rigid type variable bound by
          the type signature for `foo' at testarray.hs:4:7
    In the second argument of `newArray', namely `x'
    In a 'do' expression: a <- newArray (0, 4) x :: IO (IOArray Int a)
    In the expression:
        do a <- newArray (0, 4) x :: IO (IOArray Int a)
           readArray a 2

What the heck is this? I looked through a lot of stuff online and
eventually found that this works:

{-# LANGUAGE ScopedTypeVariables #-}
import Data.Array.MArray
import Data.Array.IO

foo :: forall a. a -> IO a
foo x = do a <- newArray (0, 4) x :: IO (IOArray Int a)
           readArray a 2

main = foo 42 >>= print

So I had to add some weird "forall" stuff to my function signature and
enable some language extension flag(?). This seems way too
complicated.

I just want to be able to make and use a simple polymorphic array in
the IO monad with regular Haskell, without changing compiler flags or
anything like that. I have been doing well in other stuff involving
the IO monad, but these mutable arrays really got me stuck.

Thanks,


------------------------------

Message: 6
Date: Wed, 22 Oct 2008 20:04:10 -0700
From: "Alexander Dunlap" <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] Type problems with IOArray
To: "Xuan Luo" <[EMAIL PROTECTED]>
Cc: beginners@haskell.org
Message-ID:
        <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=ISO-8859-1

On Wed, Oct 22, 2008 at 7:26 PM, Xuan Luo <[EMAIL PROTECTED]> wrote:
> I am having lots of trouble using polymorphic mutable IOArrays. Here
> is an example program:
>
> import Data.Array.MArray
> import Data.Array.IO
>
> foo x = do a <- newArray (0, 4) x
>           readArray a 2
>
> main = foo 42 >>= print
>
> So there is a function "foo" which makes an array of polymorphic type
> initialized with a value, then returns one of the elements of the
> array. So here "foo x" essentially does the same as "return x"; but it
> demonstrates problems I am having.
>
> So the above program fails with:
> testarray.hs:7:7:
>    No instance for (MArray a t IO)
>      arising from a use of `foo' at testarray.hs:7:7-12
>    Possible fix: add an instance declaration for (MArray a t IO)
>    In the first argument of `(>>=)', namely `foo 42'
>    In the expression: foo 42 >>= print
>    In the definition of `main': main = foo 42 >>= print
>
> Okay; so the problem is that "newArray" is a function that creates
> MArrays in general; but there is no function to specifically create
> IOArrays in particular, and it doesn't know I want to use IOArrays. In
> fact, all the other functions that are used to operate on mutable
> arrays are generic MArray functions too, and there is basically
> nothing that is specific to IOArrays, so it is not as if the compiler
> can "figure it out from context". This is bad design. I wish it could
> just decide to default to IOArrays or something, since IOArrays of any
> type already are instances of MArray, so it would be natural.
>
> Okay so the general way to resolve this is to add signatures to tell
> it that it is an IOArray. But when I give the type for IOArray I also
> have to tell it what type its contents are, and I want it to work
> polymorphically over any type, so the array has to be of a polymorphic
> type:
>
> foo x = do a <- newArray (0, 4) x :: IO (IOArray Int a)
>           readArray a 2
>
> But of course it doesn't know what "a" is, so maybe I am forced to
> also add a signature for the function "foo" itself, which the compiler
> should really be able to figure out for me:
>
> import Data.Array.MArray
> import Data.Array.IO
>
> foo :: a -> IO a
> foo x = do a <- newArray (0, 4) x :: IO (IOArray Int a)
>           readArray a 2
>
> main = foo 42 >>= print
>
> Okay, now the real problems begin:
> testarray.hs:5:32:
>    Couldn't match expected type `a1' against inferred type `a'
>      `a1' is a rigid type variable bound by
>           the polymorphic type `forall a1. IO (IOArray Int a1)'
>             at testarray.hs:5:16
>      `a' is a rigid type variable bound by
>          the type signature for `foo' at testarray.hs:4:7
>    In the second argument of `newArray', namely `x'
>    In a 'do' expression: a <- newArray (0, 4) x :: IO (IOArray Int a)
>    In the expression:
>        do a <- newArray (0, 4) x :: IO (IOArray Int a)
>           readArray a 2
>
> What the heck is this? I looked through a lot of stuff online and
> eventually found that this works:
>
> {-# LANGUAGE ScopedTypeVariables #-}
> import Data.Array.MArray
> import Data.Array.IO
>
> foo :: forall a. a -> IO a
> foo x = do a <- newArray (0, 4) x :: IO (IOArray Int a)
>           readArray a 2
>
> main = foo 42 >>= print
>
> So I had to add some weird "forall" stuff to my function signature and
> enable some language extension flag(?). This seems way too
> complicated.
>
> I just want to be able to make and use a simple polymorphic array in
> the IO monad with regular Haskell, without changing compiler flags or
> anything like that. I have been doing well in other stuff involving
> the IO monad, but these mutable arrays really got me stuck.
>
> Thanks,
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>

One way is to move the type signature one level lower:

import Data.Array.MArray
import Data.Array.IO

foo :: a -> IO a
foo x = do a <- (newArray (0, 4) :: a -> IO (IOArray Int a)) x
          readArray a 2

main = foo 42 >>= print

Essentially, the problem you are running into is this: You need to
tell the compiler what kind of array you want newArray (0,4) x to
create. You'd like to be able to say newArray (0,4) x :: IO (IOArray
Int *SOMETHING*), but Haskell doesn't let you do that; you have to
assign it a  type variable. Normally, you'd say IO (IOArray Int a), as
you did, but in this case, there's a problem: the type of "newArray
(0,4) x" in this context is not as general as "a". You can't make it
an instance of *any* type, only the type of x. Unfortunately, there's
no way to specify the type of x without using scoped type variables.
(In fact, that's pretty much the whole point of scoped type
variables.)

The solution, then, is to not specify the type of newArray (0,4) x but
only the type of newArray (0,4). newArray (0,4) actually can have the
type (a -> IO (IOArray Int a)) for *any* a, because you haven't put
any constraints on "a" by applying it to "x".

I hope that's somewhat clear; I apologize for the convolutedness.

Alex


------------------------------

Message: 7
Date: Wed, 22 Oct 2008 22:36:09 -0500
From: Larry Evans <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] what type is 'Val 9' when 'Val Int' a
        ctor    for 'Expr e'?
To: Daniel Fischer <[EMAIL PROTECTED]>
Cc: Beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset="iso-8859-1"

On 10/22/08 19:52, Daniel Fischer wrote:
> Am Mittwoch, 22. Oktober 2008 23:44 schrieb Antoine Latter:
>   
>> On Wed, Oct 22, 2008 at 4:10 PM, Jason Dusek <[EMAIL PROTECTED]> wrote:
>>     
>>>  Can you explain why you think you need that annotation? I
>>>  can't see an ambiguous interpretation of your code.
>>>       
>> The confusion is that the 'Val' constructor is for the 'Expr' type,
>> which has a phantom type parameter in its type constructor.
>>
>> Can you load that up into GHCi and type:
>>     
>>> :t val_9
>>>       
>> which should cause GHCi to print out what it thinks the type of that
>> expression is.
>>
>> -Antoine
>>     
>
> ghci correctly thinks that has the type Expr e. Much like
> *Main> :t []
> [] :: [a]
>
> I think what goes on here is defaulting (deviating from Section 4.3.4 of the 
> report, but it's the same deviation that allows [] to be printed). To print 
> it, ghci picks some default type for e, probably Integer, as the defaut 
> default is (Integer, Double), doesn't influence the result of show.
> If you muck around with the Show instance, you can easily get compilation 
> errors like "Ambiguous type variable..." (e.g. if you add a (Show e) 
> constraint to the Show instance for (Expr e), but not if you add a (Num e) or 
> an (Integral e) constraint).
>   
Thanks Deaniel.  The fog in my head begins to clear.
I took Antoine's suggestion and got:
<---cut here ---
GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
Loading package base ... linking ... done.
Prelude> :load 
"/home/evansl/prog_dev/haskell/my-code/uniplate.try.phantom.hs"
[1 of 1] Compiling Main             ( 
/home/evansl/prog_dev/haskell/my-code/uniplate.try.phantom.hs, interpreted )
Ok, modules loaded: Main.
*Main> let val_9 = Val 9
Loading package mtl-1.1.0.0 ... linking ... done.
Loading package array-0.1.0.0 ... linking ... done.
Loading package containers-0.1.0.1 ... linking ... done.
Loading package uniplate-1.2.0.1 ... linking ... done.
*Main> :t val_9
val_9 :: Expr e
*Main> print val_9
Val 9
*Main>
 >---cut here---
I guess the phantom type mentioned in Antoine's post  is the e in:

val_9::Expr e

?

-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20081022/23562c71/attachment.htm

------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 4, Issue 9
***************************************

Reply via email to