Re: [Haskell-cafe] type families and type signatures

2008-04-09 Thread Martin Sulzmann
Manuel said earlier that the source of the problem here is foo's ambiguous type signature (I'm switching back to the original, simplified example). Type checking with ambiguous type signatures is hard because the type checker has to guess types and this guessing step may lead to too many

RE: [Haskell-cafe] type families and type signatures

2008-04-09 Thread Sittampalam, Ganesh
OK, thanks. I think I'm finally understanding :-) Cheers, Ganesh -Original Message- From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Martin Sulzmann Sent: 09 April 2008 07:21 To: Ganesh Sittampalam Cc: Manuel M T Chakravarty; haskell-cafe@haskell.org Subject: Re:

Re: [Haskell-cafe] type families and type signatures

2008-04-09 Thread Lennart Augustsson
Let's look at this example from a higher level. Haskell is a language which allows you to write type signatures for functions, and even encourages you to do it. Sometimes you even have to do it. Any language feature that stops me from writing a type signature is in my opinion broken. TFs as

Re: [Haskell-cafe] type families and type signatures

2008-04-09 Thread Martin Sulzmann
I think it's not fair to say TFs as implemented in GHC are broken. Fine, they are situations where the current implementation is overly conservative. The point is that the GHC type checker relies on automatic inference. Hence, there'll always be cases where certain reasonable type signatures

Re: [Haskell-cafe] type families and type signatures

2008-04-09 Thread Martin Sulzmann
Claus Reinke wrote: type family Id a type instance Id Int = Int foo :: Id a - Id a foo = id n foo' :: Id a - Id a foo' = foo type function notation is slightly misleading, as it presents qualified polymorphic types in a form usually reserved for unqualified polymorphic types. rewriting

Re: [Haskell-cafe] type families and type signatures

2008-04-09 Thread Claus Reinke
The point is that the GHC type checker relies on automatic inference. Hence, there'll always be cases where certain reasonable type signatures are rejected. .. To conclude, any system with automatic inference will necessary reject certain type signatures/instances in order to guarantee

Re: [Haskell-cafe] Re: type families and type signatures

2008-04-09 Thread Tom Schrijvers
However, I have this feeling that bar :: forall a . Id a - String with a type family Id *is* parametric in the sense that no matter what a is, the result always has to be the same. Intuitively, that's because we may not pattern match on the branch of a definition like type instance Id

Re: [Haskell-cafe] instance Monad m = Functor m

2008-04-09 Thread Hans Aberg
On 9 Apr 2008, at 11:26, Jules Bean wrote: Using 'hugs -98', I noticed it accepts: instance Monad m = Functor m where fmap f x = x = return.f Has this been considered (say) as a part of the upcoming Haskell Prime? This forbids any Functors which are not monads. Unless you allow

[Haskell-cafe] Re: type families and type signatures

2008-04-09 Thread apfelmus
Manuel M T Chakravarty wrote: apfelmus: Manuel M T Chakravarty wrote: Let's alpha-rename the signatures and use explicit foralls for clarity: foo :: forall a. Id a - Id a foo' :: forall b. Id b - Id b GHC will try to match (Id a) against (Id b). As Id is a type synonym family, it would

Re: [Haskell-cafe] type families and type signatures

2008-04-09 Thread Martin Sulzmann
Claus Reinke wrote: The point is that the GHC type checker relies on automatic inference. Hence, there'll always be cases where certain reasonable type signatures are rejected. .. To conclude, any system with automatic inference will necessary reject certain type signatures/instances in

Re: [Haskell-cafe] instance Monad m = Functor m

