RE: Core questions

2009-02-02 Thread Simon Peyton-Jones
Matthijs

| However, there are two issues bothering me still. The first is that the
| Core types (in particular CoreExpr) are not instances of Show. They are
| instances of Outputable, which allows them to be pretty printed.
| However, this pretty printing is good to view the structure of the
| expression that the CoreExpr represents, but doesn't show the structure
| of the CoreExpr itself. For example, tuple construction is printed
| simply as (a, b), while the actual core expression is a nested
| application of two types, and a and b to the GHC.Tuple.(,) function
| (or datacon?). Also, the exact constructors used are not quite clear,

There's absolutely no reason why
CoreExpr
CoreBind
Type
should not be an instance of Show.  It'd take you 10 mins to make it so, with 
the aid of 'standalone deriving' (described in the GHC user manual).

There *is* a reason why TyCon and Class are not:
a TyCon
enumerates its DataCons
whose type mentions the TyCon

In short, the data structures are, by design, cyclic.  Printing one of these 
would take a long time.

But I bet you could get a long way with the three above, plus just printing the 
*name* of a TyCon or Class or Id.  Something like:
instance Show TyCon where
   show tc = showSDoc (ppr tc)



| My second question concerns typle construction. Since tuple types are
| not primitive types, but dependent types defined in various places
| (GHC.Tuple and Base IIRC), code working with tuples is not fundamentally
| different from code working with other (user defined) dependent types
| and thus not trivial to recognize. I've found that there are some
| predicate functions that can tell me if a type is a tuple type, but I've
| had no such luck for the actual tuple construction.

Well a tuple looks like (tdc ty1 ... tyn arg1 .. argn), where tdc is the data 
constructor for the tuple. So what you need is:

isTupleDataConId :: Id - Bool

It's easy to write

  isTupleDataConId id
| Just data_con - isDataConId_maybe id
= isTupleTyCon (dataConTyCon data_con)

I hope this is helpful

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


Re: ST monad and monad tranformers

2009-02-02 Thread Reid Barton
On Mon, Feb 02, 2009 at 06:03:15PM +0100, Josef Svenningsson wrote:
 Hi Tyson,
 
 I also needed something like this a while ago so I knocked up a really
 simple module and put it on hackage:
 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/STMonadTrans

Warning!  The STMonadTrans package uses State# nonlinearly, and as a
result, can violate referential transparency:

 import Control.Monad
 import Control.Monad.Trans
 import Control.Monad.ST.Trans
 
 data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving Show
 
 instance Monad Tree where
   return = Leaf
   Leaf a = k = k a
   Branch l r = k = Branch (l = k) (r = k)
 
 foo :: STT s Tree Integer
 foo = do
   x - newSTRef 0
   y - lift (Branch (Leaf 1) (Leaf 2))
   when (odd y) (writeSTRef x y)
   readSTRef x
 
 main = do
   print $ runST foo
   let Branch _ (Leaf x) = runST foo
   print x

prints

Branch (Leaf 1) (Leaf 1)
0

Evaluating the thunk in the left branch affects the value seen in the
right branch.  In general a monad transformer version of ST would need
to duplicate its state for each branch when used in conjunction with a
nondeterminism monad like Tree, which would make it not really
different from State, I think.

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


Re: ST monad and monad tranformers

