Re: AlternateLayoutRule

2014-05-13 Thread John Meacham
Okay, I believe I have come up with a modified version that accepts many more programs and doesn't require complicated comma handling, you can make all decisions based on the top of the context stack. It also allows many useful layouts that were illegal under the old system. The main change was to

Re: vector and GeneralizedNewtypeDeriving

2014-05-13 Thread John Lato
Not by anything I've tried yet, no. On Tue, May 13, 2014 at 10:40 PM, Carter Schonwald < carter.schonw...@gmail.com> wrote: > can you get the deriving to work on > a newtype instance MVector s Foo = > ? > > > On Tue, May 13, 2014 at 9:39 PM, John Lato wrote: > >> Hello, >> >> Prior to ghc-

Re: vector and GeneralizedNewtypeDeriving

2014-05-13 Thread Carter Schonwald
can you get the deriving to work on a newtype instance MVector s Foo = ? On Tue, May 13, 2014 at 9:39 PM, John Lato wrote: > Hello, > > Prior to ghc-7.8, it was possible to do this: > > > module M where > > > > import qualified Data.Vector.Generic.Base as G > > import qualified Data.Vector

vector and GeneralizedNewtypeDeriving

2014-05-13 Thread John Lato
Hello, Prior to ghc-7.8, it was possible to do this: > module M where > > import qualified Data.Vector.Generic.Base as G > import qualified Data.Vector.Generic.Mutable as M > import Data.Vector.Unboxed.Base -- provides MVector and Vector > > newtype Foo = Foo Int deriving (Eq, Show, Num, > M.

Re: AlternateLayoutRule

2014-05-13 Thread Ian Lynagh
On Tue, May 13, 2014 at 03:11:16PM -0700, John Meacham wrote: > > ah cool, can you point me to which file it is implemented in in the source > so I can copy your new rules? It's lexTokenAlr and friends in compiler/parser/Lexer.x It's a while since I looked at it, but IIRC it's not as clean to re

Re: AlternateLayoutRule

2014-05-13 Thread John Meacham
On Tue, May 13, 2014 at 2:22 PM, Ian Lynagh wrote: > It's based on your code, but I had to essentially completely re-write it > to work with the way that GHC's parser works; I don't think sharing the > code will be feasible. Ah, yeah, I didn't think the code would translate directly, but I'd want

Re: question about GADT's and error messages

2014-05-13 Thread Andres Löh
Hi. Daniel is certainly right to point out general problems with GADT pattern matching and principal types. Nevertheless, the changing behaviour of GHC over time is currently a bit confusing to me. In GHC-6.12.3, Doaitse's program fails with three errors (demo1, demo2, demo4, all the GADT pattern

Re: question about GADT's and error messages

2014-05-13 Thread Daniel Wagner
I just hit a similar error the other day. I think the gist of it is that there are two perfectly good types, and neither is more general than the other. A slightly different example shows why more clearly: foo (AInt i) = (3 :: Int) Now, what type should this have? foo :: Any a -> a foo :: Any

Re: AlternateLayoutRule

2014-05-13 Thread Ian Lynagh
On Tue, May 13, 2014 at 09:32:31PM +0100, Simon Marlow wrote: > On 13/05/14 15:04, John Meacham wrote: > >Hi, I noticed that ghc now supports an 'AlternateLayoutRule' but am > >having trouble finding information about it. Is it based on my > >proposal and sample implementation? > >http://www.mail-a

Re: AlternateLayoutRule

2014-05-13 Thread Simon Marlow
On 13/05/14 15:04, John Meacham wrote: Hi, I noticed that ghc now supports an 'AlternateLayoutRule' but am having trouble finding information about it. Is it based on my proposal and sample implementation? http://www.mail-archive.com/haskell-prime@haskell.org/msg01938.html Yes it is, but I thin

question about GADT's and error messages

2014-05-13 Thread S. Doaitse Swierstra
Given the following code: {-# LANGUAGE GADTs #-} data Any a where AInt :: Int -> Any Int -- demo 1 does not compile {- demo1 a = do case a of (AInt i) -> print i Couldn't match expected type ‘t’ with actual type ‘IO ()’ ‘t’ is untouchable inside the constraints (t1 ~ Int)

AlternateLayoutRule

2014-05-13 Thread John Meacham
Hi, I noticed that ghc now supports an 'AlternateLayoutRule' but am having trouble finding information about it. Is it based on my proposal and sample implementation? http://www.mail-archive.com/haskell-prime@haskell.org/msg01938.html https://ghc.haskell.org/trac/haskell-prime/wiki/AlternativeLayo

Re: Using mutable array after an unsafeFreezeArray, and GC details

2014-05-13 Thread Simon Marlow
On 12/05/2014 21:28, Brandon Simmons wrote: The idea is I'm using two atomic counters to coordinate concurrent readers and writers along an "infinite array" (a linked list of array segments that get allocated as needed and garbage collected as we go). So currently each cell in each array is writt