[Haskell-cafe] Type vs TypeClass duality

2007-10-23 Thread TJ
Hi again,

Following up on my previous thread, I have figured out why it bothered
me that we cannot have a list such as the following: [abc, 123, (1,
2)] :: Show a = [a]

It seems to me that there is an annoying duality in treating simple
algebraic data type vs type classes. As it stands, I can only have a
list where all the elements are of the same basic, ADT, type. There is
no way to express directly a list where all the elements satisfy a
given type class constraint.

If I am not mistaken, type classes are currently implemented in GHC like so:

Given a function show of type Show a = a - string, and the
expression show 10, GHC will pass the Int dictionary for class
Show's methods and the integer 10 to the function show. In other
words, for each type class constraint in the function type, there will
be a hidden dictionary parameter managed entirely by the compiler.

What I find strange is, if we can have functions with hidden
parameters, why can't we have the same for, say, elements of a list?

Suppose that I have a list of type Show a = [a], I imagine that it
would not be particularly difficult to have GHC insert a hidden item
along with each value I cons onto the list, in effect making the
concrete type of the list [(Dictionary Show, a)]. I'm assuming that it
will not be particularly difficult because GHC will know the types of
the values I cons onto it, so it will most definitely be able to find
the Show dictionary implemented by that type, or report a type
mismatch error. No dynamic type information is necessary.

I am not an OO programming zealot, but I'd like to note here that this
is also how (class based) OO languages would allow the programmer to
mix types. e.g. I can have a ListShow where the elements can be
instances of Show, or instances of subclasses of Show.

Why does this second rate treatment of type classes exist in Haskell?


TJ
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type vs TypeClass duality

2007-10-23 Thread TJ
On 10/23/07, Luke Palmer [EMAIL PROTECTED] wrote:
 On 10/23/07, TJ [EMAIL PROTECTED] wrote:
  What I find strange is, if we can have functions with hidden
  parameters, why can't we have the same for, say, elements of a list?
 
  Suppose that I have a list of type Show a = [a], I imagine that it
  would not be particularly difficult to have GHC insert a hidden item
  along with each value I cons onto the list, in effect making the
  concrete type of the list [(Dictionary Show, a)]. I'm assuming that it
  will not be particularly difficult because GHC will know the types of
  the values I cons onto it, so it will most definitely be able to find
  the Show dictionary implemented by that type, or report a type
  mismatch error. No dynamic type information is necessary.

 Which is exactly what happens with:

 data Showable = forall a. Show a = Showable a
 stuff = [Showable 42, Showable hello, Showable 'w']

Which is exactly the kind of 2nd-rate treatment I dislike.

What does data Showable = forall a. Show a = Showable a do for you
anyway? Nothing. You just have to type it down. Imagine if we have to
type down our anonymous functions at the top level, and give them a
name just to satisfy the language: ugh. I find this extra annoying due
to not being able to declare datatypes anywhere other than at
top-level.

  I am not an OO programming zealot, but I'd like to note here that this
  is also how (class based) OO languages would allow the programmer to
  mix types. e.g. I can have a ListShow where the elements can be
  instances of Show, or instances of subclasses of Show.
 
 
  Why does this second rate treatment of type classes exist in Haskell?

 I think partially the reason is that such polymorphic data structures
 are somewhat less useful in Haskell than they are in OO languages.
 This may be in part due to the fact that there's no down-casting.  And
 certain wrappers, eg. Gtk, emulate up- and down-casting using various
 typeclass tricks.

 I was in a similar dilemma shortly after I started learning Haskell,
 coming from a C++ and Perl background.  I think #perl6 has some logs
 of me whining about Haskell's lack of OO features.  How are you
 supposed to design your programs modularly if you can't have a
 type-agnostic list?

 But it doesn't bug me anymore.  I can't really say why.  The natural
 solution space in Haskell is so different than that of OO languages,
 that you don't really need such existentially polymorphic (just made
 up that term) objects[1].  There is still plenty of modularity in
 Haskell programs--I would even call it OO, I think--it just looks
 different, and took a lot of getting used to.  I had to remap what I
 considered an object in my brain.

 Anyway, enough preachy.  Typeclasses definitely aren't perfect; global
 instance exportation has gotten me in trouble several times.  But,
 other than

  [exists a. Show a = a]

I actually don't understand that line. Substituting forall for exists,
someone in my previous thread said that it means every element in the
list is polymorphic, which I don't understand at all, since trying to
cons anything onto the list in GHCi results in type errors.

 What would be a first-rate treatment of type classes to you?  What
 kind of features do you want that they don't have?