2009-02-02 Thread Tyson Whitehead
On February 2, 2009 11:26:02 Tyson Whitehead wrote:
 The STT type above is a version of ST like the ReaderT, StateT, etc. types.

 newtype STT s m a = STT ( State# s - m (STTBox s a) )
 data STTBox s a = STTBox {-#UNPACK#-} !(State# s) {-#UNPACK#-} !a

 runSTT :: (Monad m) = (forall s. STT s m a) - m a
 runSTT m = case m of STT m' - do STTBox _ x - m' realWorld#
   return x

 instance Monad m = Monad (STT s m) where
 return x = STT $ \s - return $ STTBox s x
 (STT m) = k = STT $ \s - do STTBox s' x - m s
case k x of STT k' - k' s'

Of course, I forgot the method to actually use state threaded code

stToSTT :: Monad m = ST s a - STT s m a
stToSTT (ST m) = STT $ \s - case m s of (# s',x #) - return $ STTBox s' x

In re-reading my original email, I also thought I might not have been clear 
that I did write the instance methods (MonadCont, etc.), I just didn't include 
them as they would have made the email too lengthy.

Cheers!  -Tyson

PS:  Thanks for all the comments so far.


signature.asc
Description: This is a digitally signed message part.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Segmentation fault trying to build ghc 6.10.1 using macports, Mac OS X 10.5, PPC

2009-02-02 Thread Gregory Wright

Hi David,

On Feb 2, 2009, at 4:48 AM, Christian Maeder wrote:


David Menendez wrote:

I'm trying to upgrade GHC to 6.10.1 using macports on a PowerBook G4
running OS X 10.5.5. From what I can tell, I'm getting a segmentation
fault from cabal-bin.


On PPC leopard you need to update to XCode 3.1
http://hackage.haskell.org/trac/ghc/wiki/Building/MacOSX
http://hackage.haskell.org/trac/ghc/ticket/2887

HTH Christian



It would be very helpful to know if this solves the problem for you.   
I've had reports
of similar failures on 10.4, but have not been able to reproduce them  
on a ppc/10.4 machine

or a ppc/10.5 machine.

Even with Xcode 3.0, it seems as if not everyone gets tagged by the  
error.


Greg



This is possibly related to http://trac.macports.org/ticket/15142
and http://hackage.haskell.org/trac/ghc/ticket/2380.


cd extensible-exceptions 
/opt/local/var/macports/build/ 
_opt_local_var_macports_sources_rsync 
.macports.org_release_ports_lang_ghc/work/ghc-6.10.1/libraries/ 
cabal-bin
/opt/local/var/macports/build/ 
_opt_local_var_macports_sources_rsync 
.macports.org_release_ports_lang_ghc/work/ghc-bootstrap/bin/ghc
/opt/local/var/macports/build/ 
_opt_local_var_macports_sources_rsync 
.macports.org_release_ports_lang_ghc/work/ghc-6.10.1/libraries/ 
bootstrapping.conf

configure --distpref=dist-bootstrapping
--with-compiler=/opt/local/var/macports/build/ 
_opt_local_var_macports_sources_rsync 
.macports.org_release_ports_lang_ghc/work/ghc-bootstrap/bin/ghc
--with-hc-pkg=/opt/local/var/macports/build/ 
_opt_local_var_macports_sources_rsync 
.macports.org_release_ports_lang_ghc/work/ghc-bootstrap/bin/ghc-pkg
--package-db=/opt/local/var/macports/build/ 
_opt_local_var_macports_sources_rsync 
.macports.org_release_ports_lang_ghc/work/ghc-6.10.1/libraries/ 
bootstrapping.conf.tmp

/bin/sh: line 1: 19203 Segmentation fault
/opt/local/var/macports/build/ 
_opt_local_var_macports_sources_rsync 
.macports.org_release_ports_lang_ghc/work/ghc-6.10.1/libraries/ 
cabal-bin
/opt/local/var/macports/build/ 
_opt_local_var_macports_sources_rsync 
.macports.org_release_ports_lang_ghc/work/ghc-bootstrap/bin/ghc
/opt/local/var/macports/build/ 
_opt_local_var_macports_sources_rsync 
.macports.org_release_ports_lang_ghc/work/ghc-6.10.1/libraries/ 
bootstrapping.conf

configure --distpref=dist-bootstrapping
--with-compiler=/opt/local/var/macports/build/ 
_opt_local_var_macports_sources_rsync 
.macports.org_release_ports_lang_ghc/work/ghc-bootstrap/bin/ghc
--with-hc-pkg=/opt/local/var/macports/build/ 
_opt_local_var_macports_sources_rsync 
.macports.org_release_ports_lang_ghc/work/ghc-bootstrap/bin/ghc-pkg
--package-db=/opt/local/var/macports/build/ 
_opt_local_var_macports_sources_rsync 
.macports.org_release_ports_lang_ghc/work/ghc-6.10.1/libraries/ 
bootstrapping.conf.tmp

make[1]: *** [bootstrapping.conf] Error 139
make: *** [stage1] Error 2





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


Re: ST monad and monad tranformers

2009-02-02 Thread Josef Svenningsson
On Mon, Feb 2, 2009 at 8:50 PM, Reid Barton rwbar...@math.harvard.edu wrote:
 On Mon, Feb 02, 2009 at 06:03:15PM +0100, Josef Svenningsson wrote:
 Hi Tyson,

 I also needed something like this a while ago so I knocked up a really
 simple module and put it on hackage:
 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/STMonadTrans

 Warning!  The STMonadTrans package uses State# nonlinearly, and as a
 result, can violate referential transparency:

Indeed, thanks for pointing this out. I really should have a warning
sign on the package saying that it only works for certain monads.

Cheers,

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


Re: ST monad and monad tranformers

2009-02-02 Thread Josef Svenningsson
Hi Tyson,

I also needed something like this a while ago so I knocked up a really
simple module and put it on hackage:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/STMonadTrans

If you have any suggestions for improvement they are most welcome.
Patches even more so.

Josef

2009/2/2 Tyson Whitehead twhiteh...@gmail.com:
 I have a situation in which I believe I need a parameterizable version of the
 strict ST monad.  My computation type is StateT s' (STT s (ErrorT e m)) a
 (i.e., fails or succeeds and has an internal state involving a state thread).

 The STT type above is a version of ST like the ReaderT, StateT, etc. types.

 newtype STT s m a = STT ( State# s - m (STTBox s a) )
 data STTBox s a = STTBox {-#UNPACK#-} !(State# s) {-#UNPACK#-} !a

 (I'm guessing on the UNPACK paragmas here) with

 runSTT :: (Monad m) = (forall s. STT s m a) - m a
 runSTT m = case m of STT m' - do STTBox _ x - m' realWorld#
  return x

 (writing this as runSTT (STT m') = ... doesn't typecheck with ghc 6.8.2)

 instance Monad m = Monad (STT s m) where
return x = STT $ \s - return $ STTBox s x
(STT m) = k = STT $ \s - do STTBox s' x - m s
   case k x of STT k' - k' s'

 plus all the assorted instances for Functor, MonadPlus, MonadFix, MonadTrans,
 MonadReader, MonadState, etc.  For example,

 instance MonadWriter w m = MonadWriter w (STT s m) where
tell = lift . tell
listen (STT m) = STT $ \s - do (STTBox s' x,w) - listen $ m s
return $ STTBox s' (x,w)
pass   (STT m) = STT $ \s - pass $ do STTBox s' (x,f) - m s
   return (STTBox s' x,f)

 I was looking for any comments, wondering if there is a reason for this not
 existing in the library already, and what I should do in terms of paragmas and
 such for speed?  I see the GHC-ST file has a mix of INLINE and NOINLINE.

 http://www.haskell.org/ghc/dist/current/docs/libraries/base/src/GHC-ST.html

 In particular, return, =, , and runST are marked INLINE, but there is a
 regrettably delicate comment that goes with the runST method.  Also, what
 about the Functor, MonadPlus, MonadFix, MonadTrans, MonadReader, etc. methods?

 Thanks! -Tyson

 PS:  I would be happy to provide the whole works to be added to the library if
 it is something that should be there.

 ___
 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


Re: Core questions

2009-02-02 Thread Sean Leather
Hi Matthijs,

This is a shameless plug for EMGM, a library for generic programming that
we've been working on at Utrecht.

| However, there are two issues bothering me still. The first is that the
 | Core types (in particular CoreExpr) are not instances of Show. They are
 | instances of Outputable, which allows them to be pretty printed.
 | However, this pretty printing is good to view the structure of the
 | expression that the CoreExpr represents, but doesn't show the structure
 | of the CoreExpr itself. For example, tuple construction is printed
 | simply as (a, b), while the actual core expression is a nested
 | application of two types, and a and b to the GHC.Tuple.(,) function
 | (or datacon?). Also, the exact constructors used are not quite clear,

 There's absolutely no reason why
CoreExpr
CoreBind
Type
 should not be an instance of Show.  It'd take you 10 mins to make it so,
 with the aid of 'standalone deriving' (described in the GHC user manual).

 There *is* a reason why TyCon and Class are not:
a TyCon
enumerates its DataCons
whose type mentions the TyCon

 In short, the data structures are, by design, cyclic.  Printing one of
 these would take a long time.

 But I bet you could get a long way with the three above, plus just printing
 the *name* of a TyCon or Class or Id.  Something like:
instance Show TyCon where
   show tc = showSDoc (ppr tc)


Suppose you want to print a type with the exception of one constructor,
because it is mutually recursive with another or just prints out lots of
useless information. There are at least two ways to do it, one with EMGM,
and one with standalone deriving. I show both below.

 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE OverlappingInstances #-}
 {-# LANGUAGE UndecidableInstances #-}
 {-# LANGUAGE StandaloneDeriving #-}

 module Example where

 import qualified Generics.EMGM as G

 -

 data A = A0 Int  | A1 B
 data B = B0 Char | B1 A

 $(G.derive ''A)
 $(G.derive ''B)

 instance G.Rep G.Show B where
   rep = G.Show (\_ _ - f)
 where
   f (B0 c) = showString (B0  . showChar c . showString )
   f (B1 _) = showString (B1 some A)

 valAB = A1 (B1 (A0 37))
 showAB = G.show valAB

 -

 data C = C0 Int  | C1 D
 data D = D0 Char | D1 C

 deriving instance Show C
 instance Show D where
   showsPrec _ = f
 where
   f (D0 c) = showString (D0  . showChar c . showString )
   f (D1 _) = showString (D1 some C)

 valCD = C1 (D1 (C0 37))
 showCD = show valCD

 -

The first one uses EMGM's Template Haskell-based derive function to generate
the type representation. I then give an overriding instance for the generic
Show function (where G.Show is a newtype used for all show/shows/showsPrec
generic functions). So, the constructor B1 will not print out the value of
its A-type argument.

The second uses standalone deriving and a handwritten instance for D that
does the same thing as the first solution did for B.

What's the difference? Well, between these instances of G.Show and Show,
there's not much. However, the EMGM approach gives you access to a lot of
other generic functions including Read, Crush, Collect, etc. See the
documentation for all of them [1].

One function you may be able to take advantage of is 'collect', perhaps to
collect the B values in valAB.

*Example G.show (G.collect valAB :: [B])
[(B1 some A)]

Moral of the story: you can do it either way, but EMGM gives you a lot
extra.

Apologies for the self-promotion, but we're looking for people who might
want to use EMGM. ;) If you have feedback, let us know! [2]

Regards,
Sean

[1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/emgm
[2] http://www.cs.uu.nl/wiki/GenericProgramming/EMGM
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Segmentation fault trying to build ghc 6.10.1 using macports, Mac OS X 10.5, PPC

2009-02-02 Thread Christian Maeder
David Menendez wrote:
 I'm trying to upgrade GHC to 6.10.1 using macports on a PowerBook G4
 running OS X 10.5.5. From what I can tell, I'm getting a segmentation
 fault from cabal-bin.

On PPC leopard you need to update to XCode 3.1
http://hackage.haskell.org/trac/ghc/wiki/Building/MacOSX
http://hackage.haskell.org/trac/ghc/ticket/2887

HTH Christian

 
 This is possibly related to http://trac.macports.org/ticket/15142
 and http://hackage.haskell.org/trac/ghc/ticket/2380.
 
 
 cd extensible-exceptions 
 /opt/local/var/macports/build/_opt_local_var_macports_sources_rsync.macports.org_release_ports_lang_ghc/work/ghc-6.10.1/libraries/cabal-bin
 /opt/local/var/macports/build/_opt_local_var_macports_sources_rsync.macports.org_release_ports_lang_ghc/work/ghc-bootstrap/bin/ghc
 /opt/local/var/macports/build/_opt_local_var_macports_sources_rsync.macports.org_release_ports_lang_ghc/work/ghc-6.10.1/libraries/bootstrapping.conf
 configure --distpref=dist-bootstrapping
 --with-compiler=/opt/local/var/macports/build/_opt_local_var_macports_sources_rsync.macports.org_release_ports_lang_ghc/work/ghc-bootstrap/bin/ghc
 --with-hc-pkg=/opt/local/var/macports/build/_opt_local_var_macports_sources_rsync.macports.org_release_ports_lang_ghc/work/ghc-bootstrap/bin/ghc-pkg
 --package-db=/opt/local/var/macports/build/_opt_local_var_macports_sources_rsync.macports.org_release_ports_lang_ghc/work/ghc-6.10.1/libraries/bootstrapping.conf.tmp
 /bin/sh: line 1: 19203 Segmentation fault
 /opt/local/var/macports/build/_opt_local_var_macports_sources_rsync.macports.org_release_ports_lang_ghc/work/ghc-6.10.1/libraries/cabal-bin
 /opt/local/var/macports/build/_opt_local_var_macports_sources_rsync.macports.org_release_ports_lang_ghc/work/ghc-bootstrap/bin/ghc
 /opt/local/var/macports/build/_opt_local_var_macports_sources_rsync.macports.org_release_ports_lang_ghc/work/ghc-6.10.1/libraries/bootstrapping.conf
 configure --distpref=dist-bootstrapping
 --with-compiler=/opt/local/var/macports/build/_opt_local_var_macports_sources_rsync.macports.org_release_ports_lang_ghc/work/ghc-bootstrap/bin/ghc
 --with-hc-pkg=/opt/local/var/macports/build/_opt_local_var_macports_sources_rsync.macports.org_release_ports_lang_ghc/work/ghc-bootstrap/bin/ghc-pkg
 --package-db=/opt/local/var/macports/build/_opt_local_var_macports_sources_rsync.macports.org_release_ports_lang_ghc/work/ghc-6.10.1/libraries/bootstrapping.conf.tmp
 make[1]: *** [bootstrapping.conf] Error 139
 make: *** [stage1] Error 2
 
 
 
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Surprised to type in (1+n) as a type index!

2009-02-02 Thread Ahn, Ki Yung
I was writing a document in lhs form and typed in something like this.

 data Exp n where
   Atom :: Exp ()
   List :: [Exp n] - Exp (1+n)

I wasn't expecting this to actually load up on GHCi,
but when I load this up with the magical -fglasgow-exts option,
it just worked !!!

*Main :t Atom
Atom :: Exp ()
*Main :t List [Atom, Atom]
List [Atom, Atom] :: forall (+ :: * - * - *).
 Exp (+ GHC.Generics.Unit ())

It seems GHC is treating + as just a type variable for binary type
constructor of kind * - * - *.

*Main :t List [Atom, Atom]
List [Atom, Atom] :: forall (+ :: * - * - *).
 Exp (+ GHC.Generics.Unit ())
*Main :t List [List [Atom, Atom], List []]
List [List [Atom, Atom], List []] :: forall (+ :: * - * - *)
(+1 :: * - * - *).
 Exp (+1 GHC.Generics.Unit (+
GHC.Generics.Unit ()))
*Main :t List [List [List [Atom, Atom], List []]]
List [List [List [Atom, Atom], List []]] :: forall (+ :: *
 - *
 - *)
   (+1 :: * - * - *)
   (+2 :: * - * - *).
Exp
  (+2 GHC.Generics.Unit (+1
GHC.Generics.Unit (+ GHC.Generics.Unit (

But, what is this GHC.Generics.Unit thing and where is this documented?

Thanks,

Ahn, Ki Yung

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