2008-04-09 Thread Jules Bean
Hans Aberg wrote: Using 'hugs -98', I noticed it accepts: instance Monad m = Functor m where fmap f x = x = return.f Has this been considered (say) as a part of the upcoming Haskell Prime? This forbids any Functors which are not monads. Unless you allow overlapping instances (which of

Re: [Haskell-cafe] type families and type signatures

2008-04-09 Thread Claus Reinke
type family Id a type instance Id Int = Int foo :: Id a - Id a foo = id n foo' :: Id a - Id a foo' = foo type function notation is slightly misleading, as it presents qualified polymorphic types in a form usually reserved for unqualified polymorphic types. rewriting foo's type helped me

Re: [Haskell-cafe] instance Monad m = Functor m

2008-04-09 Thread Henning Thielemann
On Wed, 9 Apr 2008, Hans Aberg wrote: I don't know if it is possible to extend the syntax this way, but it would be closer to math usage. And one would avoid duplicate definitions just to indicate different operator names, like: class AdditiveMonoid a where o :: a (+) :: a - a - a as it

[Haskell-cafe] Lock-Free Data Structures using STMs in Haskell

2008-04-09 Thread Pete Kazmier
I recently read the STM paper on lock-free data structures [1] which I found very informative in my quest to learn how to use STM. However, there are a few things I do not fully understand and was hoping someone might be able to explain further. In the STM version of the ArrayBlockingQueue, the

Re: [Haskell-cafe] instance Monad m = Functor m

2008-04-09 Thread Hans Aberg
On 9 Apr 2008, at 15:23, Henning Thielemann wrote: I don't know if it is possible to extend the syntax this way, but it would be closer to math usage. And one would avoid duplicate definitions just to indicate different operator names, like: class AdditiveMonoid a where o :: a (+) :: a -

Re: [Haskell-cafe] instance Monad m = Functor m

2008-04-09 Thread Henning Thielemann
On Wed, 9 Apr 2008, Hans Aberg wrote: Different names result in different operator hierarchies. So a class like class Monoid (a; unit, mult) where unit :: a mult :: a - a - a must have an instantiation that specifies the names of the operators. In particular, one will need a class

Re: [Haskell-cafe] instance Monad m = Functor m

2008-04-09 Thread Hans Aberg
On 9 Apr 2008, at 15:23, Henning Thielemann wrote: I also recognized that problem in the past, but didn't know how to solve it. In Haskell 98, methods are resolved using the types of the operands. How would the compiler find out which implementation of (+) to choose for an expression like

Re: [Haskell-cafe] instance Monad m = Functor m

2008-04-09 Thread Hans Aberg
On 9 Apr 2008, at 16:26, Henning Thielemann wrote: I think a classical example are number sequences which can be considered as rings in two ways: 1. elementwise multiplication 2. convolution and you have some function which invokes the ring multiplication f :: Ring a = a - a and a

Re: [Haskell-cafe] instance Monad m = Functor m

2008-04-09 Thread Hans Aberg
On 9 Apr 2008, at 16:26, Henning Thielemann wrote: 1. elementwise multiplication 2. convolution and you have some function which invokes the ring multiplication f :: Ring a = a - a and a concrete sequence x :: Sequence Integer what multiplication (elementwise or convolution) shall be used

Re: [Haskell-cafe] instance Monad m = Functor m

2008-04-09 Thread Henning Thielemann
On Wed, 9 Apr 2008, Hans Aberg wrote: On 9 Apr 2008, at 16:26, Henning Thielemann wrote: 1. elementwise multiplication 2. convolution and you have some function which invokes the ring multiplication f :: Ring a = a - a and a concrete sequence x :: Sequence Integer what multiplication

Re: [Haskell-cafe] instance Monad m = Functor m

2008-04-09 Thread Hans Aberg
On 9 Apr 2008, at 17:49, Henning Thielemann wrote: Additionally I see the problem, that we put more interpretation into standard symbols by convention. Programming is not only about the most general formulation of an algorithm but also about error detection. E.g. you cannot compare complex

Re: [Haskell-cafe] type families and type signatures

2008-04-09 Thread Lennart Augustsson
On Wed, Apr 9, 2008 at 8:53 AM, Martin Sulzmann [EMAIL PROTECTED] wrote: Lennart, you said (It's also pretty easy to fix the problem.) What do you mean? Easy to fix the type checker, or easy to fix the program by inserting annotations to guide the type checker? Martin I'm referring

Re: [Haskell-cafe] instance Monad m = Functor m

2008-04-09 Thread Hans Aberg
On 9 Apr 2008, at 17:49, Henning Thielemann wrote: Also (2*5 == 7) would surprise people, if (*) is the symbol for a general group operation, and we want to use it for the additive group of integers. One might resolve the Num binding of (+) problem by putting all operators into an

Re: [Haskell-cafe] Lock-Free Data Structures using STMs in Haskell

2008-04-09 Thread Ariel J. Birnbaum
decPair v1 v1 :: TVar Int - TVar Int - IO () decPair v1 v2 = atomically (decT v1 `orElse` decT v2) Will this actually compile? I was under the impression that 'orElse' could only combine STM types, not IO () types. The type of atomically is STM a - IO a. But orElse :: STM a - STM

Re: [Haskell-cafe] What's the difference?

2008-04-09 Thread Ariel J. Birnbaum
For me, the word implies is too tied in my brain to an arrow symbol to be useful to me in keeping the implications straight. Pun implied? -- Ariel J. Birnbaum ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] problems building hpodder

2008-04-09 Thread Duncan Coutts
On Tue, 2008-04-08 at 15:43 -0500, John Goerzen wrote: On Tue April 8 2008 3:21:34 pm Karl Hasselström wrote: http://www.haskell.org/haskellwiki/Package_versioning_policy seems to have something relevant to say. build-depends: HaXml = 1.13.3 1.14 ought to do the trick, since any

[Haskell-cafe] Control.Parallel.Strategies

2008-04-09 Thread Sebastian Sylvan
Hi, I was toying with the Control.Parallel.Strategies library, but can't seem to get it to actually do anything in parallel! Here's the code: import System.Random import Control.Parallel.Strategies fib :: Int - Int fib 0 = 1 fib 1 = 1 fib n = fib (n-1) + fib (n-2) main = print $ parMap rnf fib

Re: [Haskell-cafe] Control.Parallel.Strategies

2008-04-09 Thread Justin Bailey
2008/4/9 Sebastian Sylvan [EMAIL PROTECTED]: main = print $ parMap rnf fib $ take 80 $ randomRs (30,35) (mkStdGen 123) Does the strategy rwhnf do it for you? Justin ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Control.Parallel.Strategies

2008-04-09 Thread Sebastian Sylvan
On Wed, Apr 9, 2008 at 10:22 PM, Justin Bailey [EMAIL PROTECTED] wrote: 2008/4/9 Sebastian Sylvan [EMAIL PROTECTED]: main = print $ parMap rnf fib $ take 80 $ randomRs (30,35) (mkStdGen 123) Does the strategy rwhnf do it for you? Justin Nope! This is GHC 6.8.2 btw, downloaded the

Re: [Haskell-cafe] Control.Parallel.Strategies

2008-04-09 Thread Justin Bailey
On Wed, Apr 9, 2008 at 2:25 PM, Sebastian Sylvan [EMAIL PROTECTED] wrote: Nope! This is GHC 6.8.2 btw, downloaded the binary from the web site, so it's nothing strange. On my hyper-threaded CPU, your original code works fine. With -N2, I see 100% CPU. With N1, only 50%. I am also using GHC

Re: [Haskell-cafe] Control.Parallel.Strategies

2008-04-09 Thread Sebastian Sylvan
On Wed, Apr 9, 2008 at 10:58 PM, Justin Bailey [EMAIL PROTECTED] wrote: On Wed, Apr 9, 2008 at 2:25 PM, Sebastian Sylvan [EMAIL PROTECTED] wrote: Nope! This is GHC 6.8.2 btw, downloaded the binary from the web site, so it's nothing strange. On my hyper-threaded CPU, your original code

Re: [Haskell-cafe] Control.Parallel.Strategies

2008-04-09 Thread Justin Bailey
On Wed, Apr 9, 2008 at 3:03 PM, Sebastian Sylvan [EMAIL PROTECTED] wrote: Hmm, that's curious. I compile with ghc --make -threaded partest.hs -o par.exe, and then run it with par.exe +RTS -N2 -RTS. Am I making some silly configuration error? Are you running this on windows? Yep, that's the

[Haskell-cafe] Re: Lock-Free Data Structures using STMs in Haskell

2008-04-09 Thread Pete Kazmier
Bryan O'Sullivan [EMAIL PROTECTED] writes: Pete Kazmier wrote: data ArrayBlockingQueueSTM e = ArrayBlockingQueueSTM { [...] sa :: Array Int (TVar e) } It's unclear to me why the Array's elements must be wrapped in TVars. To allow them to be modified. You can't otherwise

[Haskell-cafe] Pattern match failure

2008-04-09 Thread Jackm139
I'm trying to write a function to recognize a context free grammar, but I keep getting pattern match failure errors. This is what I have: data Grammar c = Brule c c c | Rule c c gez = [(Brule 'S' 'p' 'D'),(Brule 'D' 't' 'E'),(Rule 'E' 'j')] recog :: String - String - [Grammar Char] - Bool

Re: [Haskell-cafe] Pattern match failure

2008-04-09 Thread Luke Palmer
On Thu, Apr 10, 2008 at 2:05 AM, Jackm139 [EMAIL PROTECTED] wrote: I'm trying to write a function to recognize a context free grammar, but I keep getting pattern match failure errors. This is what I have: data Grammar c = Brule c c c | Rule c c gez = [(Brule 'S' 'p' 'D'),(Brule 'D' 't'

Re: [Haskell-cafe] type families and type signatures

2008-04-09 Thread Manuel M T Chakravarty
Claus Reinke: type family Id a type instance Id Int = Int foo :: Id a - Id a foo = id n foo' :: Id a - Id a foo' = foo type function notation is slightly misleading, as it presents qualified polymorphic types in a form usually reserved for unqualified polymorphic types. rewriting foo's

Re: [Haskell-cafe] type families and type signatures

2008-04-09 Thread Manuel M T Chakravarty
Lennart Augustsson: On Wed, Apr 9, 2008 at 8:53 AM, Martin Sulzmann [EMAIL PROTECTED] wrote: Lennart, you said (It's also pretty easy to fix the problem.) What do you mean? Easy to fix the type checker, or easy to fix the program by inserting annotations to guide the type checker?

Re: [Haskell-cafe] Re: type families and type signatures

2008-04-09 Thread Manuel M T Chakravarty
apfelmus: Manuel M T Chakravarty wrote: apfelmus: Manuel M T Chakravarty wrote: Let's alpha-rename the signatures and use explicit foralls for clarity: foo :: forall a. Id a - Id a foo' :: forall b. Id b - Id b GHC will try to match (Id a) against (Id b). As Id is a type synonym family,

Re: [Haskell-cafe] type families and type signatures

2008-04-09 Thread Manuel M T Chakravarty
Lennart Augustsson: Let's look at this example from a higher level. Haskell is a language which allows you to write type signatures for functions, and even encourages you to do it. Sometimes you even have to do it. Any language feature that stops me from writing a type signature is in my

Re: [Haskell-cafe] instance Monad m = Functor m

2008-04-09 Thread ajb
G'day all. Quoting Jules Bean [EMAIL PROTECTED]: Other solutions, such as class Functor m = Monad m are frequently discussed. I see no H' ticket for it, though. Then add it. :-) You'll probably want to make it depend on Ticket #101, because making class hierarchies more granular generally