Re: GHC 7.2.2 RC 1

2011-11-11 Thread Leon Smith
Chans are basically linked lists with the next pointer wrapped in an
MVar.   The source is actually very readable.   So yes,  it probably
is the same thing.

Best,
Leon

On Fri, Nov 11, 2011 at 11:37 AM, Nathan Howell
nathan.d.how...@gmail.com wrote:
 We're hitting something that looks similar with a Chan on 7.2.1, though they
 might be related..

 On Fri, Nov 11, 2011 at 4:52 AM, Simon Marlow marlo...@gmail.com wrote:

 Sorry, no.  That one has a workaround: define your own fixIO:

 fixIO :: (a - IO a) - IO a
 fixIO k = do
    m - newEmptyMVar
    ans - unsafeInterleaveIO (takeMVar m)
    result - k ans
    putMVar m result
    return result

 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


First class modules (was Existential Typing)

2001-10-29 Thread Leon Smith

On Wednesday 24 October 2001 12:32, Simon Peyton-Jones wrote:
 The elimination of stupid existential wrapper constructors
 is discussed in a bit more detail in the paper Mark and I wrote
 recently:

   First class modules for Haskell
http://research.microsoft.com/~simonpj/papers/first-class-modules/index.htm

I really like the thrust of the argument.  I definitely agree with the 
direction of the paper.  

Your paper mentioned the binder rule, which requires an explict type for 
modules that appear as arguments of functions.   I understand the need for 
this rule, and it is itself a reasonable restriction.   The problem is that 
in combination with a lack of subtyping between records, this implies that 
one must specify every field that can and must appear in a module.   I'm 
trying to decide if this is a reasonable restriction.  From my experiences 
with other systems such as Modula-3,  my instincts say no. 

Say you are implementing modules for Ints and Floats.  My old habits would 
lead to the following signatures:

record Int a =
(+), (*) :: a - a - a
div, mod :: a - a - a

record Float a  =
(+),(*):: a - a - a
(/) :: a - a - a
sin, cos :: a - a

Then, by my understanding, one could not write a function that mentions only 
(+) and (*) that is polymorphic in these modules.   You couldn't pass it both 
Int a and Float a, because the signatures are different, which seems to be an 
artificial restriction.   I think extending the system with some form of 
subtyping between records would be important for a usable system.   Your 
paper suggested that you are planning to do this.   Any thoughts on current 
ideas in this direction?

On the other hand, one could split each module up into several different 
pieces, such as Ring a, and Trig a.  This might be very reasonable, but 
it strikes me as being a little too fine-grained.

best,
leon


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Existential Typing (was Multi-parameter OOP)

2001-10-24 Thread Leon Smith

On Friday 19 October 2001 11:02, George Russell wrote:
 Recently I've been experimenting with a sort of OOP with GHC, [...]

I find your discussion rather intriguing, but I'm not sure I fully understand 
what you are trying to do.

Existential typing allows for what I would call dynamic dispatch, which 
allows for the dynamic lookup of class members (i.e. methods).  What you 
appear to be trying is something resembling dynamic typing.  Dynamic typing 
can be emulated using dynamic dispatch.  

If GHC had true existential typing, as opposed to just existential datatypes, 
you could reasonably code what I think you want like this:

class A a where
basicA :: Bool
nextA  :: a - (EX a'. A a' = a')
basicA = True
nextA  = id

data WrappedA = forall a. A a = WrappedA a

instance A WrappedA where
basicA = False
nextA (WrappedA a) = a

data A1 = A1

instance A A1

--... similarly for B ...

class AB a b where
   toBool :: a - b - Bool

instance (A a, B b) = AB a b where
   toBool a b 
  | (basicA :: a)  (basicB :: b) = True
  | (basicA :: a) || (basicB :: b) = False
  | otherwise = toBool (nextA a) (nextB b)


In this new setting, class AB seems a little silly.  You could simply get rid 
of it.  

Of course, GHC doesn't work this way.  Instead, you have to introduce a 
datatype StupidA to wrap your existential type in.   For the benefit of 
this new stupid datatype, you'll also need to change the type of basicA from 
(:: Bool) to (:: a - Bool).  This datatype also introduces unnecessary 
overhead, as you end up having chains of StupidA constructors that do 
essentially nothing.

You could look at my attached code if you really want to.  It has been beaten 
throughly with an ugly stick. 

From the purely denotational point of view of semantics,  I love existential 
typing.   I think this example really drives the point across that 
existential datatypes are not nearly as useful as existential typing.   I can 
think of several similar situations in actual code of mine.  However, using 
existential datatypes was overkill for the situation, and thus I opted for a 
different solution altogether.  

I don't understand all the implementation consequences of existential typing. 
Most importantly, how does existential typing effect the operational 
semantics?  Mercury has existential typing,  but then again, Mercury is newer 
and its design philosophy is far more ambitious.

best,
leon

class A a where
   basicA :: a - Bool
   nextA  :: a - StupidA
   basicA _ = True 
   nextA  a = StupidA a

data StupidA = forall a . A a = StupidA a

instance A StupidA where
   basicA (StupidA a) = basicA a 
   nextA  (StupidA a) = StupidA (nextA a)

data WrappedA = forall a . A a = WrappedA a 

instance A WrappedA where
   basicA _   = False
   nextA (WrappedA a) = StupidA a 

data A1 = A1

instance A A1 

class B b where
   basicB :: b - Bool
   nextB  :: b - StupidB
   basicB _ = True 
   nextB  b = StupidB b

data StupidB = forall b . B b = StupidB b

instance B StupidB where
   basicB (StupidB b) = basicB b
   nextB  (StupidB b) = StupidB (nextB b)

data WrappedB = forall b . B b = WrappedB b

instance B WrappedB where
   basicB _   = False
   nextB (WrappedB b) = StupidB b

data B1 = B1

instance B B1 


toBool :: (A a, B b) = a - b - Bool
toBool a b 
  | basicA a  basicB b = True
  | basicA a || basicB b = False
  | otherwise= toBool (nextA a) (nextB b)









main = return ()


Re: unsafePtrCompare, anybody?

2001-09-17 Thread Leon Smith

 I can't think of a way to use unsafePtrCompare safely :-)  The relative
 ordering of objects isn't guaranteed to be stable under GC.

 Cheers,
   Simon

Doh,  that would throw a monkey wrench into things, wouldn't it?   I know of 
compacting GC algorithms, but I didn't consider that GHC might be using one.  
At least I am now more enlightened on the inner workings of the magic beast...

I've considered many of the other implementation options, but as it isn't 
essential to the working of the compiler,  it hasn't been a priority yet.  It 
simply struck me that this would be a particularly quick and easy way to 
implement reasonably good atom tables, only requiring a newtype declaration 
and a few very simple function definitions.   

Thanks to Simon for saving me from reinventing the wheel.   The libraries 
mentioned here should prove to be quite useful.  

One's intuition would suggest that you could be safely implement mkAtom 
without wrapping it in a IO monad.   After all, at least at a abstract level, 
an atom table is referentially transparent.  The library documentation says 
that lack of side effects and environmental independance is sufficent to 
order for uses of unsafePerformIO to be safe.  Is there a exact (or at least 
better) criterion for safety?   

unsafePerformIO is used in the implementation of mkFastString, so how is 
it's side effects safe.   I experimented with unsafePerformIO with my Atom 
table, but I could not get tthe code to work properly.

best,
leon

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



unsafePtrCompare, anybody?

2001-09-15 Thread Leon Smith

I'm writing an atom table for a compiler/interpreter, and it would be really 
nice to use unsafePtrLT to implement tree-based finite maps.  

For clarification, my atom table consists  of these three functions: 

mkAtom :: String - IO Atom
show  :: Atom - String
(==)  :: Atom - Atom - Bool

such that   
mkAtom s = (return . show) == return s
and
mkAtom . show == return
and 
atom == atom'  =  show atom == show atom' 

mkAtom looks up each string in a table stored in an global variable, and 
returns the atom stored in the table if it is there.  Otherwise, it makes the 
string into an atom, inserts the atom into the table, and returns this new 
atom.

The point of all of this is that now string equality, when strings are made 
into atoms, is just pointer equality, which is available as 
IOExts.unsafePtrEq.

However, in this situation, pointer comparison is simply an arbitrary total 
order on the set of all atoms, which is all we need to implement finite maps 
based on search trees.  And of course, pointer comparisons are a much cheaper 
operation that actual string comparison.

Of course, the misuses of unsafePtrEq aren't nearly as heinous as those of 
unsafePtrCompare.   On the other hand, it might be next to impossible to 
effectively use unsafePtrCompare in cases that it isn't completely safe to 
use, whereas there are plently of situations where unsafePtrEq is semi-safe 
to use.

best,
leon

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Problems finding modules with GHC 5

2001-06-04 Thread Leon Smith

I'm having problems running programs that use modules found in
the hslibs libraries.  I've tried these with GHC 5.00.1 on both
a x86 Linux box on which I compiled GHC from source, and a Sparc 
box where I installed the precompiled binaries.

If I simply try to load my program (which uses MArray), I get:



$ ghci Main.hs
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 5.00.1, For Haskell
98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package std ... linking ... done.
ghc-5.00.1: can't find module `MArray'

-

If I try using the -i option, I get 

-

$ ghci -i/usr/local/lib/ghc-5.00.1/imports/lang/ Main.hs

...

Loading package std ... linking ... done.
ghc-5.00.1: panic! (the `impossible' happened, GHC version 5.00.1):
does not exist
Action: withFileStatus
Reason: No such file or directory

Please report it as a compiler bug to [EMAIL PROTECTED],
or http://sourceforge.net/projects/ghc/.

---

$ ghci -i/usr/local/build/ghc-5.00.1/hslibs/lang/ Main.hs

...

Loading package std ... linking ... done.
ghc-5.00.1: can't find module `PrelPrim'

Finally, if I then try adding the prelude  to the path, I get the same
panic.
If I try to compile my project with GHC, I get link errors.

best,
leon



If I try

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users