Convenience. Same thing 1st-class functions do for me ;-)


TJ
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type vs TypeClass duality

2007-10-23 Thread TJ
On 10/23/07, Jules Bean [EMAIL PROTECTED] wrote:
 Short answer: You are worrying about syntax. The things you want are
 possible.

 TJ wrote:
  Following up on my previous thread, I have figured out why it bothered
  me that we cannot have a list such as the following: [abc, 123, (1,
  2)] :: Show a = [a]

 That type doesn't mean what you want it to mean. That means :

 A list of objects of some fixed type 'a', such that a is a member of the
 typeclass 'Show'. In fact, worse than that, it's a polymorphic list,
 which means the *caller* should be able to choose the type 'a'.

 What you want to mean is 'A list of objects, each of which is of some
 possibly different type 'a', subject only to the restriction that a is a
 member of typeclass Show.

Yes, of course. But given that what I want isn't directly expressible
in Haskell, without creating an existential type, I would not have
been able to give a valid Haskell type signature anyway ;-)

 Incidentally there is no restriction that all the elements in a list
 have to be an ADT. They can be functions, or tuples of functions, or
 higher order functions, or lists of tuples of higher order polymorphic
 functions operating on lists of functions on tuples of.

Yes. My mistake.

  Suppose that I have a list of type Show a = [a], I imagine that it
  would not be particularly difficult to have GHC insert a hidden item
  along with each value I cons onto the list, in effect making the
  concrete type of the list [(Dictionary Show, a)].

 Right. That's almost exactly what the Showable existential does.

   I'm assuming that it
  will not be particularly difficult because GHC will know the types of
  the values I cons onto it, so it will most definitely be able to find
  the Show dictionary implemented by that type, or report a type
  mismatch error. No dynamic type information is necessary.

 Now it sounds like your only complaint is that : has the wrong type?

No. I am saying that Haskell's type system forces me to write boilerplate.

 That is, the type inference algorithm which GHC uses, which is not the
 only one you can imagine, but for a variety of reasons is considered to
 be one of the best choices, cannot 'automatically' construct
 existentials, and requires some kinds of explicit annotations to
 'delimit' the existential.

Why can't it automatically construct them then? Assuming we do have a
syntax for A list of objects, each of which is of some
possibly different type 'a', subject only to the restriction that a is a
member of typeclass Show, as the following:

ls :: [a where Show a]

Then I would think that all the type checker has to do would be to check that,
a) everything you cons onto ls is an instance of class Show
b) where you extract items from ls, you only use them as you would use
any instance of class Show.

Which is exactly the same as for a list intList of type [Int], where
a) everything you cons onto it is of type Int
b) where you extract items from intList, you use them only as it is
valid to use an Int (+,-,*,/,etc)

Now assuming the existential type
data E = forall a. Show a = E a
EList :: [E]

What I have done is to wrap up the idea that E contains any instance
of Show, and that EList contains any E. Which is a roundabout way of
saying what I wanted to say: ls contains any instance of Show.

It seems Haskell's type inference has not kept up with advancements in
existential types.

 I will also repeat the non-justified assertion that others have made,
 and that I've made myself in the other thread, that you don't need
 existentials as often in haskell as you do in OO languages, and they
 certainly don't always need to be type-class quantified ones.

And I would like to say that whether or not I need it is not the
issue, as I currently do not in fact need it. This is a study of the
Haskell language not my possible practical applications of it.


TJ
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Uniqueness of principle type? (was Re: [Haskell-cafe] Type vs TypeClass duality)

2007-10-23 Thread TJ
On 10/23/07, Jules Bean [EMAIL PROTECTED] wrote:
 I believe it is to do with the requirement that expressions have a
 unique principle type. Certainly in principle the algorithm you outline
 is possible, but I don't know what else you would lose.

I'm not familiar with the term principal type. I shall have to study it.

  And I would like to say that whether or not I need it is not the
  issue, as I currently do not in fact need it. This is a study of the
  Haskell language not my possible practical applications of it.

 Whether one needs it, or does not need it, is indeed an issue: any
 change to the type inference algorithm has a cost. That cost has to be
 judged against the value of it. If an extension is seldom needed, then
 its value is low, so the cost is unlikely to be considered worth it. If
 an extension is frequently need and the cost is low, then that argues
 for it..

Ah... harsh realities of engineering. Well I hope this is judged to be
important enough to be included in a future revision of Haskell.


Thanks,

TJ
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type vs TypeClass duality

2007-10-23 Thread TJ
Tristan Allwood:

Very cool. I don't understand some (a lot of) parts though:

 instance Show a = Reify (ShowConstraint a) where
   reify = ShowC

