Re: testing 6.12.2-pre

2010-04-15 Thread Matthias Kilian
On Wed, Apr 14, 2010 at 08:44:29PM +0200, Matthias Kilian wrote:
 module Main(main) where
 
 import System.IO
 import System.Process
 
 main = do
   hin - openBinaryFile /dev/null ReadMode
   hp - runProcess /bin/ls [-l] Nothing Nothing (Just hin) 
 Nothing Nothing
   r - waitForProcess hp
   print r
 
 
 IF I run this on OpenBSD (amd64), I get
 
 foo: /bin/ls: runProcess: unsupported operation (Operation not supported by 
 device)

I found it. I'll send a patch as soon as I've tested the fix. The
neat thing is that darcs send probably doesn't work without the fix

;-)

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


interaction of GADTs and data families: a bug?

2010-04-15 Thread Sebastian Fischer

Dear GHC experts,

Certain behaviour when using

{-# LANGUAGE GADTs, TypeFamilies #-}

surprises me. The following is accepted by GHC 6.12.1:

data GADT a where
  BoolGADT :: GADT Bool

foo :: GADT a - a - Int
foo BoolGADT True = 42

But the following is not:

data family DataFam a
data instance DataFam Bool where
  BoolDataFam :: DataFam Bool

fff :: DataFam a - a - Int
fff BoolDataFam True = 42

GHC 6.12.1 throws the following error (GHC 6.10.4 panics):

 Couldn't match expected type `a' against inferred type `Bool'
   `a' is a rigid type variable bound by
   the type signature for `fff' at gadtDataFam.hs:13:19
 In the pattern: BoolDataFam
 In the definition of `fff': fff BoolDataFam True = 42

I expect that `fff` should be accepted just like `foo`. Do I  
expect too much?


Cheers,
Sebastian

--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



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


Re: interaction of GADTs and data families: a bug?

2010-04-15 Thread José Pedro Magalhães
Hi Sebastian,

Is this perhaps another instance of #3851?
http://hackage.haskell.org/trac/ghc/ticket/3851


Cheers,
Pedro

On Thu, Apr 15, 2010 at 14:10, Sebastian Fischer 
s...@informatik.uni-kiel.de wrote:

 Dear GHC experts,

 Certain behaviour when using

{-# LANGUAGE GADTs, TypeFamilies #-}

 surprises me. The following is accepted by GHC 6.12.1:

data GADT a where
  BoolGADT :: GADT Bool

foo :: GADT a - a - Int
foo BoolGADT True = 42

 But the following is not:

data family DataFam a
data instance DataFam Bool where
  BoolDataFam :: DataFam Bool

fff :: DataFam a - a - Int
fff BoolDataFam True = 42

 GHC 6.12.1 throws the following error (GHC 6.10.4 panics):

 Couldn't match expected type `a' against inferred type `Bool'
   `a' is a rigid type variable bound by
   the type signature for `fff' at gadtDataFam.hs:13:19
 In the pattern: BoolDataFam
 In the definition of `fff': fff BoolDataFam True = 42

 I expect that `fff` should be accepted just like `foo`. Do I expect too
 much?

 Cheers,
 Sebastian

 --
 Underestimating the novelty of the future is a time-honored tradition.
 (D.G.)



 ___
 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: interaction of GADTs and data families: a bug?

2010-04-15 Thread Sebastian Fischer

Is this perhaps another instance of #3851? 
http://hackage.haskell.org/trac/ghc/ticket/3851


Honestly: I don't know.

My example is different from the one shown in #3851 in that it also  
does not work in GHC 6.10 (which even panics instead of giving the  
error 6.12 gives) and in that it uses a data family, not a type family.


Whether or not it is the same awkward interaction that causes this  
behaviour is beyond my expertise.


Cheers,
Sebastian

--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



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


Re: interaction of GADTs and data families: a bug?

2010-04-15 Thread José Pedro Magalhães
Hi Sebastian,

On Thu, Apr 15, 2010 at 15:08, Sebastian Fischer 
s...@informatik.uni-kiel.de wrote:

 Is this perhaps another instance of #3851?
 http://hackage.haskell.org/trac/ghc/ticket/3851


 Honestly: I don't know.

 My example is different from the one shown in #3851 in that it also does
 not work in GHC 6.10 (which even panics instead of giving the error 6.12
 gives) and in that it uses a data family, not a type family.


The example in the ticket uses type families, but later in the comments I
show an example with data families which fails on both 6.10.4 and 6.12.1.


Cheers,
Pedro



 Whether or not it is the same awkward interaction that causes this
 behaviour is beyond my expertise.

 Cheers,
 Sebastian

   --
 Underestimating the novelty of the future is a time-honored tradition.
 (D.G.)




 ___
 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: interaction of GADTs and data families: a bug?

2010-04-15 Thread Sebastian Fischer
 but later in the comments I show an example with data families  
which fails on both 6.10.4 and 6.12.1.



Ah, I think I misinterpreted your comment, when I read it for the  
first time. Thanks for pointing me at it again. But I still don't see  
whether or not the two examples are related. At least the error is  
different.


Sebastian

--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



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


RE: interaction of GADTs and data families: a bug?

2010-04-15 Thread Sittampalam, Ganesh
Sebastian Fischer wrote:
 Dear GHC experts,
 
 Certain behaviour when using
 
  {-# LANGUAGE GADTs, TypeFamilies #-}
 
 surprises me. The following is accepted by GHC 6.12.1:
 
  data GADT a where
BoolGADT :: GADT Bool
 
  foo :: GADT a - a - Int
  foo BoolGADT True = 42
 
 But the following is not:
 
  data family DataFam a
  data instance DataFam Bool where
BoolDataFam :: DataFam Bool
 
  fff :: DataFam a - a - Int
  fff BoolDataFam True = 42
 
 GHC 6.12.1 throws the following error (GHC 6.10.4 panics):
 
   Couldn't match expected type `a' against inferred type `Bool'
 `a' is a rigid type variable bound by
 the type signature for `fff' at gadtDataFam.hs:13:19
   In the pattern: BoolDataFam
   In the definition of `fff': fff BoolDataFam True = 42
 
 I expect that `fff` should be accepted just like `foo`. Do I
 expect too much?

I think you expect too much. You just don't get type refinement with
type or data families. The function you wrote is similar to this code
that doesn't use families at all:

fffuuu :: Maybe a - a - Int
fffuuu (Just True) True = 42

and we wouldn't expect that to work because Haskell in general doesn't
have the runtime type match that would be required to handle it.

With GADTs, the specific choice of constructor is what gives you the
type matching functionality.

Cheers,

Ganesh


=== 
Please access the attached hyperlink for an important electronic communications 
disclaimer: 
http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html 
=== 

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


Re: interaction of GADTs and data families: a bug?

2010-04-15 Thread Dan Doel
On Thursday 15 April 2010 8:10:42 am Sebastian Fischer wrote:
 Dear GHC experts,
 
 Certain behaviour when using
 
  {-# LANGUAGE GADTs, TypeFamilies #-}
 
 surprises me. The following is accepted by GHC 6.12.1:
 
  data GADT a where
BoolGADT :: GADT Bool
 
  foo :: GADT a - a - Int
  foo BoolGADT True = 42
 
 But the following is not:
 
  data family DataFam a
  data instance DataFam Bool where
BoolDataFam :: DataFam Bool
 
  fff :: DataFam a - a - Int
  fff BoolDataFam True = 42
 
 GHC 6.12.1 throws the following error (GHC 6.10.4 panics):
 
   Couldn't match expected type `a' against inferred type `Bool'
 `a' is a rigid type variable bound by
 the type signature for `fff' at gadtDataFam.hs:13:19
   In the pattern: BoolDataFam
   In the definition of `fff': fff BoolDataFam True = 42
 
 I expect that `fff` should be accepted just like `foo`. Do I
 expect too much?

I don't really see how your example could be expected to work. I can only 
conclude that DataFam Bool is not a GADT, it's an ADT written with GADT 
syntax.

Data/type families allow for definition of a family of types by case analysis 
on one or more indices. To define functions polymorphic in those indices, one 
must first do case analysis on those indices (via classes or a separate GADT 
parameter), or work at a specific index. Presumably one can do the following:

  data family Fam a :: * - *
  data instance Fam Bool :: * - * where
BoolInt :: Fam Bool Int

where Fam Bool a is itself a GADT with index a. But we can also write an 
instance:

  data instance Fam Int a = CInt a a

which can also be written:

  data instance Fam Int a where
CInt :: a - a - Fam Int a

but the specificity of Int comes not from CInt being a GADT constructor, but 
because we are specifying what the type Fam Int is. And we cannot expect to 
define a function:

  foo :: Fam a b - Int
  foo (CInt x y) = 32
  foo BoolInt= 42

simply because type/data families do not work that way. The index of the 
family needs to be known before we can know which constructors we are able to 
match against. We could, however, write:

  foo :: Fam Bool b - b
  foo BoolInt = 42

which shows that once we know that we are working with Fam Bool b, matching 
can refine b.

I haven't used this feature yet, so perhaps an expert will correct me. But 
that is my interpretation of the situation.

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


Re: interaction of GADTs and data families: a bug?

2010-04-15 Thread Sebastian Fischer

With GADTs, the specific choice of constructor is what gives you the
type matching functionality.


My intention was to use a GADT as data family instance (hence, I wrote  
it in GADT style and it was accepted as such). Can't GADTs be used as  
data family instances?


Sebastian

--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



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


RE: interaction of GADTs and data families: a bug?

2010-04-15 Thread Sittampalam, Ganesh
Sebastian Fischer wrote:
 With GADTs, the specific choice of constructor is what gives you the
 type matching functionality.
 
 My intention was to use a GADT as data family instance (hence, I
 wrote it in GADT style and it was accepted as such). Can't GADTs be
 used as data family instances?  

I'm not aware of any restriction there, but that's not the issue here.

You were trying to choose between different top-level types (which
happen to be instances of the same family) by their constructors. GADTs
allow you to choose between different constructors of the *same*
top-level type.

If DataFam Bool had multiple constructors, you could choose between them
in fff. But fff would have to have type DataFam Bool - Bool -
Int (as is necessary with your originally posted code).

Ganesh

=== 
Please access the attached hyperlink for an important electronic communications 
disclaimer: 
http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html 
=== 

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


Re: interaction of GADTs and data families: a bug?

2010-04-15 Thread Sebastian Fischer

On Apr 15, 2010, at 3:44 PM, Sittampalam, Ganesh wrote:


You were trying to choose between different top-level types (which
happen to be instances of the same family) by their constructors.


That is true. I was trying to emulate an open data type such that I  
can write


-- does not work
fff :: DataFam a - a - Int
fff BoolDataFam True = 42
fff CharDataFam 'c'  = 43

But apparently such thing is only possible with a (closed) GADT:

data GADT a where
  BoolGADT :: GADT Bool
  CharGADT :: GADT Char

-- does work
foo :: GADT a - a - Int
foo BoolGADT True = 42
foo CharGADT 'c'  = 43

I was hoping to achieve the same without having a single closed type.

On Apr 15, 2010, at 3:29 PM, Dan Doel wrote:


DataFam Bool is not a GADT, it's an ADT written with GADT syntax.


Yes, that was the main source of my confusion.

Thank you both for clarifying!

Sebastian


--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



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


Re: Unicode alternative for '..' (ticket #3894)

2010-04-15 Thread Jason Dusek
  I think the baseline ellipsis makes much more sense; it's
  hard to see how the midline ellipsis was chosen.

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


Re: Unicode alternative for '..' (ticket #3894)

2010-04-15 Thread Yitzchak Gale
My opinion is that we should either use TWO DOT LEADER,
or just leave it as it is now, two FULL STOP characters.

Two dots indicating a range is not the same symbol
as a three dot ellipsis.

Traditional non-Unicode Haskell will continue to be
around for a long time to come. It would be very
confusing to have two different visual glyphs for
this symbol.

I don't think there is any semantic problem with using
TWO DOT LEADER here. All three of the characters
ONE DOT LEADER, TWO DOT LEADER, and HORIZONTAL
ELLIPSIS are legacy characters from Xerox's XCCS.
There, the characters they come from were used for forming
dot leaders, e.g., in a table of contents. Using them that way
in Unicode is considered incorrect unless they represent text
that was originally encoded in XCCS; in Unicode, one does
not form dot leaders using those characters. However, other
new uses are considered legitimate. For example, HORIZONTAL
ELLIPSIS can be used for fonts that have a special ellipsis glyph,
and ONE DOT LEADER represents mijaket in Armenian encodings.
So I don't see any reason why we can't use TWO DOT LEADER to
represent the two-dot range symbol.

The above analysis is based in part upon a discussion of these
characters on the Unicode list in 2003:

http://www.mail-archive.com/unic...@unicode.org/msg16285.html

The author of that particular message, Kenneth Whistler, is
of the opinion that two dots expressing a range as in [0..1]
should be represented in Unicode as two FULL STOP characters,
as we do now in Haskell. Others in that thread - whom
Mr. Whistler seems to feel are less expert than himself
regarding Unicode - think that TWO DOT LEADER is appropriate.
No one considers replacing two-dot ranges with HORIZONTAL
ELLIPSIS.

If we can't find a Unicode character that everyone agrees upon,
I also don't see any problem with leaving it as two FULL STOP
characters.

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


Re: Unicode alternative for '..' (ticket #3894)

2010-04-15 Thread Roel van Dijk
That is very interesting. I didn't know the history of those characters.

 If we can't find a Unicode character that everyone agrees upon,
 I also don't see any problem with leaving it as two FULL STOP
 characters.

I agree. I don't like the current Unicode variant for .., therefore
I suggested an alternative. But I didn't consider removing it
altogether. It is an interesting idea.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: FFI calls: is it possible to allocate a small memory block on a stack?

2010-04-15 Thread Denys Rtveliashvili
 While alloca is not as cheap as, say, C's alloca, you should find that 
 it is much quicker than C's malloc.  I'm sure there's room for 
 optimisation if it's critical for you.  There may well be low-hanging 
 fruit: take a look at the Core for alloca.
 
 The problem with using the stack is that alloca needs to allocate 
 non-movable memory, and in GHC thread stacks are movable.
 
 Cheers,
   Simon


Thank you for reply.

I think I have had a few wrong assumptions. One of them is that stack is
non-movable. Of course, for this purpose I need a non-movable region and
a pinned array on a heap is probably the only choice.
Also, I was hoping it is possible to use the low-level stack (the one
which is being used when instructions such as push and pop are
executed), but I guess it is not possible in case of GHC-generated code.

As for the performance of alloca, I though it would be faster than
malloc. However, in a simple test I have just written it is actually
slower. The test allocates 16-bytes arrays and immediately de-allocates
them. This operation is repeated 10 times. On my computer the C
program takes 27 seconds to complete while Haskell version takes about
41.


#include stdlib.h

int main (int argc, char **argv) {
for(long i = 0; i  10; i ++) {
free(malloc(16));
}
}

module Main where

import Control.Monad
import Foreign.Storable
import Foreign.Marshal.Alloc
import Foreign.Ptr

data Data = Data
instance Storable Data where
  sizeOf _ = 16
  alignment _ = 16
  peek _ = return Data
  poke _ _ = return ()

main = sequence_ $ replicate 10 $ alloca $ \ptr -
  if (nullPtr::Ptr Data) == ptr then fail Can't be else return 


I would gladly take a look at the Core of alloca. But frankly, I am
not sure how to tell ghc to show me that. With the help of -ddump-simpl
and -fext-core I can make it show me the Core, but it does not have the
body of the alloca itself, just a call to it. And when I look at C--
source with the help of -ddump-cmm the source is transformed too much
already to tell where alloca is.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Advice on Multiple GHC installations

2010-04-15 Thread Bradford Larsen
Many choices were suggested!  For now, I have decided to go with stow.
 I installed 3 versions of GHC in /usr/local/stow, and installed
cabal-install locally (i.e. to my home directory), built with ghc
6.12.1.  I'm not sure that this is the best way to go about this, but
it's what I'm working with for now.  I experimented a little bit, and
switching between default ghc versions seems to work, not breaking my
installation of cabal-install in my home directory.

I seriously considered the simpler `manual symlink' approach, or even
just installing in sequence to /usr/local 6.8.3, 6.10.4, and 6.12.1.
These alternatives could both permit having several versions of ghc in
my PATH simultaneously (e.g., /usr/local/bin/ghc-6.10.4 and
/usr/local/bin/ghc-6.12.1).  With stow, only the currently selected
`installed' ghc binaries will show up in /usr/local/bin.

Thanks,
Brad

On Tue, Apr 13, 2010 at 11:30 AM, Nils Anders Danielsson
n...@cs.nott.ac.uk wrote:
 On 2010-04-13 15:08, Dave Bayer wrote:

 Why not just use symbolic links?

 When using stow I am just using symbolic links (and directories), except
 that I don't need to create them all manually, and I can remove all of
 them with a single command. I don't need to modify my PATH.

 I only believe in scattering program parts through
 /usr/local/[bin,lib,doc] if I believe they will work, will never need
 upgrading for the life of my OS [...]

 When using stow you can easily uninstall things: just use stow -D to
 remove the symbolic links (and directories which only contain such
 links), and then you can delete the single directory which contains all
 the files.

 --
 /NAD
 ___
 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: interaction of GADTs and data families: a bug?

2010-04-15 Thread Simon Peyton-Jones
|  My intention was to use a GADT as data family instance (hence, I
|  wrote it in GADT style and it was accepted as such). Can't GADTs be
|  used as data family instances?
| 
| I'm not aware of any restriction there, but that's not the issue here.
| 
| You were trying to choose between different top-level types (which
| happen to be instances of the same family) by their constructors. GADTs
| allow you to choose between different constructors of the *same*
| top-level type.
| 
| If DataFam Bool had multiple constructors, you could choose between them
| in fff. But fff would have to have type DataFam Bool - Bool -
| Int (as is necessary with your originally posted code).

Ganesh and Dan are exactly right.  You can certainly have a data family 
instance that it itself a GADT:

data family T a b
data instance T Int b where
 Foo :: T Int Bool
  Bar :: T Int Char
data instance T Char b where 

And indeed matching on a (T Int b) can refine the b:

f :: T Int b - b
f Foo = True
f Bra = 'c'

But (T Int b) and (T Char b) are distinct data types, and do not share 
constructors.

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