ShowC has type (Show a) = ShowConstraint a, whereas reify is
supposed to have type ShowConstraint a.

 data SingleList (a :: * - *) where
   Cons :: (a b) - b - SingleList a - SingleList a
   Nil :: SingleList a

Cons has a type variable b in its signature, but no forall. I
suppose it comes from the * - * in SingleList's type?


That's all I can come up with for now. A great deal of high level
coding flying around above my head now.

Thanks,

TJ
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polymorphic (typeclass) values in a list?

2007-10-22 Thread TJ
On 10/22/07, Tim Docker [EMAIL PROTECTED] wrote:
 [...]
 You may then like to add a type class to turn things into renderables:

 class IsRenderable where
 toRenderable :: a - Renderable

 instance IsRendeable Point where ...
 instance IsRenderable Line where ...
 [...]

Cool. I should get more familiar with basic Haskell98 before I decide
on using GHC extensions...

Thanks,

TJ
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polymorphic (typeclass) values in a list?

2007-10-21 Thread TJ
On 10/22/07, Tim Docker [EMAIL PROTECTED] wrote:
 TJ:

  After all, sometimes all you need to know about a list is that
  all the elements support a common set of operations. If I'm
  implementing a 3d renderer for example, I'd like to have
 
  class Renderable a where
render :: a - RasterImage
 
  scene :: Renderable a = [a]


 Everyone has launched into explanations of how to use existentials
 to do this, but you may be happy in just haskell 98. In the above,
 you could just have:

 scene :: [RasterImage]

 Laziness will ensure that the computation/storage of the images
 will not occur until they are used.

 Tim


Ah... indeed it can, in this case. It won't work if class Renderable
also has a method for saving to file, etc, I suppose, unless scene ::
[(RasterImage,IO (),...whatever other operations...)]

Thanks for the heads up :)

TJ
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Polymorphic (typeclass) values in a list?

2007-10-19 Thread TJ
Why is it illegal to store values of differing types, but which
instance the same class, into a list? e.g.

a = [ 1, 2.0 ] :: Num a = [a]

After all, sometimes all you need to know about a list is that all the
elements support a common set of operations. If I'm implementing a 3d
renderer for example, I'd like to have

class Renderable a where
  render :: a - RasterImage

scene :: Renderable a = [a]


Instead of hardcoding a bunch of types as being Renderable, as in

data Renderable
  = Point Something
  | Line Something
  | Polygon Something

scene :: [Renderable]


Or maybe

data Point = Point Something
data Line = Line Something
data Polygon = Polygon Something

scene :: { points :: [Point], lines :: [Line], polygons :: [Polygons] }


Is there a way of achieving what I want to do? Existentials maybe? I'm
still learning the basic stuff and don't grok existentials at all, but
I even if I use those, I'll still have to wrap things up in a
constructor, won't I?


Thanks a bunch,

TJ
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polymorphic (typeclass) values in a list?

2007-10-19 Thread TJ
Dan Licata: Thanks for explaining the mechanics behind it. Knowing how
it (could) be implemented always helps me understand things.


On 10/20/07, Jules Bean [EMAIL PROTECTED] wrote:
 Quite often an explicit ADT is much nicer. But they represent two
 opposing patterns of code-writing. Explicit ADT allows you to write case
 statements handling 'all the logic in one place'; a class forces you to
 separate the differences into 'separate instances'.

Nice ADT example. Indeed that would be how I'd do it in SML. Use a
record type holding closures referencing an object of unknown type.
The nice thing I've found about doing it in SML this way is that I can
extract the object back out, using exceptions. e.g.

(* Start Standard ML *)

datatype Renderable = Renderable { render : unit - RenderedImage,
extract : unit - unit, tag : exn }

local
  datatype Point = Point Something
  exception ExtractMe Point
  exception Tag
in
  fun mkPoint Something =
let val p = Point Something
in { render = fn () = ... ,
 extract = fn () = raise ExtractMe p,
 tag = Tag }
end
  (* extractPoint would return the Point hidden away in a Renderable. *)
  fun extractPoint (Renderable { tag = Tag, extract, ... }) =
(extract (); Point SomethingPointless)
handle ExtractMe p = p
end

(* End SML *)

I don't know if this would work in Haskell, as I'm not familiar with
Haskell exceptions. Anyway I see that Haskell has a Dynamic type...


I've got a good grip on this now, I think. Thanks everyone.

TJ
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] State monad in the wikibood article

2007-03-01 Thread TJ

Matthew Brecknell:

Note the lambda abstraction (\st - ...) at the beginning of the
definition. This means that (container = fn) returns a *function* that
maps an input state to the result of (container2 st2). It doesn't return
the result of (container st2) directly.


Ah. Silly me :D
Thanks a bunch mate.

Cheers :)

TJ
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] State monad in the wikibood article

2007-02-28 Thread TJ

In the wikibook article here:
http://en.wikibooks.org/wiki/Haskell/Understanding_monads, which
really does an excellent job explaining things (nuclear waste
woohoo!), I am stuck at the following code snippet:

container = fn =
\st - let (a, st2)   = container st
   container2 = fn a
   in  container2 st2

What stumps me is that (=) is supposed to return a container, but if
we return (container2 st2) as in the code, then what we're really
returning is the contents of the container! So what would happen if we
do this:

nuclearWasteInContainer = processTheWaste = thoroughProcessTheWaste

It seems to me that the second (=) in the above expression would
have the arguments (nuclearWaste) and (nuclearWasteProcessor), when
what it really expects are (Container nuclearWaste) and
(nuclearWasteProcessor). So isn't something wrong with the definition
of (=) above? Or am I missing something?

(I know the article says that the type for their supposed State monad
at that point is not actually correct, and will be clarified further
on, but that seems to be irrelevant to my question.)


TJ the forever noobie.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] How is laziness defined?

2007-02-04 Thread TJ

I would think that with 100% laziness, nothing would happen until the
Haskell program needed to output data to, e.g. the console. Quite
obviously that's not it. So how is laziness defined in Haskell?

I remember vaguely someone saying that pattern matching on a value
forces it to be evaluated. Is that right? What else?

This is one of the things that just boggles my mind everytime I try to
wrap it around this thing called Haskell ;)

Cheers,

TJ
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How is laziness defined?

2007-02-04 Thread TJ

On 2/5/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:

Quoting TJ [EMAIL PROTECTED]:

 I would think that with 100% laziness, nothing would happen until the
 Haskell program needed to output data to, e.g. the console. Quite
 obviously that's not it. So how is laziness defined in Haskell?

It means that the program behaves as if things are evaluated if and
only if they are needed.  Needed in the Haskell sense, means needed
to do I/O.


So it's just IO which makes things run huh? OK that's basically what I
said there. Cool.


 This is one of the things that just boggles my mind everytime I try to
 wrap it around this thing called Haskell ;)

The cool part is that for the most part, it doesn't matter.  It just
works.  If you ever come across a case where it doesn't just work (e.g.
if you need a tilde pattern), you'll be ready for it.


I despise using what I don't understand. It's a big problem but one
which is more insurmountable than understanding Haskell, I think...

On 2/5/07, Andrew Wagner [EMAIL PROTECTED] wrote:

I found it useful to work through an example where lazy evaluation was
important, and wrote it up in a tutorial. It may or may not help you,
no guarantees, but here it is:
http://www.haskell.org/haskellwiki/Haskell/Lazy_Evaluation


With the code from your tutorial,

magic :: Int - Int - [Int]
magic 0 _ = []
magic m n = m : (magic n (m+n))

getIt :: [Int] - Int - Int
getIt [] _ = 0
getIt (x:xs) 1 = x
getIt (x:xs) n = getIt xs (n-1)

and the example expression,

getIt (magic 1 1) 3

It only gets run  (starts pattern matching and all) if I do a print on
it, or run it from GHCi (which will do theprint for me), right?

Thanks,

TJ
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How is laziness defined?

2007-02-04 Thread TJ

I went through the entry on laziness on the wikipedia wikibook. Very
nice. The wikibook sure has grown a lot since I last visited.

http://en.wikibooks.org/wiki/Haskell/Laziness

I believe I've got it now. By it I mean the understanding of laziness
in Haskell. Even though Haskell is, strictly speaking, not lazy, but
non-strict. It being but read and thought about, and not practiced,
might prove _itself_ to become Undefined as I evaluate it further. :D

Cheers,

TJ

On 2/5/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:

G'day all.

tjay.dreaming:

 So it's just IO which makes things run huh? OK that's basically what I
 said there. Cool.

Yeah, but you said output.  Sending a signal to another process in
Unix is I/O, which would force the process id to be evaluated, but
there's no output as such.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Beginner: IORef constructor?

2006-12-01 Thread TJ

Thanks. I've been reading the docs and examples on State (in
Control.Monad.State), but I can't understand it at all. ticks and
plusOnes... All they seem to do is return their argument plus 1...

On 12/1/06, Bernie Pope [EMAIL PROTECTED] wrote:


On 01/12/2006, at 6:08 PM, TJ wrote:

 First of all, sorry if this is a really silly question, but I couldn't
 figure it out from experimenting in GHCi and from the GHC libraries
 documentation (or Google).

 Is there an IORef consturctor? Or is it just internal to the
 Data.IORef module?

 I want a global variable, so I did the following:

 --
 module VirtualWorld where
  import Data.IORef
  theWorld = IORef [] -- This will be writeIORef'ed with a populated
 list as the user modifies the world.
 -

 It doesn't work. GHCi says that the IORef constructor is not in scope.
 I did a :module Data.IORef and then IORef [] and it still gives me
 the same error.

 I'm using GHC 6.6 on Windows.

Hi TJ,

IORef is an abstract data type, so you cannot refer to its
constructors directly.

Instead you must use:

newIORef :: a - IO (IORef a)

which will create an IORef on your behalf. Note that the result is in
the IO type,
which limits what you can do with it.

If you want a global variable then you can use something like:

import System.IO.Unsafe (unsafePerformIO)

global = unsafePerformIO (newIORef [])

But this is often regarded as bad programming style (depends who you
talk to). So you
should probably avoid this unless it is really necessary (perhaps you
could use a state
monad instead?)

Read the comments about unsafePerformIO on this page:

http://www.haskell.org/ghc/docs/latest/html/libraries/base/System-
IO-Unsafe.html

especially the notes about NOINLINE and -fno-cse

Cheers,
Bernie.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Beginner: IORef constructor?

2006-12-01 Thread TJ

Thanks for the demo. I don't actually understand what's going on yet,
but your code doesn't  really use a global variable, does it? From
what I can understand, the main function is passing the State to the
other functions.

I think I was careless about mixing IO functions and normal
functions. Now that I think about it, my global variable really
should only be available to IO functions, so the following should be
just fine:

--
module Global where

import Data.IORef

theGlobalVariable = newIORef []

testIt = do ref - theGlobalVariable
   original - readIORef ref
   print original
   writeIORef ref [1,2,3]
   new - readIORef ref
   print new
--

I've got a lot to learn about Haskell...

On 12/1/06, Donald Bruce Stewart [EMAIL PROTECTED] wrote:

tjay.dreaming:
 Thanks. I've been reading the docs and examples on State (in
 Control.Monad.State), but I can't understand it at all. ticks and
 plusOnes... All they seem to do is return their argument plus 1...

Here's a little demo. (I agree, the State docs could have nicer demos)

Play around with the code, read the haddocks, and it should make sense
eventually :)_

-- Don


import Control.Monad.State

--
-- the type for a 'global' 'variable'
--
data T = T { ref :: Int }

-- Run code with a single global 'ref', initialised to 0
main = evalStateT g $ T { ref = 0 }

-- set it to 10
g = do
printio g
putRef 10
printio modified state
f

-- read that ref, print it
f = do
r - getRef
printio r
return ()

getRef = gets ref

putRef x = modify $ \_ - T { ref = x }

printio :: Show a = a - StateT T IO ()
printio = liftIO . print


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Beginner: IORef constructor?

2006-12-01 Thread TJ

Donald:

This doesn't mean what you think it means :) In particular,
theGlobalVariable isn't a global variable, its a function that creates a
new IORef, initialised to []. So you create two new iorefs, once in
modify1, and again in modify2.


Indeed, it's not what I thought it was at all!

Bulat:

you may be interested in looking at
http://haskell.org/haskellwiki/IO_inside


Thanks for the link.

Udo:

Whatever you're trying to do right now, just forget that there are
variables in BASIC and do it without mutable state.


Alrighty. But I'd like to set the record straight that it was C++
which screwed up my mind forever ;)

Donald:

Note that there's no need for any mutable variables here. If this isn't
suitable, perhaps you could elaborate a bit on what effect you're trying
to achieve?


Yes I've come to the same conclusion. Thanks for the help, it really helps :)

TJ
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Beginner: IORef constructor?

2006-11-30 Thread TJ

First of all, sorry if this is a really silly question, but I couldn't
figure it out from experimenting in GHCi and from the GHC libraries
documentation (or Google).

Is there an IORef consturctor? Or is it just internal to the Data.IORef module?

I want a global variable, so I did the following:

--
module VirtualWorld where
 import Data.IORef
 theWorld = IORef [] -- This will be writeIORef'ed with a populated
list as the user modifies the world.
-

It doesn't work. GHCi says that the IORef constructor is not in scope.
I did a :module Data.IORef and then IORef [] and it still gives me
the same error.

I'm using GHC 6.6 on Windows.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe