Re: FW: 7.4.1-pre: Show Integral

2012-03-06 Thread John Meacham
On Sat, Dec 24, 2011 at 12:37 PM, Ian Lynagh ig...@earth.li wrote:
 On Fri, Dec 23, 2011 at 05:41:23PM +, Simon Peyton-Jones wrote:
 I'm confused too.  I'd welcome clarification from the Haskell Prime folk.

 We use the library process to agree changes to the libraries, and
 Haskell' should then incorporate the changes into the next version of
 the standard.

FWIW, the library change process is nowhere near rigorous enough to
decide what should go into a language standard. Not that some good
 ideas have not been explored, but before adding them to a language
standard, they would require considerably more discussion.

   John

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


simple extension to ghc's record disambiguation rules

2012-02-17 Thread John Meacham
Hi, I'd like to propose an extremely simple extension to ghc's record
disambiguation rules,

my motivation is that I often have record types with multiple constructors
but common fields.

so the handy idiom of

f Rec { .. } = do
blah
return Rec { .. }

won't work, because I don't know the specific constructor.

so, my proposal is that when you come across something like

(e::RecType) { blah = foo }

(with an explicit type signature like shown)

You interpret 'blah' as if it is a field of the record of type 'Rec'. This
gives the advantages of record field names being scoped by type but without
you having to specify the precise constructor.

It is also backwards compatible for expressions, but would be a new thing
for patterns which generally don't allow type signatures there.

It sidesteps type checker interactions by only being triggered when an
explicit type annotation is included.

ideally it would be combined with the 'update' and 'label-based
pattern-matching' extensions from this page
http://hackage.haskell.org/trac/haskell-prime/wiki/ExistingRecords

John

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: [jhc] new extension in jhc: explicit namespaces in import/export lists

2012-02-13 Thread John Meacham
On Sun, Feb 12, 2012 at 11:26 PM, Roman Cheplyaka r...@ro-che.info wrote:
 * John Meacham j...@repetae.net [2012-02-12 19:26:24-0800]
 In haskell 98 [...]

 Not sure what you mean here. You aren't going to modify an existing
 standard, are you? :)
 [...] a name such as 'Foo' in an export list will indicate that all of
 a class named Foo, a type named 'Foo' and a data constructor named
 'Foo' shoud be exported.

 This bit doesn't sound right... I think this behaviour would be
 something that people will more often fight against (by using
 namespaces) than appreciate. (Esp. that Foo exports both the type and
 the data constructor.)

Yeah, I worded it incorrectly, actually it is more that I read my own
code incorrectly :)
The data constructor isn't matched. as stands
my extension behaves identically to h2010 rules when no namespace
specifiers are used.  When a namespace specifier
is used, the declaration is restricted to just the names that match
that namespace.
So it is transparent when not used.

 How about this:

 Foo in the export list may refer to a class, a type or a kind (but not a
 data constructor). It is an error if multiple entities with the name
 Foo are in scope.

Allowing multiple things of the same name was part of the goal, in
that you can use the explicit namespaces to restrict it if it is what you
intend.. But I suppose that could be considered an independent change.

In any case, part of the reason for implementing this in jhc was to
experiment with variants like this too see what works.

Actually, perhaps a better rule would be it is an error if multiple entities
within the same namespace are matched

hmm.. not sure on that one yet...

 I see your point regarding 'hiding' inconsistency, but I'd prefer having
 'hiding' fixed (in a similar way).

Yeah, it is just annoying that there is this one exception.

John

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Proposal: require spaces around the dot operator

2012-02-09 Thread John Meacham
I mean, it is not worth worrying about the syntax until the extension has been
 implemented, used, and proven useful to begin with. Monads were in use
well before the 'do' notation. Shaking out what the base primitives that make
up a monad took a while to figure out.

Even discussing syntax feels a little like a garage band discussing what
the lighting of their  stage show will look like before they learned to play
their instruments.

If we can implement it and test it without breaking existing code, why
wouldn't we? It would mean more people can experiment with the
feature because they wouldn't have to modify existing code much. So
we will have more feedback and experience with how it interacts with
other aspects of the language.

John

On Thu, Feb 9, 2012 at 6:41 PM, Greg Weber g...@gregweber.info wrote:
 There are 2 compelling reasons I know of to prefer dot for record access
 1) follows an almost universal convention in modern programming languages
 2) is consistent with using the dot to select functions from module 
 name-spaces

 We can have a lot of fun bike-shedding about what operator we would
 prefer were these constraints not present. Personally I wouldn't care.
 However, I find either one of these 2 points reason enough to use the
 dot for record field access, and even without a better record system
 the second point is reason enough to not use dot for function
 composition.

 It is somewhat convenient to argue that it is too much work and
 discussion for something one is discussing against. The only point
 that should matter is how existing Haskell code is effected.

 On Thu, Feb 9, 2012 at 8:27 PM, Daniel Peebles pumpkin...@gmail.com wrote:
 I'm very happy to see all the work you're putting into the record
 discussion, but I'm struggling to see why people are fighting so hard to get
 the dot character in particular for field access. It seems like a huge
 amount of work and discussion for a tiny bit of syntactic convenience that
 we've only come to expect because of exposure to other very different
 languages.

 Is there some fundamental reason we couldn't settle for something like # (a
 valid operator, but we've already shown we're willing to throw that away in
 the MagicHash extension) or @ (only allowed in patterns for now)? Or we
 could even keep (#) as a valid operator and just have it mean category/lens
 composition.

 Thanks,
 Dan

 On Thu, Feb 9, 2012 at 9:11 PM, Greg Weber g...@gregweber.info wrote:

 Similar to proposal #20, which wants to remove it, but immediately
 less drastic, even though the long-term goal is the same.
 This helps clear the way for the usage of the unspaced dot as a record
 field selector as shown in proposal #129.

 After this proposal shows clear signs of moving forward I will add a
 proposal to support a unicode dot for function composition.
 After that we can all have a lively discussion about how to fully
 replace the ascii dot with an ascii alternative such as ~ or 
 After that we can make the dot operator illegal by default.

 This has already been discussed as part of a records solution on the
 ghc-users mail list and documented here:
 http://hackage.haskell.org/trac/ghc/wiki/Records/DotOperator

 ___
 Haskell-prime mailing list
 Haskell-prime@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-prime



 ___
 Haskell-prime mailing list
 Haskell-prime@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-prime

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: specify call-by-need

2011-02-15 Thread John Meacham
Except for the fact that compilers don't actually implement call by
need. An example would be the speculative evaluation of ghc.

http://research.microsoft.com/en-us/um/people/simonpj/papers/optimistic/adaptive_speculation.ps

And local optimizations that affect asymptotic behavior are used all
the time, to the point they are vital for a functioning compiler. The
tail-call optimization turning O(n) space usage to O(1) being a prime
example.

And what is meant by call-by-need in the presence of exceptions and
concurrency is not entirely obvious.

I think that specifying call-by-need would be more confusing and
contrary to what actually exists in the wild.

   John


On Tue, Feb 15, 2011 at 5:53 PM, Scott Turner 2hask...@pkturner.org wrote:
 In practice, Haskell a call-by-need language.  Still, software
 developers are not on firm ground when they run into trouble with
 evaluation order, because the language definition leaves this open. Is
 this an underspecification that should be fixed?

  1. Haskell programmers learn the pitfalls of sharing as soon
     as they cut their teeth on 'fib',
  2. Virtually all significant-sized Haskell programs rely on
     lazy evaluation and have never been tested with another
     evaluation strategy,
  3. Questions come up on Haskell-Café, infrequently but regularly,
     regarding whether a compiler optimization has altered sharing
     of values within a program, causing it to fail,
  4. The rationale for the monomorphism restriction assumes
     lazy evaluation,
  5. It is the effect on asymptotic behavior that matters,
  6. Portable Haskell code should not have to allow for the
     variety of non-strict evaluation strategies, as the Haskell
     Report currently implies.

 I suggest specifying call-by-need evaluation, allowing for the places
 where type classes prevent this.  If necessary, make it clear that local
 optimizations not affecting asymptotic behavior are permitted.

 This would not eliminate struggles with evaluation order. The intent
 would be to clarify expectations.

 -- Scott Turner

 ___
 Haskell-prime mailing list
 Haskell-prime@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-prime


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Propsal: NoDatatypeContexts

2010-07-19 Thread John Meacham
On Mon, Jul 19, 2010 at 11:29:37AM +0200, Christian Maeder wrote:
 I'm for this proposal, although I've got an example where I need this
 context, namely for DrIFT to derive a proper context for instances.
 
 DrIFT doesn't know that the Read instance for Data.Set.Set relies on Ord
 of the elements. For
 
 data Ord symbol = ExtSign sign symbol = ExtSign
   { plainSign :: sign
   , nonImportedSymbols :: Set.Set symbol
   } deriving Show
 
 DrIFT cannot derive the Read (or our deserialization) instance without
 the Ord symbol = context.
 
 However, ghc is able by deriving (Show, Read) to see
 
 instance (Ord symbol, Read sign, Read symbol) =
  Read (ExtSign sign symbol)
 
 without the context.

Hmm... if you can provide a fix for this I'll integrate it, perhaps a
manual annotation will be the only way, I don't think there is any easy
way for DrIFT to derive that information otherwise.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: prefix operators

2010-07-10 Thread John Meacham
On Fri, Jul 09, 2010 at 09:33:52AM +0100, Simon Marlow wrote:
 On 08/07/2010 09:45, John Meacham wrote:
 On Thu, Jul 08, 2010 at 07:09:29AM +, Simon Peyton-Jones wrote:
 (ie as infix operators) and I have to squizzle around to re-interpret them 
 as prefix operators.  Not very cool.  Something unified would be a Good 
 Thing.

 So, after thinking about it some, I think there may be a somewhat
 elegant solution.

 I like the sound of it.  I put the code for the Haskell 2010 fixity  
 resolver together with a little testing framework in the haskell-prime 
 repo:

   http://darcs.haskell.org/haskell-prime


There is also my one-pass layout algorithm that requires no interaction
with the parser that I believe still has promise. It was able to
properly layout all the wild code I threw at it (all of nofib). With the
addition of that, we may achieve the holy grail of fully independent
lexing,layout,parsing,and fixing of haskell code, and a specification
that has a direct correspondence to an implementable algorithm!


I actually just noticed that my layout code is now implemented in ghc:
http://hackage.haskell.org/trac/haskell-prime/wiki/AlternativeLayoutRule
I am curious what the results will be, I know that adding pattern guards
to it would be complicated, I will have to check out how my algorithm
was modified.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: prefix operators

2010-07-08 Thread John Meacham
On Thu, Jul 08, 2010 at 07:09:29AM +, Simon Peyton-Jones wrote:
 (ie as infix operators) and I have to squizzle around to re-interpret them as 
 prefix operators.  Not very cool.  Something unified would be a Good Thing.

So, after thinking about it some, I think there may be a somewhat
elegant solution. 

The other day I found myself writing a prolog parser in haskell, an
interesting thing about prolog is that it is a pure operator precedence
grammar[1]. Meaning that the entire grammar can be defined by a list of
symbols, their fixities and their priorities. An example of a definition
for a prolog-like language is 
http://www.mercury.csse.unimelb.edu.au/information/doc-release/mercury_ref/Builtin-Operators.html
Now, a really nice thing about operator precedence grammars is that they
admit a very simple linear parsing algorithm[2] and they are quite simple
to understand.

So, Why not utilize the nice properties of this style of grammar when
defining haskell, we already attempt to interpret infix operators in the
grammar BNF proper, but then go and refix them anyway in the fixity
fixups pass, probably with something very similar to an operator
precedence parser. so the idea is basically to get rid of the initial
dummy parsing of expressions altogether and parse expressions as a pure
operator precedence grammar in the fixups pass. This will allow seamless
handling of prefix operators and likely simplify the formal description
of the language to boot.

So, for the most part the grammar will look like it does now, except
when we get to expressions, patterns, and types, we just parse them
uniformly as a sequence of atomic nodes. These may be variables, but
also may be things like infix operators, or even an entire parenthesized
term or case expression. These can be recursive, a parenthesized
expression will itself contain a list of nodes. 

Now, we can simply define the fixity resolution pass as applying the
appropriate operator precedence grammar to each list of nodes, producing
expressions, types, or patterns. The really nice thing is that we are
under no obligation to use the same operator precedence grammar for each
context, we can always tell from the parsing context whether we are parsing
a type, expression, or pattern, so we just use the appropriate grammar,
for instance, we will augment the grammar with the prefix '~' in
patterns, and the prefix '!' (for strictness) in types. '!' can be
defined as prefix in patterns and infix in expressions simply by using a
slightly different precedence table when interpreting them. This also
makes very clear how user defined fixities are used, they are simply
appended to the precedence table in this pass. Turning on and off bang
patterns with a switch is also extremely easy, just omit that prefix
operator from the table when they are switched off. no need to mess with
the lexer or the parser.

I also suspect we can produce much better error messages with this
strategy.

John


[1]  http://en.wikipedia.org/wiki/Operator-precedence_parser 
[2] http://www.engr.mun.ca/~theo/Misc/exp_parsing.htm

-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


prefix operators

2010-07-07 Thread John Meacham
It occurred to me the other day that Haskell (w/ bang patterns) now has
3 prefix operators, all of which are defined independently and follow
their own special rules for parsing. we have (-), (!) and (~). 

It would seem to me that we should somehow be able to unify the
mechanism behind parsing these, as in practice, it seems that prefix
operators are useful in haskell.

We have some similarities, - and ! are both infix and prefix operators,
~ is not. ! and ~ can only be in patterns as prefix, (-) can be in both
patterns and expressions.

But it seems like we may be able to come up with a common way of parsing
them all, prolog has had user defined infix, prefix, and postfix
operators (sharing the same name even) and is still able to parse things
properly so I don't think there will be a technical issue.

My first impulse is to treat application as just another binary operator
with a certain precedence and find appropriate precedences for !,~,- in
the new framework. 

note: I am not proposing user defined prefix operators, just musing
about whether we can unify the rules behind parsing the current three
prefix operators, perhaps folding them into the fixity resolution
algorithm.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


RECOMMENDATION: Use 'labeled fields' rather than records when talking about labeled fields

2010-02-24 Thread John Meacham
This isn't so much a proposal as a recommendation for terminology we use
when talking about things on the list and proposals in general. Calling
haskell's labeled field mechanism 'records' leads to all sorts of
confusion for people that come from other languages where 'records'
means something else, this is compounded by the fact there are several
actual record proposals out there that are orthogonal to labeled fields,
but calling fields 'records' confuses this issue.

I believe we have already gotten rid of every reference to 'record' in
the report in favor of 'labeled field' or just 'field', so it would be
good if we could use the same terminology in all discussions. Not only
will it help avoid confusion but it is a more accurate description of
what Haskell actually provides and is in line with the report. 

So, let's call 'record puns' 'field puns' as a first step.

John


-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: RECOMMENDATION: Use 'labeled fields' rather than records when talking about labeled fields

2010-02-24 Thread John Meacham
On Wed, Feb 24, 2010 at 11:35:44AM -0800, Evan Laforge wrote:
 On Wed, Feb 24, 2010 at 11:03 AM, John Meacham j...@repetae.net wrote:
  This isn't so much a proposal as a recommendation for terminology we use
  when talking about things on the list and proposals in general. Calling
  haskell's labeled field mechanism 'records' leads to all sorts of
  confusion for people that come from other languages where 'records'
  means something else, this is compounded by the fact there are several
  actual record proposals out there that are orthogonal to labeled fields,
  but calling fields 'records' confuses this issue.
 
 Just out of curiosity, what are the attributes associated with
 labeled fields and what are the ones associated with records?

Well, when you have a data constructor like

data Foo = Foo Int Char

your Int and Char are the two fields of your data constructor Foo,
labeled fields are exactly that, a way to refer to them by labels rather
than positionally. in particular, the run-time implementation and
ability for optimization is exactly the same. it is simply a more
convienient way to work with a construct that already exists in Haskell
with no overhead, like a newtype.

A record system generally implies labels that can be easily re-usued between
different types and is extensible in nature. They may not need to be
pre-declared. Allowing these may require compromises at run-time
creating a tension between their utility and performance. I like to think
of them more analogous to tuples with labels than declared data types.
Of course, not all record proposals for haskell embody the exact same
thing, but these features seem to be what people coming to haskell
expect out of something called a 'record' system and are more or less
what the various proposals provide.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Negation

2010-02-08 Thread John Meacham
On Mon, Feb 08, 2010 at 04:18:07PM +, Simon Peyton-Jones wrote:
 Which of these definitions are correct Haskell?
 
   x1 = 4 + -5
   x2 = -4 + 5
   x3 = 4 - -5
   x4 = -4 - 5
   x5 = 4 * -5
   x6 = -4 * 5
 
 Ghc accepts x2, x4, x6 and rejects the others with a message like
 Foo.hs:4:7:
 Precedence parsing error
 cannot mix `+' [infixl 6] and prefix `-' [infixl 6] in the same infix 
 expression
 
 Hugs accepts them all.
 
 I believe that the language specifies that all should be rejected.  
 http://haskell.org/onlinereport/syntax-iso.html
 
 
 I think that Hugs is right here.  After all, there is no ambiguity in any of 
 these expressions.  And an application-domain user found this behaviour very 
 surprising.
 
 I'm inclined to start a Haskell Prime ticket to fix this language definition 
 bug.  But first, can anyone think of a reason *not* to allow all the above?

What would be the actual change proposed? If it is something concrete
and not something like negatives should be interpreted as unary minus
when otherwise it would lead to a parse error then that wouldn't be
good. I have enough issues with the layout rule as is :)

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: bug in language definition (strictness)

2009-08-29 Thread John Meacham
On Mon, Aug 17, 2009 at 01:02:29PM +0100, Simon Marlow wrote:
 On 07/08/2009 12:17, Ravi Nanavati wrote:
 I wonder if this discussion has veered too far into legalistic
 reasoning (of various sorts). From where I'm standing the
 state-of-play is this:

 1. Compiler writers (and some users) want a liberal version of seq
 (that's slippery about evaluation order) for optimizations and better
 correspondence with the denotational semantics.
 2. Other users want a version of seq that guarantees evaluation order
 for use cases where that matters.

 Is there any deep reason why we don't just figure out what the best
 way to give people both versions of seq is and do that?

 Compilers can provide seq with an ordering guarantee if they want, just  
 as GHC does with Control.Parallel.pseq.  I don't think it would be good  
 to mandate this in the standard, for the reassons I've already described  
 in this thread, in summary:

  - it constrains evaluation order in a way that Haskell
doesn't currently do, and which might prevent interesting
implementations (e.g. automatic parallelisation)

  - it's not clear how to specify what seq with an ordering guarantee
actually means.  If someone were to come up with a precise
definition, that would be a much better basis for discussion.

What is interesting is that pseq, or seq with an ordering guarentee,
actually would introduce a lazyness, instead of strictness. in order to
see this, we can observe what will have with the strictness analyzer.
imagine the function

f :: Int - Int - Int
f x y = y `seq` x

Now, the strictness analysis will see that f is strict in both its
arguments, y because of seq, and x because it is what returned. we can
say it derives the following annotated type (where ! means strict)

f :: !Int - !Int - Int

now, anything that calls f is free to evaluate its arguments before
passing them to f, more importantly, it enables things like the
worker-wrapper transform and unboxing. however if we have

f x y = y `pseq` x

now, what is the strictness for f?
Although f is still 'strict' in both arguments in that it evaluates
both, in order to guarentee the ordering that its second argument is
evaluated before its first, it must be lazy in its first argument. or:

f :: Int - !Int - Int

otherwise the calling function may evaluate the first argument before
the second, since the strictness information doesn't include ordering
information.  So, adding a 'pseq' actually gets rid of strictness.

things get worse with something like

j :: Bool - Int - Int - Int
j b x y = if b then f x y else f y x


even though j is obviously strict in all its arguments in that it
evaluates them all, the compiler cannot derive that fact since it
doesn't know the _order_ in which they are strict.


This suggests a natural implementation (and specification) for pseq,

pseq :: a - b - b
pseq x y = x `seq` lazy y

where lazy :: a - a is a compiler provided function equivalent to 'id'
except that it is considered lazy in its argument by the strictness
analyzer.


So, I think an order preserving 'seq' is possible, but it has the ironic
quality of introducing lazyness, rather than strictness.

And if anything were proposed as a cross-compiler convention, I think
'lazy' would be a more useful and less confusing function to introduce
as a portable primitive.


John



-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Standarize GHC.Prim.Any

2009-08-18 Thread John Meacham
On Mon, Aug 17, 2009 at 07:52:26PM -0400, Isaac Dupree wrote:
 Also, can/do all compilers that implement unsafeCoerce implement a safe Any?
 Hugs can do it with just data Any = Ignored I believe, not sure about  
 nhc, yhc or jhc...

Jhc has existentials, so that is the best way to handle this. Jhc
existentials do require an invisible type parameter to be added to the
representation so wouldn't be able to remove the extra box in general.

Jhc implements unsafeCoerce, but it is really unsafe as the type
information plays a major role in the data layout as jhc has no
'universal' run time representation of data. For instance, you
might unsafeCoerce something that was statically determined to not need
to be traversed by the garbage collector to something that the garbage
collector follows, surely resulting in a segfault or other undefined
behavior at run-time. This is the reason existentials always need to
carry around their type information, if nothing else, it potentially
guides the garbage collector. So, existentials really are the only safe
way to do this in jhc.

Really the only guarenteed safe use of unsafeCoerce in jhc is between a
newtype and its underlying representation.

John


-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: [Haskell'-private] StricterLabelledFieldSyntax

2009-08-13 Thread John Meacham
On Sun, Jul 26, 2009 at 02:34:59AM +0100, Ian Lynagh wrote:
 I've made a ticket and proposal page for making the labelled field
 syntax stricter, e.g. making this illegal:

 data A = A {x :: Int}

 y :: Maybe A
 y = Just A {x = 5}

 and requiring this instead:

 data A = A {x :: Int}

 y :: Maybe A
 y = Just (A {x = 5})


I don't like this not only because it would make a lot of code more
unwieldy, but it muddles the interpretation of how one interprets
braces.

Right now, we have a very simple rule, braces always bind to the left,
no matter where they are used, you can always tell what they mean by the
thing immediately preceeding them. Whether it is 'let', 'do', 'where', a
constructor, or an expression, you have a simple rule to remember which
is nice.

Also, what about data declarations? Would we need something like below?
It seems odd to apply such a rule sometimes but not others.

 data Foo = (Foo { .. }) | ...


John



-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: bug in language definition (strictness)

2009-08-13 Thread John Meacham
On Fri, Aug 07, 2009 at 08:56:39AM +1000, Peter Gammie wrote:
 How so? Take this code:

 newtype BDD = BDD (ForeignPtr Int)

 exists :: Group BDD - BDD - BDD
 exists group bdd = bdd `seq` unsafePerformIO $
   withGroup group $ \ gid -
 do bdd_assoc bdd_manager gid
withBDD bdd ({#call unsafe bdd_exists#} bdd_manager) =  
 addBDDfinalizer

Just a question, why not do

 How so? Take this code:

 newtype BDD = BDD (ForeignPtr Int)

 exists :: Group BDD - BDD - BDD
 exists group bdd = unsafePerformIO $
   bdd - evaluate bdd
   withGroup group $ \ gid -
 do bdd_assoc bdd_manager gid
withBDD bdd ({#call unsafe bdd_exists#} bdd_manager) =  
 addBDDfinalizer

It seems that evaluate is exactly the thing to order evaluations in the
IO monad.

John


-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: what about moving the record system to an addendum?

2009-07-06 Thread John Meacham
Well, without a replacement, it seems odd to remove it. Also, Haskell
currently doesn't _have_ a record syntax (I think it was always a
misnomer to call it that) it has 'labeled fields'. None of the proposed
record syntaxes fit the same niche as labeled fields so I don't see them
going away even if a record syntax is added to haskell in the future. I
would like to see the simple modifications to the record syntax listed
on this page though

http://hackage.haskell.org/trac/haskell-prime/wiki/ExistingRecords

and a reworking of the standard to not refer to the current system as a
'record syntax' but rather a 'labeled fields' syntax.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Specific denotations for pure types

2009-03-20 Thread John Meacham
On Fri, Mar 20, 2009 at 06:31:20PM -0700, Conal Elliott wrote:
 Oh -- not one version of Int for 32-bit execution and another version for
 64-bit execution?  Seen on #haskell today:
 
 mux  maxBound :: Int
  lambdabot   9223372036854775807

Yeah, that is actually a difference between jhc and ghc, jhc always uses
a 32 bit type for 'Int', while with ghc it follows the machines pointer
size. But they do both implement it as a standard haskell data type with
a single unboxed component. I used the jhc definition in my message as I
couldn't remember the exact way ghc defined it off the top of my head.

Although, I don't think any such user visible representation of Int or
other basic types should be mandated by the standard, I think it can be
useful as a way to express a portable denotational model for
understanding what operations on these types mean.

John



-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Mutually-recursive/cyclic module imports

2008-09-03 Thread John Meacham
On Mon, Sep 01, 2008 at 10:16:50PM -0700, Iavor Diatchki wrote:
 a free copy is available at:
 http://www.purely-functional.net/yav/publications/modules98.pdf
 (the source code, is also available at the same site).
 Hope that this helps,

Thanks. I liked this paper and hope we can come up with a similar formal
treatment of the module system for haskell' in the specification itself.
describing the result of import/export statements as the minimal
fixpoint of a set of equations is delightfully concise and
straightforward.


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Mutually-recursive/cyclic module imports

2008-08-26 Thread John Meacham
On Tue, Aug 26, 2008 at 04:31:33PM -0700, John Meacham wrote:
 http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.6.8816

Doh! wrong paper.

http://portal.acm.org/citation.cfm?id=581690.581692

anyone have a free link?

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: PROPOSAL: Make Applicative a superclass of Monad

2008-06-27 Thread John Meacham
On Thu, Jun 26, 2008 at 06:25:28PM -0700, Ashley Yakeley wrote:
 I wrote:
 Proposal:
 Make Applicative (in Control.Applicative) a superclass of Monad (in 
 Control.Monad).

 So does the silence = approval rule apply here?

I think that people believe this is generally a good idea, but until the
actual language that is haskell' is formalized, library issues are on
the backburner. But yeah, I think cleaning up various things about the
haskell 98 class hierarchy is a good idea. 

Even if class aliases are not in the standard itself but this change
was, implementing class aliasse would allow individual compilers to
provide full back and forwards compatability with haskell 98 and
haskell'.

So, that might be a route to having our cake and eating it too. We can
have the benefit of class aliases without having to break the haskell'
rules and standardize such an immature extension since they were
designed to be 'transparent' to code that doesn't know about them.
Haskell 98 code, and conformant haskell' prime code (as in, code that
doesn't explicitly mention class aliases) will coexist peacefully and we
will get a lot of experience using class aliases for when they
eventually perhaps do get standardized.

John



-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Haskell' - class aliases

2008-05-02 Thread John Meacham
On Fri, May 02, 2008 at 10:00:32AM +0100, Simon Peyton-Jones wrote:
 John

 This is good stuff, but I fear that in 3 months time it'll be buried
 in our email archives. In contrast, your original web page is alive
 and well, and we were able to start our discussion based on it

 So can I suggest that you transfer your web page to the Haskell' wiki
 (simply a convenient, editable place to develop it), or to the
 haskell.org wiki (likewise).  And that, as the design gets fleshed
 out, you try to reflect the current state of play there? I don't want
 this work to be lost!

Yes. I will try to do that. if anyone else wants to go ahead and do it,
that would be fine too.

 Ok, on to your email:

 === Desugaring the class alias decl = |
 there are two different desugaring rules, one for instances, one for
 the | alias appearing anywhere other than an instance declaration: | |
  g :: A a = a - b |  g = ...  | | translates to | |  g :: (S a,
  C1 a, C2 a) = a - b |  g = ...  | | the triplet of (S a, C1 a, C2
  a) is completely equivalent to (A a) in | all ways and all places
  (other than instance heads)

 Notice that this part *is* exactly true of a superclass with no
 methods

 class (S a, C1 a, C2 a) = A a where {}

No, this isn't true. imagine

 f :: (S a, C1 a, C2 a) = a - Int
 f x = g x

 g :: A a = a - Int
 g x = 

If A is a class alias, then this compiles just fine, if A is a
concrete class with superclasses, then it doesn't necessarily.

 That's not necessarily bad; but it does make it harder to figure out
 when to user a superclass and when to use a class alias.  Does that
 make sense?

 In fact, I suggest the following (**): the class alias

  class alias S a = A a = (C1 a, C2 a) where f1 = nd1

 desugars to

   class (S a, C1 a, C2 a) = A a

 The class alias decl *also* affects the desugaring of instances, still
 to come, but by desugaring the class alias into an ordinary class, you
 don't have to say *anything* about g :: (S a, C1 a, C2 a) = a - b vs
 g :: (A a) = a - b



But there is a difference, as noted above. And how can you decide
whether the expansion:

 class S a
 class S a = A a
 instance A Int

is supposed to declare an instance for 'S Int' as well as 'A Int' or
produce an error? Neither is a good choice universally. which is why I
made the distinction explicit in my class alias proposal.

 === Desugaring instanc decls =
 | now for instance declarations
 |
 |  instance A a where
 |  f2 = bf2
 |
 | expands to
 |
 |  instance (S a) = C1 a where
 |  f1 = nd1
 |
 |  instance (S a) = C2 a where
 |  f2 = bf2
 |  f3 = d3

 Do you really mean that? Presumably 'a' is not a type variable here?
 Furthermore, instance decls typically have a context.  Unless I have
 profoundly misunderstood, I think you mean this:

Yeah, a is likely not a type variable, so it will be of form 'S Foo' for
some concrete type 'Foo'. Which is checked at compile time (just as if a
method of S were used in a default) and produce an error if such an
instance doesn't exist.

   instance (Foo a, Bar b) = A (a,b) where f1 = bf1

 expands to

   instance (Foo a, Bar b) = C1 (a,b) where f1 = nd1

   instance (Foo a, Bar b) = C2 (a,b) where f2 = bf2 f2 = d3

 Notice the *absence* of an instance for (S (a,b)).  It's up to the
 *user* to ensure that there is such an instance, perhaps, say

 instance Foo a = S (a,b) where ...

No, the 'S a' as appended to whatever instance context you provide. so

   instance (Foo a, Bar b) = A (a,b) where f1 = bf1

expands to

   instance (S (a,b), Foo a, Bar b) = C1 (a,b) where f1 = nd1
   instance (S (a,b), Foo a, Bar b) = C2 (a,b) where f2 = bf2 f2 = d3

If 'S (a,b)' is not entailed by the environment in scope then the
declaration produces an error.

 In this way S is behaving just like any ordinary superclass.  If we
 have

 class S a = T a then given an instance instance (Foo a, Bar
 b) = T (a,b) it's up to the user to ensure that there is an
 instance for S (a,b).


 With the desugaring (**) I proposed above, we'd add one more instance:
 instance (Foo a, Bar b) = A (a,b)

Yes, but we explicitly did not want to add that instance by using a
class alias context rather than putting it in the expansion, for a
similar reason we don't create a dummy 'Eq' instance when someone
declares something an instance of 'Num' even though Eq is a superclass
of Num.  The 'class alias context' vs 'class alias expansion' is there
to make that distinction clear and unambigous, the expansion is what you
declare with an instance, the context is a prerequisite for creating an
instance.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Haskell' - class aliases

2008-05-02 Thread John Meacham
On Fri, May 02, 2008 at 11:24:11AM +0100, Simon Peyton-Jones wrote:
 | The more I think about it, I think 'superclass' is just the wrong
 | terminology for dealing with class aliases. Superclass implies a strict
 | partial order on classes, which just isn't the case for class aliases,
 | for instance
 |
 |  class alias Foo a = Foo a = Bar a where ...
 
 Crumbs!  I have no idea what that means!  Did you really mean to repeat 
 Foo?  According to your expansion in type signatures
 f :: (Foo a) = ...
 expands to
 f :: (Foo a, Bar a) = ...
 which presumably expands again.  I'm totally lost here

Yes I did, because I wanted to make the differences between class alias
contexts and superclasses very clear, the above context is valid, if
vacuous. the expansion goes as follows .

1. Foo a -- reduce(Foo a,Bar a)
-- Foo a expanded
2. reduce(Foo a,Bar a) -- (Foo a,Bar a)  
-- no entailment reduction possible, reduction is unchanged from H98
3. (Foo a,Bar a) - reduce(Foo a,Bar a,Bar a)
-- Foo a expanded
4. reduce(Foo a, Bar a, Bar a) - (Foo a, Bar a) 
-- reductino removes duplicates

5. we notice we are the same as in step #2. fixed point reached, we stop
expansion.

6. we remove all class aliases from result:

(Foo a, Bar a) - Bar a

7. 'Bar a' is our final result.


informal proof of termination:

each step adds a new class or class alias to the context, there are a
finite number of classes or class aliases, therefore we must eventually
reach a fixed point.

 Have a look at my last message, which gives a variant of your
 desugaring that IMHO greatly clarifies the meaning of (what I
 understand by) aliases.

I think the difference in what we mean is that I intend class aliases to
be a true bijection in all contexts (isomorphism?) between a single
alias and a set of classes. This is opposed to superclasses which are a
one directional implication.

One of my main motivations is being able to mix unchanged H98 and H'
code (with different numerical hierarchies, and both calling each other)
without modifications or prefered treatment for either. this means
instances for H' must silently and transparently create instances for
H98 classes and vice versa, moreso, type signatures should be
compatible.

As in, the H' specification should be able to make absolutely no
reference to H98 and vice versa, yet class aliases allow one to write a
compiler that seamlessly allows mixing code from the two without
compromising the design of either.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Haskell' - class aliases

2008-05-02 Thread John Meacham
On Fri, May 02, 2008 at 11:54:13AM +0100, Simon Peyton-Jones wrote:
 Even more crumbs!  Is this fixpoint iteration (being careful to avoid
 infinite expansion) *really* essential to your proposal?  That would
 be a significant and unwelcome thing IMHO.
 
 To be concrete, consider f :: (Foo a) = ...
 
 In GHC, f really takes an extra dictionary argument for the class Foo.
 If aliases mean aliases in the sense of type synonyms (which I think
 you intend) you must expand Foo to find out whether f takes zero, one,
 or many dictionary arguments.  Furthermore, everyone must expand in
 precisely the same way, so that we agree on the order of these
 arguments.  That's reasonably simple if expand simply means
 normalise; but it's more complicated if there's a fixpoint algorithm
 involved.

Yeah, I do mean normalize I think. There is no run time representation
of class aliases at all so this issue doesn't arise. f will just take a
'Bar' dictionary argument. I am envisioning class alias expansion taking
place very early in the desugaring, certainly before any transformation
to ghc core and turning contexts into dictionary arguments. 

 So is this really crucial?

Probably not, minimal fixpoint calculations are just what I find the simplest
way to formally define/think about things. In this case, I am sure a
simpler straight up normalization algorithm can be used to get
equivalent results... but minimal fixpoints are so easy to implement in
haskell and formally well defined that I am not sure of the value of
specifying the extension in terms of it. It of course doesn't mean
compilers have to perform the fixpoint iteration, it is just a
declarative statement of what class aliases are equivalent to.

John
 

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: instance export decls

2008-05-02 Thread John Meacham
On Thu, May 01, 2008 at 03:21:11PM +0100, Simon Peyton-Jones wrote:
 Indeed! I think it'd be good to allow type signatures, including
 instance signatures, in export lists

The problem with instance signatures is that it would give the
impression that it would be possible to _not_ export an instance, and it
wouldn't make explicit the fact that the instances of all modules it
depends on are also exported. 

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Haskell' - class aliases

2008-05-01 Thread John Meacham
On Thu, May 01, 2008 at 03:42:53PM +0100, Simon Peyton-Jones wrote:
 | Yeah, I disagree here, mainly because I don't want to conflate
 | superclasses with class aliases. I feel they have different uses, even
 | though they can sometimes achieve the same thing.
 
 Fair enough.  But the strange syntax
 
 class alias Num a = Eq a = (Additive a, Multiplicative a)
 
 *does* seem so say that the (Eq a) behaves in a superclass way, and
 (Additive a, Multiplicative a) behave in a class-alias way, as it
 were.  That seems inconsistent with the design goal you describe
 above.

Wolfgang suggested the alternate syntax

class alias Eq a = Num a = (Additive a, Multiplicative a) where 

The correct reading being:

if 'Eq a' then 'Num a' is an alias for (Additive a,Multiplicative a)

I think I am coming around to his point of view, do you think this makes
it clearer?

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Haskell' - class aliases

2008-05-01 Thread John Meacham
On Thu, May 01, 2008 at 11:57:14PM +0100, Simon Peyton-Jones wrote:
 |  Fair enough.  But the strange syntax
 | 
 |  class alias Num a = Eq a = (Additive a, Multiplicative a)
 | 
 |  *does* seem so say that the (Eq a) behaves in a superclass way, and
 |  (Additive a, Multiplicative a) behave in a class-alias way, as it
 |  were.  That seems inconsistent with the design goal you describe
 |  above.
 |
 | Wolfgang suggested the alternate syntax
 |
 | class alias Eq a = Num a = (Additive a, Multiplicative a) where 
 |
 | The correct reading being:
 |
 | if 'Eq a' then 'Num a' is an alias for (Additive a,Multiplicative a)
 |
 | I think I am coming around to his point of view, do you think this makes
 | it clearer?

 I am not arguing about syntax!

oh, I just meant that this syntax is actually a different way of
thinking about it for me and it helped me clarify some stuff in my mind
so thought it might be clearer for others as well.


 You say class aliases are orthogonal to superclasses, but then you
 allow this Eq a thing in the above alias, which is very like a
 superclass.  I think that if you allow the Eq a = part, you should
 also allow new methods to be declared in the alias (as I originally
 thought you did).  And if not, then you shouldn't allow superclasses.
 It's precisely that you allow superclasses (Eq a =) that makes your
 feature non-orthogonal to ordinary superclasses.  Maybe you can't make
 them orthogonal, but it quite hard to explain this definition to me.

Oh, the reason to allow superclasses of class aliases is so methods of
the superclass can be used in the default instance methods for your
alias. In addition, it allows full emulation of any explicit class you
can currently declare.

You do not want 'instance 'Num a'' to declare an instance for Eq as that
is very different behavior from the old Num class. Yet the default
instances for 'Num' may require use of methods from its superclass.

it actually would make more sense to call them the context of the class
alias rather than the superclass, since they don't declare a super/sub
class relationship between the two.

 Incidentally, you say that your proposal is just syntactic sugar: if
 so, can you give the desugaring translation?

Hmm.. okay, here is a rough draft that covers all the important cases I
think.

assume the following declarations:

 class C1 a where
 f1 :: t1
 f1 = d1

 class C2 a where
 f2 :: t2
 f2 = d2
 f3 :: t3
 f3 = d3



 class alias S a = A a = (C1 a, C2 a) where
 f1 = nd1



okay, the desugaring is as follows:

there are two different desugaring rules, one for instances, one for the
alias appearing anywhere other than an instance declaration:

 g :: A a = a - b
 g = ...

translates to

 g :: (S a, C1 a, C2 a) = a - b
 g = ...

the triplet of (S a, C1 a, C2 a) is completely equivalent to (A a) in
all ways and all places (other than instance heads), one is just a
different way to express the other, just like type synonyms. An alias
just expands to the union of the classes it is an alias for as well as
its class constraints (superclasses).

now for instance declarations

 instance A a where
 f2 = bf2

expands to

 instance (S a) = C1 a where
 f1 = nd1

 instance (S a) = C2 a where
 f2 = bf2
 f3 = d3


Note that when declaring an instance of a concrete type, like Int, the
constraint (S Int) will be trivially satisfied or not at compile time.
(bf2 is free to use methods of 'S' of course).

this translation is also a bijection, declaring those two instances
manually as above is indistinguishable from declaring instances via the
alias in all ways.

Hopefully the generalization to arbitrary numbers of classes is clear...

John

--
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Haskell' - class aliases

2008-04-25 Thread John Meacham
On Thu, Apr 24, 2008 at 10:21:03PM +0200, Wolfgang Jeltsch wrote:
 Am Donnerstag, 24. April 2008 21:27 schrieb John Meacham:
  On Thu, Apr 24, 2008 at 08:48:15PM +0200, Wolfgang Jeltsch wrote:
  […]
 
   I also have some remark: Why not write
  
class Eq a = Num a = (Additive a, Multiplicative a)
  
   instead of
  
class Num a = Eq a = (Additive a, Multiplicative a)
 
  Well, because you can think of 'Num a' as an alias for 'Eq a =
  (Additive a, Multiplicative a)', not that Eq is a superclass of Num
  which the class declaration syntax implies.
 
 Hmm, in what way is Num a an alias for Eq a = (Additive a, Multiplicative 
 a)?  
 You cannot write this:
 
  square :: (Eq a = (Additive a, Multiplicative a)) = a - a
 
 I would say: “Under the condition that Eq a holds, Num a is an alias for 
 (Additive a, Multiplicative a).  And this seems to be perfectly expressed by 
 my above proposal.

Hmm... I guess it depends on how you think about it. I tend to think
about them in terms of what they are rewritten to rather than a
proposition about classes. but perhaps that makes more sense. Will mull
on it some..

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: patch applied (haskell-prime-status): add Make $ left associative, like application

2008-04-24 Thread John Meacham
On Thu, Apr 24, 2008 at 09:38:22PM +0200, Wolfgang Jeltsch wrote:
 Am Donnerstag, 24. April 2008 00:43 schrieb Ian Lynagh:
  […]
 
  Please see
  http://www.haskell.org/haskellwiki/Library_submissions
 
   f $$ x = f x
 
  Note that this clashes with Text.PrettyPrint
 
 I also doesn’t correspond to $!.  We should introduce $$! then.

I don't think either of these are necessary and eat up valuable
operator-space. 

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: patch applied (haskell-prime-status): add Make $ left associative, like application

2008-04-23 Thread John Meacham
On Wed, Apr 23, 2008 at 09:52:11AM -0700, Simon Marlow wrote:
 The problem with this is that

   f !x y

 would associate differently in an expression than it does on the left hand 
 side of an equation, where ! is the prefix bang-pattern operator. To make 
 this consistent we'd have to make ! a prefix operator in expressions, or 
 give it the same precedence as function application; both mean a new 
 extension.

Hmm.. that is another possible solution to the ~ ! - thing, have ~ and !
be prefix operators in general. with ~ meaning 'negate' in expressions.
then parsing is the same everywhere.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Haskell' - class aliases

2008-04-22 Thread John Meacham
On Tue, Apr 22, 2008 at 08:33:53AM +0100, Simon Peyton-Jones wrote:
 Is this the most up-to-date description of the proposal?
 http://repetae.net/recent/out/classalias.html

There were a few changes proposed in the discussion that followed my
announcement that I wanted to make. The one I can remember now is
getting rid of the 'alias' keyword since the equals sign unabiguously
identifies it as an alias. I will dig through the archive to find the
others..

 I've just had another look, which threw up quite a few questions in my
 mind.   I wonder what would be a good list to discuss it.  Maybe this
 one is not bad, because it has people interested in Haskell
 innovation, regardless of whether it's a live Haskell' candidate?

Sounds good to me.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Some clarity please!

2008-04-22 Thread John Meacham
On Tue, Apr 22, 2008 at 05:28:27PM +, Michael Karcher wrote:
 I am quite late to join this thread, but as I just read the thread
 about Conal's AddBounds where he had a very valid point for
 implementing min/max without resorting to = or compare:
 
 min [] ys = []
 min xs [] = []
 min (x:xs) (y:ys)
  | cmp == LT = (x:xs)
  | cmp == GT = (y:ys)
  | cmp == EQ = x:min xs ys
 where cmp = compare x y
 
 This is a properly lazy implementation for min (the one in GHC's
 prelude is not), as it is able to calculate (take 5 $ min [1,2..]
 [1,2..]). This is not possible if min has to wait for compare or = to
 compare the full lists before returning the head.

In addition, you need special min and max functions to implement IEEE
floating point properly. Of course, floating point is odd in general,
but we should be correct when we can.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: patch applied (haskell-prime-status): BangPatterns: probably accept == undecided

2008-04-21 Thread John Meacham
On Mon, Apr 21, 2008 at 01:36:33PM -0700, Simon Marlow wrote:
 0. do nothing
 1. use a Unicode operator for composition
 2. require spaces around . as an operator
 3. require spaces around all operators
 4. use another ASCII operator for composition, e.g. 

 Nothing has been decided yet, but most of the committee tends to favour 
 (2), with some expressing a slight preference for (0).  We've pretty much 
 ruled out (1) and (3) as too radical, and as you say using Unicode is still 
 too impractical.

There is also the proposal to change the fixity of '$'. this would mean
that '.' becomes a lot more common as 

f $ a $ b $ c  
would now be written
f . a . b $ c

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: patch applied (haskell-prime-status): BangPatterns: probably accept == undecided

2008-04-18 Thread John Meacham
On Fri, Apr 18, 2008 at 08:36:42AM +0100, Simon Peyton-Jones wrote:
 Not allowing infix functions on the LHS would be a notable
 simplification.  Constructors in patterns should still be infix of
 course: f (a :=: b) = ...

I don't know, I think this will confuse things, especially for newbies,
people tend to say things like:

a + b = foo

as a plus b is foo, and so would probably naturally write it in infix
form, it would be a source of confusion if the compiler didn't accept
it.

I don't think saying ~ and ! are operators unless they 

1. immediately followed  by a '(', a letter, or an underscore
2. are preceded by whitespace or BOL

is that onerous. 


John



-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: patch applied (haskell-prime-status): BangPatterns: probably accept == undecided

2008-04-17 Thread John Meacham
On Wed, Apr 16, 2008 at 06:22:14PM +0100, Neil Mitchell wrote:
 Hi
 
   In the list of features required for Haskell in practice, bang patterns 
  are
   way up there.
 
 But their syntax has issues:
 
 a!b = ...
 
 Did I just define the function a or the function !?

Interesting note, if we solve this, then we can apply the same thing to
the treatment of ~ and regain it as a usable operator.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: patch applied (haskell-prime-status): proposal: remove string gaps

2008-04-01 Thread John Meacham
I concur! i use them in quite a few places. If anything, I would like
some more powerful style of quoting, like triple quotes in python.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: patch applied (haskell-prime-status): proposal: remove string gaps

2008-04-01 Thread John Meacham
On Tue, Apr 01, 2008 at 09:47:30PM +0100, Neil Mitchell wrote:
 * string gaps cause problems with CPP, which doesn't like the
 backslash at the end of the line. (a minor consideration, since CPP is
 not part of the language, and in any case there is cpphs).

Between the two, I'd say CPP is the much uglier beast. (I tend to use m4
actually when I must use a preprocessor in general, it meshes with haskell 
better
and is pretty ubiquitous). In any case, the simple solution of
not using CPP in the same file as string gaps works quite well. It has
never really been an issue before.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: If newtype = data !, then why use does Haskell' need newtype

2007-10-11 Thread John Meacham
On Thu, Oct 11, 2007 at 02:32:25PM -0700, Dan Weston wrote:
 I presume that the two statements below are equivalent [1]:
 
 newtype A = MkA  Int
 dataA = MkA !Int
 
 So does Haskell' still need newtype? It seems like a needless keyword.

they are not the same:

 newtype A = MkA  Int
 dataB = MkB !Int


f (MkA x) = 3
g (MkB x) = 3

f _|_ = 3
g _|_ = _|_


newtype construction/deconstruction is defined to be a nop, data
deconstruction always requires evaluation. just because the value inside
the data type is guarenteed not to be bottom, it doesn't mean
deconstruction/construction is a nop.

That said, ghc is quite clever and figured out it can unbox that data
type for you in this particular case, but such a transformation is not
necessarily valid in general.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Wanted: warning option for usages of unary minus

2007-05-21 Thread John Meacham
On Mon, May 21, 2007 at 10:33:56AM +0100, Simon Marlow wrote:
 I think that we could easily remove the '3e4' lexical syntax though, since 
 '3*10^^4' works just as well (I often write the latter anyway) (and guess 
 what, I just had to look up the difference between ^ and ^^, only to 
 discover I picked the wrong one).  The '3e4' syntax is a common source of 
 compiler bugs, becuase it is rarely used and hence rarely tested.

but they have substantially different translations.

3e2 - fromRational (300 % 1)

3*10^^2   -

(fromInteger 3) * (fromInteger 10) ^^ (2 :: Foo)

where Foo is whatever 4 defaults to, probably Integer, but could be a
compile error if defaulting is off or changed.

Though, the current floating point support in haskell is pretty funky as
is...

John 

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: strict bits of datatypes

2007-03-21 Thread John Meacham
On Mon, Mar 19, 2007 at 03:22:29PM +, Simon Peyton-Jones wrote:
 | This reminds me of something I discovered about using strict fields in
 | AVL trees (with ghc). Using strict fields results in slower code than
 | doing the `seq` desugaring by hand.
 
 That is bad.  Can you send a test case that demonstrates this behaviour?
 
 | If I have..
 |
 | data AVL e = E
 | | N !(AVL e) e !(AVL e)
 | .. etc
 |
 | then presumably this..
 |
 | case avl of N l e r - N (f l) e r
 |
 | desugars to something like ..
 |
 | case avl of N l e r - let l' = f l
 | in l' `seq` r `seq` N l' e r
 |
 | but IMO it should desugar to..
 |
 | case avl of N l e r - let l' = f l
 | in l' `seq` N l' e r
 
 I agree.  If it doesn't please let me know!
 

Although I have not looked into this much, My guess is it is an issue in
the simplifier, normally when something is examined with a case
statement, the simplification context sets its status to 'NoneOf []',
which means we know it is in WHNF, but we don't have any more info about
it. I would think that the solution would be to add the same annotation
in the simplifier to variables bound by pattern matching on strict data
types?

Just a theory. I am not sure how to debug this in ghc without digging
into it's code.

John


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: help from the community?

2007-02-03 Thread John Meacham
On Mon, Jan 29, 2007 at 10:08:59AM +0100, Andres Loeh wrote:
  I didn't fully understand this requirement.  If Haskell-prime gets
  rank-2 or rank-n types, then do we need to restrict constructors in this
  way?
 
 Ok, this really boils down to the question of whether we do rank-2 or
 rank-n types. I'm biased, because I actually use rank-n types
 frequently, and feel somewhat limited by the rank-2 restrictions.  I
 don't know how many people actually do, though. I can understand
 Iavor's points that rank-2 might be easier to explain, but at least
 GHC's rank-n extension has a very detailed paper explaining it, so I
 guess it's one of the better documented extensions.

I would say there is not much point in doing just rank-2. Once you know
how to do rank-n (and we do, thanks to SPJ's great paper) then it is
just as easy to implement as rank-2. Perhaps even moreso since it is a
rather elegant general change to the type inferencer rather than a
special case.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Global variables

2007-02-01 Thread John Meacham
On Thu, Feb 01, 2007 at 04:51:39PM +, David House wrote:
 I think that's too safe-looking. Anything that translates to something
 involving unsafe* should be tagged with 'unsafe' somewhere as well.
 Also, as unsafe* is still compiler specific, I think a pragma is
 probably most appropriate:

then pretty much everything will have to be 'unsafe' :) look inside of
how the libraries are implemented and they all involve unsafe operations
at some point, 'unsafe' does not mean unsafe always, it means it is up
to the user to provide proofs of certain properties rather than the
compiler. when such a proof is provided and abstracted by an API, then
it is safe.


As to this particular extension, depending on the exact details it can
be safe or unsafe and make different demands on the implementation.
luckily, pretty much all of this was worked out in a discussion a while
ago, the trick was to create a new type 'ACIO' which contained only
'good' top level operations. There will be an 'unsafeIOToACIO' of
course, I mean, ACIO functions have to be implemented somehow. :)

John
 
-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


New Layout Rule

2006-12-08 Thread John Meacham
Motivated by some recent discussion, I thought I would explore the
possibilty of formalizing the haskell layout rule without the dreaded
parse-error clause, as in, one that can be completly handled by the
lexer.

motivated by that I have written a little program that takes a haskell
file with layout on stdin and spits out one without layout on stdout.

it can be gotten here:
darcs get http://repetae.net/repos/getlaid/

the code is designed to make the layout algorithm completly transparent,
so that we might experiment with it. The function layout in 'Layout.hs'
is the single and complete layout algorithm and the only thing that need
be modified by experimentors.

I have come up with a simple improvement to the algorithm given in the
paper that seems to catch a very large number of layouts. basically,
whenever it comes across something that must come in matched pairs (, ), case
of, if then. it pushes a special context onto the stack, when it comes
across the closing token, it pops every layout context down to the
special context.

there is a special case for in that causes it to pop only up to the
last context created with a let, but not further.

here is the complete algorithm (with my modification, sans the
parse-error rule):
 
 data Token = Token String | TokenVLCurly String !Int | TokenNL !Int 
 deriving(Show)
 
 data Context = NoLayout | Layout String !Int

 -- the string on 'Layout' and 'TokenVLCurly' is the token that
 -- created the layout, always one of where, let, do, or of
 
 layout :: [Token] - [Context] - [Token]
 layout (TokenNL n:rs) (Layout h n':ls)
 | n == n' = semi:layout rs (Layout h n':ls)
 | n  n' = layout rs (Layout h n':ls)
 | n  n' = rbrace:layout (TokenNL n:rs) ls
 layout (TokenNL _:rs) ls = layout rs ls
 layout (TokenVLCurly h n:rs) (Layout h' n':ls)
 | n = n' = lbrace:layout rs (Layout h n:Layout h' n':ls)
 | otherwise = error inner layout can't be shorter than outer one
 layout (TokenVLCurly h n:rs) ls = lbrace:layout rs (Layout h n:ls)
 layout (t@(Token s):rs) ls | s `elem` fsts layoutBrackets = t:layout rs 
 (NoLayout:ls)
 layout (t@(Token s):rs) ls | s `elem` snds layoutBrackets = case ls of
 Layout _ _:ls - rbrace:layout (t:rs) ls
 NoLayout:ls - t:layout rs ls
 [] - error $ unexpected  ++ show s
 layout (t@(Token in):rs) ls = case ls of
 Layout let n:ls - rbrace:t:layout rs ls
 Layout _ _:ls - rbrace:layout (t:rs) ls
 ls - t:layout rs ls
 layout (t:rs) ls = t:layout rs ls
 layout [] (Layout _ n:ls) = rbrace:layout [] ls
 layout [] [] = []

 layoutBrackets = [ (case,of), (if,then), 
((,)), ([,]), ({,}) ]

now. there are a few cases it doesn't catch. the hanging case at the end
of a guard for instance, I believe this can be solved easily by treating 

'|' and '='  as opening and closing pairs in lets and wheres
'|' and '-' as opening and closing pairs in case bodies.

it is easy to see which one you are in by looking at the context stack.


commas are trickier and are the only other case I think we need to
consider.

I welcome people to experiment and send patches or brainstorm ideas, I
have what I believe is a full solution percolating in my head, but am
unhappy with it, I am going to sleep on it and see if it crystalizes by
morning. In the meantime, perhaps someone can come up with something
more elegant for dealing with the remaining cases. or at least find some
real programs that this code breaks down on!

(bug fixes for the lexer and everything are very much welcome. it will
probably choke on some ghc extensions that would be trivial to add to
the alex grammar)

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: New Layout Rule

2006-12-08 Thread John Meacham
On Fri, Dec 08, 2006 at 03:26:30PM +, Ian Lynagh wrote:
 On Fri, Dec 08, 2006 at 02:33:47AM -0800, John Meacham wrote:
  Motivated by some recent discussion, I thought I would explore the
  possibilty of formalizing the haskell layout rule without the dreaded
  parse-error clause, as in, one that can be completly handled by the
  lexer.
 
 There was some discussion about that a while ago on this list, e.g.
 http://www.haskell.org/pipermail/haskell-prime/2006-March/000915.html
 and other subthreads in that thread.
 
 I'd still love to see a replacement which can be a separate phase
 between lexing and parsing, even if it means we need to lay some things
 out differently or tweak other bits of the syntax.

let isn't an issue (at least not for the reason specified in that
mail). It is taken care of properly in the version I posted. the trick
is to annotate each layout context with what caused it to occur. when
you reach an in rather than popping up to the most recent NoLayout
(as you would with a bracket) you pop up to the most recent layout
context that was started with a let. (if such a context doesn't exist,
it is a syntax error)

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Proposal for stand-alone deriving declarations?

2006-11-01 Thread John Meacham
On Wed, Nov 01, 2006 at 03:15:38PM -0600, Brian Smith wrote:
 How an instance is defined (explicitly or derived) should have nothing to do
 with how it is imported/exported in a module.
 
 In particular, I think having features like :
 import M1 hiding (instance C T)
 and
module M hiding (instance C T)
 would eliminate the need for special-case handling of derived instances (if
 two imported modules happen to derive the same instances, you can just hide
 the instances from one of them). Instance hiding is an important feature in
 its own right.

selective importing and exporting of instances is a really tricky
technical issue for a lot of reasons, and a bad idea for many others.
For a quick example, imagine a Set created with some operations using
one Ord instance and other operations using another. the globalness of
instance declarations is a great tool.

Fortunately, newtype deriving (hopefully extended as I have mentioned on
this thread) and rank-n polymorphism make it pretty much unneeded.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Proposal for stand-alone deriving declarations?

2006-10-29 Thread John Meacham
On Mon, Oct 09, 2006 at 01:19:38PM +0100, Simon Peyton-Jones wrote:
 |  I propose to add a top-level declaration on the form:
 | 
 |  'deriving' qtycls 'for' qtycon
 | 
 |  which produces the same instance as a deriving clause in the
 |  declaration of the datatype or newtype would.
 | 
 | If this is added (whatever the syntax), you'd also want to permit
 multiple
 | identical derived instances.
 
 Perhaps so.  This might generate duplicate code (one for each decl) but
 it'd be guaranteed identical since it's generated by a deriving clause.
 
 It'd require some .hi file support, to record that an instance came from
 a 'deriving' decl.
 
 I'm inclined to wait until someone asks for it for real as it were.

I was actually going to request this, but thought it might not play nice
with separate compilation that well. but if the ghc folks don't think it
is too much trouble, I would really like that feature.

I believe you can output some linker pragmas to have the duplicate
bodies merged into one so you won't end up with excess code in your
executable.. but would have to look it up to be sure.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Proposal for stand-alone deriving declarations?

2006-10-29 Thread John Meacham
On Fri, Oct 06, 2006 at 10:39:39AM -0500, Michael Shulman wrote:
 On 10/6/06, John Hughes [EMAIL PROTECTED] wrote:
 deriving (Eq Foo, Ord Foo)
 
 instead of
 
 deriving (Eq, Ord) for Foo
 
 So what does
 
 newtype Foo a = Foo a
 newtype Bar b = Bar b
 class C a b
 deriving (C (Foo a) (Bar b))
 
 mean?  I could see it meaning any or all of the following:
 
 instance (C (Foo a) b) = (C (Foo a) (Bar b))
 instance (C a (Bar b)) = (C (Foo a) (Bar b))
 instance (C a b) = (C (Foo a) (Bar b))


this is why we should make this explicit when deriving complex newtype
instances, so we would write exactly the instance we want to derive:

 deriving (C (Foo a) b) = (C (Foo a) (Bar b))
 deriving (C a (Bar b)) = (C (Foo a) (Bar b))
 deriving (C a b) = (C (Foo a) (Bar b))

respectively.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Indentation of If-Then-Else

2006-10-24 Thread John Meacham
On Tue, Oct 24, 2006 at 05:29:58PM +0100, Neil Mitchell wrote:
  Actually if-then-else isn't used that often today. Most programmers
  gave it up in favor of guards.
 
 I question both these statements. Can you cite some evidence here?
 
 I have 501 if statements in my current project. Yhc has 626. Hoogle
 has 101. If's seem pretty well used to me!

920 in jhc. I win! :)

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: (Pattern) Guards in lambdas

2006-10-19 Thread John Meacham
On Thu, Oct 19, 2006 at 12:55:48PM +0100, Simon Marlow wrote:
 As for extending lambda to allow multiple guards and/or multiple pattern
 matches, I don't think we need that either.  Lambda is a quiet syntax
 and will be lost at the beginning of a sequence of pattern
 matches/guards; it's best used for simple lambda expressions,
 complicated pattern matches should be done using function equations.

I think I would like to allow a (single) guard on a lambda. for
assertion checking, I am a sucker for assertion checking and the more
lightweight the better when it comes to that sort of thing.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Here-docs in Haskell source

2006-09-23 Thread John Meacham
I would also like to see these. I like the python syntax


stuff...


but really most anything will do.

the triple quote doesn't eat any usable syntax though and won't require
any special cases in the parser so I would much prefer something like
that.

John


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: map and fmap

2006-08-21 Thread John Meacham
On Fri, Aug 18, 2006 at 05:30:53PM +0200, John Hughes wrote:
 on students having Haskell' books. All that time, students would write map
 instead of mapList because that's what the book says, and get stuck with
 incomprehensible error messages. Is it really worth an incompatible change
 in the library functions used by all beginners, just to rename fmap to map?
 It seems to me that the gain from a change is very small, and the cost 
 considerable.

Yeah, the change doesn't seem worth it to me. And I still have concerns
about ambiguity errors, if a beginner ever has to use an explicit type
signature it sort of ruins the whole type inference benefit. I think
everyone has tried to write 

class Cast a b where
cast :: a - b

at some point but found it not very useful as whenever it was fed or
used as an argument to another overloaded function, you ended up with
ambiguity errors.

with all the added generality being added all over the place, you need
collections of functions that work on concrete data types to 'fix'
things every now and again. lists are common enough that I think they
deserve such 'fixing' functions. And it has nothing to do with newbies.

having to write type annotations when not even doing anything tricky is
not an acceptable solution for a type infered language.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: WordPtr,IntPtr,IntMax,WordMax

2006-05-12 Thread John Meacham
On Fri, May 12, 2006 at 10:19:18AM +0100, Simon Marlow wrote:
 Especially since even:
 
 checking Haskell type for intmax_t... not supported
 checking Haskell type for uintmax_t... not supported
 
 aren't universal :)
 
 Well, yes.  Any suggestions for what to do here?  Make a best guess?

What is the problem here? are intmax_t and uintmax_t not on all systems?

there is a handy autoconf macro that generates an appropriate ISO
compliant inttypes.h if one doesn't exist on a system.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org//mailman/listinfo/haskell-prime


Re: raw data access

2006-05-01 Thread John Meacham
On Tue, May 02, 2006 at 12:57:17AM +0200, Johan Henriksson wrote:
 toBinary :: a - [Int]  -- pack data as a string of bytes
 fromBinary :: [Int] - a -- unpack
 binarySize :: a - Maybe Int
 -- number of bytes for this type or Nothing if not fixed
 
 the packing would be compiler dependent since it is not of interest
 to read the content, just to get an easy way of marshalling arbitrary types.

Depending on what you mean, we might already have this, or it might be
impossible in general :)

if you just want to create a reference to an arbitrary haskell type that
you can pass to foreign code, and then recover the original haskell
value from, then the Foreign.StablePtr does just this. it lets you cast
haskell values to plain pointers and back again.

if you want to store the structure in memory, then the Storable class
provides this. I have thought it would be useful to allow
deriving(Storable) with the obvious meaning and adding a 'StorableRef'
that can create a reference to an arbitray storable object. I believe
bulat is working on unboxed arrays that can work like this.
of course, the limitation is that your data types need to be in class
Storable.

since you don't seem to care about compiler independence and if you are
willing to give up architecture independence, you can probably use
storable to serialize structures to disk, but do so at your own risk.

pretty much any solution will require a typeclass to guide and restrict
it, otherwise how would the compiler handle function types? it can't
serialize the body of functions in general, or handle cyclic structures
or pointers from the serialized version to live haskell structures and
how they interect with the GC?

You also might want to look at the various Binary libraries out there.
perhaps one fits your needs.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: FFI proposal: allow some control over the scope of C headerfiles

2006-04-25 Thread John Meacham
On Tue, Apr 25, 2006 at 09:40:58AM +0100, Simon Marlow wrote:
 Admittedly I haven't tried this route (not including *any* external
 headers at all when compiling .hc files).  It might be possible, but you
 lose the safety net of compiler-checked calls.

yeah, perhaps a hybrid approach of some sort, when building the package,
use the system headers, but then include generated prototypes inside the
package-file and don't propagate #includes once the package is built.

or just an intitial conformance check against the system headers somehow
(?), but then only use your own generated ones when actually compiling
haskell code. It would be nice to never need to include external headers
in .hc files.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: unsafePerformIO and cooperative concurrency

2006-04-25 Thread John Meacham
It was pointed out that you can't necessarily know what routines to
avoid in unsafePerformIO without mandating certain things _don't_ use
concurrency, rather than that, how about the following:

Whether an implementation can yield to another thread inside an
unsafePerformIO action is implementation dependent, however an
implementation should not 'go wrong' 

hmm.. better term than 'go wrong'? The intent is calling concurrent
routines inside of unsafePerformIO is okay, but they perhaps might not
yield to other threads or something like sharing might be lost (but 
correctness is preserved).

I think implementations should be able to handle this.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: unsafePerformIO and cooperative concurrency

2006-04-24 Thread John Meacham
On Mon, Apr 24, 2006 at 01:57:57PM +0100, Simon Marlow wrote:
 Given that unsafePerformIO is (perhaps) to be part of the Haskell'
 standard, the combination of unsafePerformIO and cooperative concurrency
 introduces some interesting cases that will probably have to be declared
 to be undefined in the standard - what happens when you yield or do some
 I/O inside unsafePerformIO?
 
I put a small note on the wiki about this saying behavior should be
implementation specific. I don't think we should try to define any
particular behavior for unsafePerformIO trickiness.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: FFI proposal: allow some control over the scope of C header files

2006-04-24 Thread John Meacham
It is my understanding that the FFI foreign imports declare an ABI and
not an API, meaning the exact way to make the foreign call should be
completely deterministic based on just what is in the haskell file
proper. Otherwise, obviously, direct to assembly implementations would
be impossible.

In this sense, include files are always potentially optional, however,
due to the oddness of the C langauge, one cannot express certain calls
without proper prototypes, current haskell implementations take the
straightforward path of relying on the prototypes that are contained in
the system headers, which also incidentally provides some safety net
against improperly specified FFI calls. However, it would also be
reasonable for an implementation to just generate its own prototypes, or
use inline assembly or any other mechanism to implement the FFI ABI
calls properly.

I am not sure what my point is, perhaps just that it is not really a
haskell-prime language issue, but new pragmas are, so perhaps this is in
that regard.

in any case, in jhc a {-# INCLUDE foo.h #-} pragma has the effect of
adding foo.h .. to every foreign ccall declaration in the current
module. Just a handy shortcut, not that I think that behavior should be
codified or anything.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


concurrency guarentees clarification

2006-04-24 Thread John Meacham
I have been twiddling some with the wording of the concurrency
guarentees and want to run them by the list.


the rules I am thinking of adding are:

* every runnable thread is guarenteed to run in a finite amount of time if a
  program reaches a yield-point infinitly often.

* Foreign concurrent calls, handle IO, and all IO actions that directly
  interact with the world outside the current process all must be
  yield-points. (in addition to any yield-points implied by the progress
  guarentee)

The first rule is just to rule out completely brain-dead schedulers and
give a fairly useful fairness guarentee. (in fact, I think it subsumes
the preemptive fairness guarentee as written, as a preemptive
implementation does reach a yield-point infinitly often independently of
what the program is doing)

I originally thought the progress guarentee implied the second, but I
realize that is somewhat UNIX-centric in that all IO must be treated as
potentially blocking. however in an embedded system where for instance
you write directly to the screen buffer rather than a file descriptor
this might not be the case so we should probably be more clear.

I would like to avoid enumerating the yield points explcitly, except
perhaps as a guide saying these library routines are examples of those
in the standard library that must be yield-points according to the
standard. Coming up with a rule rather than a list will make it easier
for users to think about and give guidance (though of course we can't
guarentee) where yield-points should be placed in any implementation
provided extensions.


I don't intend to imply things like all memory access in case it is in
an memory mapped IO region or anything that changes CPU load because
someone might be looking at your CPU usage in /proc should be
yield-points, just those IO actions that explicitly interact with the
outside world. for the correct definition of explicitly. :)

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Concurrency, FFI status

2006-04-21 Thread John Meacham
On Fri, Apr 21, 2006 at 10:01:51AM -0400, Manuel M T Chakravarty wrote:
 Concerning the issue of preemptive versus cooperative concurrency, I
 still think cooperative concurrency is pretty useless.  Is there any
 non-toy application that actually uses Hugs' current cooperative
 concurrency?

A couple of notes

* How many non-toy applications can use hugs at all independent of
concurrency? in a big concurrent app you are most likely going to need
some ghc extension anyway.

* It is unclear that pre-emptiveness even buys you much, standardwise. the
only thing it can give over a cooperative one is better latency and even
that can't be done as oleg pointed out without careful control of when
lazy (pure) code gets evaluated, a similar situation to what one has to
think about with cooperative implementations.

* Hugs does not implement concurrency. A couple tests show that.

 run1 = print foo  run1
 run2 = getLine = print  run2

 main = do
forkIO run1
run2

this should continually print foo while waiting for input on any
haskell-prime implementation due to the progress guarentee. it does not
on hugs, this makes hugs concurrency not really concurrency IMHO, more
like explicit coroutines with an odd interface. (which is the base of a
good cooperative concurrent implementation, but not the same thing)


 Concerning the trouble of Hugs and Jhc to implement preemptive
 concurrency, IMHO that's a significant design flaw in these
 implementations.  Preemptive concurrency is important for many
 applications and, if anything, will become more important with new
 architectures.  Fundamental limits on being able to support this,
 fundamentally limit the application space.  I'd rather not see that
 design flaw being transferred from these implementations to the language
 standard.

It is not a design flaw, it is a choice. pre-emptiveness is not worth
the effort given haskells other properties for many implementation
models. It buys you very little, but implementing it can cause
signifigant run-time overheads compared to cooperative ones for code
that doesn't even use concurrency.

I don't care about the difficulty of implementation, I care about the
generated code and the ability to write standards compliant _and_
efficient haskell prime implementations.



John


--
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: The goals of the concurrency standard?

2006-04-12 Thread John Meacham
Fortunatly, I don't expect these issues to be much of a problem in
practice. (though, they certainly are real issues)

the vast majority of programs, haskell ones included, are either
interactive or batch. an interactive program spends most of its time
waiting for user input or external events, responding, and in general
using very little CPU, this is the sort of app threads are ideal for,
text editors, chat clients, window managers, etc... batch programs are
things like compilers or meresenne prime calcalculators, that tend to
accept input, run for a while, and produce output. however, these types
of programs rarely need concurrency.

not that all programs fall into those categories, one can write their
GUI enabled meresenne prime calculator, and then they will have to worry
about such things. but at least with the standard they can now say 'this
requires the OS threading option' rather than 'this requires GHC'.

in any case, the situation you describe has been the case in GHC for a
long time and has not seemed to hurt the use of concurrency for writing
a lot of useful apps.

However, I am also of the mind that preemtiveness alone doesn't buy
enough to make the runtime cost of locking worth it which is why I plan
for jhc to be fully cooperative or fully OS threaded with no middle
ground. but the situation is different in compilers such as nhc, where
preemptiveness can be added relatively easily due to its run-time design
and absolute speed was never a goal. In any case, the standard should
admit a range of implementations.

though, your erlang example reminds me of a truely horrid hack I did
with jhc once when experimenting with concurrency models, link two
instances of haskell programs together and have them communicate via the
FFI while running in different OS threads :)

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: preemptive vs cooperative: attempt at formalization

2006-04-12 Thread John Meacham
On Wed, Apr 12, 2006 at 10:58:32AM +0100, Simon Marlow wrote:
 I don't know what it means for a thread to have value _|_.  A thread
 is defined by its observable effects, threads don't have values.

sure they do, the value is just usually discarded. cooperative
implementations are just the ones that don't have that luxury. :)

 What if one of the threads never yields in a cooperative system?  Even
 if it isn't calculating _|_, if it's just endlessly doing some pointless
 IO?

All real IO would have to effectively be a potential yield point. This
is in practice assumed of any state threading implementation, but
perhaps we should make it part of the standard to be sure. by real IO I
mean reading/writing file descriptors and other interaction with the
real world and not just anything in the IO monad. I don't think we need
to do anything like enumerate the yield points or anything (except the
'yield' function of course), meeting the progress guarentee ensures a
liberal sprinkling of them throughout the standard libs, in particular
on any file descriptor read or write.

Of course, if the user really wanted to, they could cheat using
something like mmaping a file into memory and writing to that in a tight
loop, but hopefully any user doing something like that would be aware of
the ramifications. (heck, it would probably lock up the old version of
ghc too if the tight loop thread never needed to GC)

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: The goals of the concurrency standard?

2006-04-12 Thread John Meacham
On Wed, Apr 12, 2006 at 11:19:53AM +0100, Simon Marlow wrote:
 I'll argue that point :)  GHC makes run-time checks at safe points and
 implements preemptive concurrency.  Cooperative scheduling is when the
 *programmer* has to insert the safe points.

the programmer of the standard libraries or low level FFI interfaces.
not the end programmer. I would be highly surprised if anyone other than
system or very low level library implementors ever actually needed to
use an explicit 'yield'. certainly a whole lot less often than they have
to add 'seq's and it is a lot more clear when they are needed :)

 The safe points don't even have to be very often: in GHC the context
 switch check is made after every 4k of allocation.

indeed, which means GHC technically doesn't meet the preemptive
requirements since a tight mathematical non-allocating loop can halt it.

in order to do true preemption, you'd need to respond to SIGALRM or
something like that, which can be quite tricky.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: FFI, safe vs unsafe

2006-04-12 Thread John Meacham
On Wed, Apr 12, 2006 at 12:07:06PM -0400, Wolfgang Thaller wrote:
 3) There might be implementations where concurrent calls run on a  
 different thread than nonconcurrent calls.

this is necessarily true for non-OS threaded implementations. there is
no other way to wait for an arbitrary C call to end than to spawn a
thread to run it in.

This doesn't have to do with bound threads, to support those you just
need to make sure the other thread you run concurrent calls on is always
the same thread. it is the cost of setting up the mechanism to pass
control to the other thread and wait for the response that is an issue.
turning a single call instruction into several system calls, some memory
mashing and a context switch or two.

I object to the idea that concurrent calls are 'safer'. getting it wrong
either way is a bug. it should fail in the most obvious way rather than
the way that can remain hidden for a long time.

in any case, blocking is a pretty well defined operation on operating
systems, it is when the kernel can context switch you away waiting for a
resource, which is the main use of concurrent calls. the ability to use
them for long calculations in C is a sort of bonus, the actual main use
is to ensure the progress guarentee, that if the OS is going to take
away the CPU because one part of your program is waiting for something
another part of your program can make progress. Which is why I'd prefer
some term involving 'blocking' because that is the issue. blocking calls
are exactly those you need to make concurrent in order to ensure the
progress guarentee. sayng something like 'takesawhile' muddies things,
what is a while? not that concurrent calls shouldn't be used for long C
calculations, it is quite a nice if uncommonly needed perk, but I don't
want the report to confuse matters by making a quantitative real matter,
meeting the progress guarentee, with a qualitiative one does this take
a while. I'd actually prefer it if there were no default and it had to
be specified in neutral language because I think this is one of those
things I want FFI library writers to think about.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-12 Thread John Meacham
On Wed, Apr 12, 2006 at 09:21:10AM -0400, Jan-Willem Maessen wrote:
 Though, to be fair, an awful lot of Prelude code didn't work in pH  
 unless it was re-written to vary slightly from the specification.  So  
 the assumption of laziness was more deeply embedded than the spec was  
 willing to acknowledge.

out of curiosity what sort of things had to be rewritten? I have been
toying with the idea of relaxing sharing to help some optimizations and
was curious what I was in for.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: preemptive vs cooperative: attempt at formalization

2006-04-12 Thread John Meacham
On Wed, Apr 12, 2006 at 05:50:40PM +0100, Malcolm Wallace wrote:
 The argument John was making is that this is a useful distinguishing
 point to tell whether your concurrent implementation is cooperative or
 preemptive.  My argument is that, even if you can distinguish them in
 this way, it is not a useful distinction to make.  Your program is
 simply wrong.  If you have a sequential program whose value is _|_, your
 program is bad.  If you execute it in parallel with other programs, that
 does not make it any less bad.  One scheduler reveals the wrongness by
 hanging, another hides the wrongness by letting other things happen.  So
 what?  It would be perverse to say that the preemptive scheduler is
 semantically better in this situation.

Oh, I didn't mean it was necessarily a useful quality to the end
programmer, I was actually just trying to make the point you were making
that such programs are incorrect and getting the non-termination case
over with. So we can get to the fairness discussion without adding
caveats like if no thread is in an infinite loop. But I didn't want to
just say assuming your program is correct without giving some
indication of what that actually means for a program to be correct. In
any case, it is something we can point to and say this! this is a
difference! whether it is a useful one or not.

now for the contrived counter-example :) 
start two threads, one trying to prove goldbachs conjecture, the other
trying to find a refutation. in a preemptive system this will terminate*,
in a cooperative system it may not.

John

* insert goedel incompleteness caveat.

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: FFI, safe vs unsafe

2006-04-12 Thread John Meacham
On Wed, Apr 12, 2006 at 04:40:29PM -0500, Taral wrote:
 pure - side-effect free
we don't really need pure because not having an IO type in the result
implies pure.
John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: FFI, safe vs unsafe

2006-04-12 Thread John Meacham
On Thu, Apr 13, 2006 at 12:43:26AM +0200, Marcin 'Qrczak' Kowalczyk wrote:
 What about getaddrinfo()? It doesn't synchronize with the rest of the
 program, it will eventually complete no matter whether other threads
 make progress, so making it concurrent is not necessary for correctness.
 It should be made concurrent nevertheless because it might take a long
 time. It does block; if it didn't block but needed the same time for
 an internal computation which doesn't go back to Haskell, it would
 still benefit from making the call concurrent.

getaddrinfo most definitly blocks so should be made concurrent, it uses
sockets internally. The progress guarentee is meant to imply if
something can effectivly use the CPU it will be given it if nothing else
is using it not that it will just eventually complete. Performing a
long calculation is progress whether in haskell or C, waiting on a file
descriptor isn't.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: FFI, safe vs unsafe

2006-04-12 Thread John Meacham
On Wed, Apr 12, 2006 at 07:35:22PM -0400, Wolfgang Thaller wrote:
 John Meacham wrote:
 This doesn't have to do with bound threads, [...]
 
 I brought it up because the implementation you are proposing  
 fullfills the most important feature provided by bound threads,  
 namely to be able to access the thread local state of the main OS  
 thread (the one that runs C main ()), only for nonconcurrent calls,  
 but not concurrent calls. This gives people a reason to specify some  
 calls as nonconcurrent, even when they are actually expected to  
 block, and it is desirable for other threads to continue running.
 This creates an implementation-specific link between the concurrent/ 
 nonconcurrent question and support for OS-thread-local-state. I would  
 probably end up writing different code for different Haskell  
 implemlementations in this situation.

Oh, I made that proposal a while ago as a first draft, bound threads
should be possible whether calls are concurrent or not, I am not
positive I like the ghc semantics, but bound threads themselves pose not
much more overhead than supporting concurrent in the first place (which
is a fairly substantial overhead to begin with). but that doesn't matter
to me if there isn't a performance impact in the case where they arn't
used. 

However, in order to achieve that we would have to annotate the foreign
functions with whether they use thread local state. it would pretty much
be vital for implementing them efficiently on a non OS-threaded
implemenation of the language. you need to perform a
stack-pass-the-baton dance between threads to pass the haskell stack to
the right OS thread which is a substantial overhead you can't pay just
in case it might be running in a 'forkOS' created thread. Checking
thread local state for _every_ foregin call is definitly not an option
either. (but for specificially annotated ones it is fine.) ghc doesn't
have this issue because it can have multiple haskell threads running at
once on different OS threads, so it just needs to create one that
doesn't jump between threads and let foreign calls proceed naturally.
non-os threaded implementations have the opposite problem, they need to
support a haskell thread that _can_ (and does) jump between OS threads.
one pays the cost at thread creation time, the other pays the cost at
foreign call time. the only way to reconcile these would be to annotate
both. (which is perfectly fine by me if bound threads are needed, which I
presume they are)

Oddly enough, depending on the implementation it might actually be
easier to just make every 'threadlocal' function fully concurrent. you
have already paid the cost of dealing with OS threads.

 Calculations done by foreign calls are not a bonus, but an  
 important use case for concurrent calls. Think of a library call that  
 causes a multimedia library to recompress an entire video file;  
 estimated time required is between a few seconds and a day. In a  
 multithreaded program, this call needs to be concurrent. It is true  
 that the program will still terminate even if the call is  
 nonconcurrent, but in the real world, termination will probably occur  
 by the user choosing to force quit an application that is not  
 responding (also known as sending SIGTERM or even SIGKILL).

they are a bonus in that you can't run concurrent computing haskell
threads at the same time. you get free concurrent threads in other
languages that you would not get if the libraries just happened to be
implemented in haskell. However, if the libraries were implemented in
haskell, you would still get concurrency on OS blocking events because
the progress guarentee says so.

 The question can I provide a certain guarantee or not could be  
 answered with no by default to flatten the learning curve a bit. My  
 objection against having no default is not very strong, but I do  
 object to specifying this in neutral language. This situation does  
 not call for neutral language; rather, it has to be made clear that  
 one of the options comes with a proof obligation and the other only  
 with a performance penalty.

you seem to be contradicting yourself, above you say a performance
penalty is vitally important in the GUI case if a call takes too long,
but here you call it 'just a performance penalty'. The overhead of
concurrent calls is quite substantial. Who is to say whether a app that
muddles along is better or worse than one that is generally snappy but
has an occasional delay.

Though, I am a fan of neutral language in general. you can't crash the
system like you can with unsafePerformIO, FFI calls that take a while
and arn't already wrapped by the standard libraries are relatively rare.
no need for strong language.


John


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: FFI, safe vs unsafe

2006-04-12 Thread John Meacham
On Wed, Apr 12, 2006 at 11:37:57PM -0400, Wolfgang Thaller wrote:
 John Meacham wrote:
 
 However, in order to achieve that we would have to annotate the  
 foreign
 functions with whether they use thread local state.
 
 I am not opposed to that; however, you might not like that here  
 again, there would be the safe, possibly inefficient default choice,  
 which means might access thread local data, and the possibly more  
 efficient annotation that comes with a proof obligation, which says  
 guaranteed not to access thread local data.
 The main counterargument is that some libraries, like OpenGL require  
 many *fast* nonconcurrent, nonreentrant but tls-using calls (and,  
 nost likely, one reentrant and possibly concurrent call for the GLUT  
 main event loop). Using OpenGL would probably be infeasible from an  
 implementation which requires a notls annotation to make foreign  
 imports fast.

this is getting absurd, 95% of foreign imports are going to be
nonreentrant, nonconcurrent, nonthreadlocalusing. Worrying about the
minor inconvinience of the small chance someone might accidentally
writing buggy code is silly when you have 'peek' and 'poke' and the
ability to just deadlock right out there in the open.

The FFI is inherently unsafe. We do not need to coddle the programer who
is writing raw FFI code.  

_any_ time you use the FFI there are a large number of proof obligations
you are commiting to that arn't necessarily apparent, why make these
_very rare_ cases so visible. There is a reason they arn't named
'unsafePoke' and 'unsafePeek', the convinience of using the names poke
and peek outweighs the unsafety concern becaues you are already using
the FFI and already know everything is unsafe and you need to be
careful. these problems can't even crash the runtime, way safer than a
lot of the unannotated routines in the FFI.


 it would pretty much
 be vital for implementing them efficiently on a non OS-threaded
 implemenation of the language.
 
 True, with the implementation plan you've outlined so far.
 Have you considered hybrid models where most threads are state  
 threads (all running in one OS thread) and a few threads (=the bound  
 threads) are OS threads which are prevented from actually executing  
 in parallel by a few well-placed locks and condition variables? You  
 could basically write an wrapper around the state threads and  
 pthreads libraries, and you'd get the best of both worlds. I feel it  
 wouldn't be that hard to implement, either.

well, I plan a hybrid model of some sort, simply because it is needed to
support foreign concurrent calls. exactly where I will draw the line
between them is still up in the air.

but in any case, I really like explicit annotations on everything as we
can't predict what future implementations might come about so we should
play it safe in the standard.

 Oddly enough, depending on the implementation it might actually be
 easier to just make every 'threadlocal' function fully concurrent. you
 have already paid the cost of dealing with OS threads.
 
 Depending on the implementation, yes. This is the case for the  
 inefficient implementation we recommended for interpreters like Hugs  
 in our bound threads paper; there, the implementation might be  
 constrained by the fact that Hugs implements cooperative threading in  
 Haskell using continuation passing in the IO monad; the interpreter  
 itself doesn't even really know about threads. For jhc, I fell that a  
 hybrid implementation would be better.

yeah, what I am planning is just providing a create new stack and jump
to a different stack(longjmp) primitive, and everything else being
implemented in haskell as a part of the standard libraries.  (with
liberal use of the FFI to call things like pthread_create and epoll)

so actually fairly close to the hugs implementation in that it is mostly
haskell based, but with some better primitives to work with. (from what
I understand of how hugs works)



 you seem to be contradicting yourself, above you say a performance
 penalty is vitally important in the GUI case if a call takes too  
 long, [...]
 
 I am not. What I was talking about above was not performance, but  
 responsiveness; it's somewhat related to fairness in scheduling.
 If a foreign call takes 10 microseconds instead of 10 nanoseconds,  
 that is a performance penalty that will matter in some circumstances,  
 and not in others (after all, people are writing real programs in  
 Python...). If a GUI does not respond to events for more than two  
 seconds, it is badly written. If the computer or the programming  
 language implementation are just too slow (performance) to achieve a  
 certain task in that time, the Right Thing To Do is to put up a  
 progress bar and keep processing screen update events while doing it,  
 or even do it entirely in the background.
 Of course, responsiveness is not an issue for non-interactive  
 processes, but for GUIs it is very important.

at some point

Re: FFI, safe vs unsafe

2006-04-11 Thread John Meacham
On Tue, Apr 11, 2006 at 09:13:00AM +0100, Simon Marlow wrote:
 What are the conclusions of this thread?
 
 I think, but correct me if I'm wrong, that the eventual outcome was:
 
  - concurrent reentrant should be supported, because it is not 
significantly more difficult to implement than just concurrent.

It wasn't a difficulty of implementation issue, it was whether there
were unavoidable performance traeoffs. I have no problem with very
difficult things if they are well specified and don't require
unreasonable concessions elsewhere in the design.

in any case, I think the __thread local storage trick makes this fast
enough to implement everywhere and there were strong arguments for not
having it causing issues for library developers.


  - the different varieties of foreign call should all be identifiable,
because there are efficiency gains to be had in some implementations.

indeed. 

  - the default should be... concurrent reentrant, presumably, because
that is the safest.  (so we need to invert the notation).

well, I like to reserve the word 'safe' for things that might crash the
runtime, unsafePerformIO, so making things nonconcurrent isn't so much
something unsafe as a decision. I'd prefer nonconcurrent be the default
because it is the much more common case and is just as safe in that
regard IMHO.

 So, can I go ahead and update the wiki?  I'll try to record the
 rationale from the discussion too.

sure.

 I'd like to pull out something from the discussion that got a bit lost
 in the swamp: the primary use case we have for concurrent reentrant is
 for calling the main loop of a GUI library.  The main loop usually never
 returns (at least, not until the application exits), hence concurrent,
 and it needs to invoke callbacks, hence reentrant.

this is a pain. (making various libraries main loops play nice
together). not that it is a haskell specific problem though I guess we
have to deal with it.  I was thikning of using something like
http://liboop.org/ internally in jhc.. but am not sure and would prefer
a pure haskell solution without compelling reason to do otherwise.


John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-11 Thread John Meacham
On Tue, Apr 11, 2006 at 09:53:54AM +0100, Simon Peyton-Jones wrote:
 Whether it should be in a class is a rather separate discussion.  In a
 way we already sold out when we allowed seq to escape from the
 type-class world.  Perhaps deepSeq is worse (because it traverses data
 structures) but not obviously. 

well, there is a difference there in that 'seq' is unimplementable in
haskell, so the design comitee had freedom to implement it however they
wanted. however, now that we have seq, a deepSeq is perfectly
implementable* in haskell using a typeclass, which is a strong argument
for making it have one. 

* dynamic idempotent issues aside. 

in any case, if it were to be in the standard, I'd put it in a typeclass
and give a haskell translation with a note that implemenations are free
to implement optimized versions under the hood as long as the observable
effect is the same but you can't count on anything better than the plain
old recursive seq definition.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Signals + minimal proposal (was Re: asynchronous exceptions)

2006-04-11 Thread John Meacham
On Tue, Apr 11, 2006 at 08:54:32AM +0100, Simon Marlow wrote:
 now If I have a handler registered that throws an exception to the
 current thread, what happens?  handleLoop is aborted, the exception is
 propagated to the top level of the thread, where the top-level exception
 handler calls exitWith again, and promptly deadlocks because exitMVar is
 already empty.

True, the handlers probably should run in their own thread then. hmm..
will think more on these issues...

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-11 Thread John Meacham
On Tue, Apr 11, 2006 at 12:15:57PM +0100, Simon Peyton-Jones wrote:
 | well, there is a difference there in that 'seq' is unimplementable in
 | haskell, so the design comitee had freedom to implement it however
 they
 | wanted. 
   
   class Eval a where
 seq :: a - b - b
 
   instance Eval (a,b) where
  seq (_,_) b = b
 
   instance Eval [a] where
  seq [] b = b
  seq (_:_) b = b

instance Eval (a - b) where


?

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Exceptions

2006-04-11 Thread John Meacham
On Tue, Apr 11, 2006 at 01:24:07PM +0100, Simon Marlow wrote:
 Attached is another variant of the extensible exceptions idea, it
 improves on the previous designs in a couple of ways:  there's only one
 catch  throw, regardless of what type you're throwing or catching.
 There is an extensible hierarchy of exceptions, and you can catch and
 re-throw subclasses of exceptions.

I made the catch and throw separate so the decision as to whether to
include imprecice exceptions and extensible extensions can be made
independently.  

that and

throw x /= ioError x

ioError x  return ()  - IO _|_  (only _|_ when IO action executed)
throw x  return () - _|_

ioError x `seq` ()  - ()
throw x `seq` () - _|_

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Exceptions

2006-04-11 Thread John Meacham
On Tue, Apr 11, 2006 at 05:35:12AM -0700, John Meacham wrote:
 throw x  return () - _|_

hmm.. actually is this true? hmm.. seq and IO always mixed oddly.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Exceptions

2006-04-11 Thread John Meacham
On Tue, Apr 11, 2006 at 01:43:18PM +0100, Simon Marlow wrote:
 yes, when I say one throw I was referring to the argument type, not
 the return type.  We should still have ioError - although it would
 probably be better named throwIO:

Ah, I see what you mean now.

would it be possible to use Typeable1 to just catch 'ArithException a'
for any Typeable a? It seems like it should be, but I have not used
Typeable1 much.


John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: limitations of newtype-derivings (fixed)

2006-04-11 Thread John Meacham
On Tue, Apr 11, 2006 at 02:19:22PM +0100, Simon Peyton-Jones wrote:
 |  newtype Id = Id Int
 |  data Term = ...
 |  newtype Subst = Subst (IM.IntMap Term)
 | 
 | ideally, we'd like an MapLike instance, but we'd have to tediously
 write
 | it ourselves. if we allow the supergeneralized newtype deriving, we
 can do:
 | 
 |  deriving(MapLike Id Term Subst)
 
 Now things aren't so clear.  You are assuming that we have an instance
   instance MapLike Int a (IntMap a)
 
 But suppose we also had an explicit instance decl for
   instance MapLike Int Term Subst
 which we might.  Which would the 'deriving' base its instance on? We
 might also have an explicit instance 
   instance MapLike Id a (IntMap a)
 Now it's even less obvious which to use.

good point. We would probably want to specify which instance we are
deriving it from with something like

deriving (MapLike Int a (IntMap a) = MapLike Id Term Subst)

being explicit seems better than making up some resolution rules.


 What if the newtype was buried more deeply.  Can we say
   deriving( C (Foo Id) )
 if we happen to have an instance for C (Foo Int) around already?  Here
 the newtype isn't at the top level of the class argument.

I had not thought about that. A use doesn't occur to me off the top of
my head, but that is probably just because it hasn't been available so I
have not considered uses of it.

I see no particular problem assuming all the constructors of Foo and Id
and the methods of C are in scope.

 GHC's newtype-deriving mechanism is very precise: it unwraps exactly one
 layer of exactly one newtype.  It's attractive to go further, as you
 describe, but it'd need to be tightly specified.  (And of course, that
 increases the complexity of the overall language.)

yeah, the restriction that you can only newtype derive the last argument
has always bothered me with its arbitraryness based solely on syntax. so
getting rid of that restriction would simplify the language. coderiving
(is there a better term?) instances based on multiple newtypes is a true
new feature, but I don't see any issues from an implementation
standpoint, just the same problem of defining it without saying the
same method

We also have a few derivings which are special,
'Show,Read,Typeable,Data' that don't follow the newtype deriving rule,
but I am not proposing we change them. 

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: preemptive vs cooperative: attempt at formalization

2006-04-11 Thread John Meacham
On Tue, Apr 11, 2006 at 09:05:12PM -0700, [EMAIL PROTECTED] wrote:
  [Rule 1]
  * in a cooperative implementation of threading, any thread with value
_|_ may cause the whole program to have value _|_. In a preemtive one,
this is not true.
 
 I'm afraid that claim may need qualifications:
 
  1. if there is only one runnable thread, if it loops in pure code,
 the whole program loops -- regardless of preemptive/cooperative
 scheduling.
 
  2. in a system with thread priorities, if the highest priority thread
 loops (in pure code or otherwise), the whole program loops -- again
 irrespective of the preemptive/cooperative scheduling.
 
  3. [a variation of 1 or 2]. A thread that loops in a critical section
 (or holding a mutex on which the other threads wait) loops the whole
 program -- again, irrespective of preemptive/cooperative scheduling.

would the simple qualifier
'if there exists another runnable thread'

solve the issues?

A thread is not runnable if it is waiting on a resource or can't run due
to the priority policy of the scheduler. and it means there is at least
one other thread to switch to.


perhaps we should just make the ability to implement 'merge' and
'nmerge' the difference. though, defining the behavior of those routines
very well could be a harder problem than defining the difference between
preemptive and cooperative in the first place.


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Signals + minimal proposal (was Re: asynchronous exceptions)

2006-04-10 Thread John Meacham
 exitWith, exitWith calss exit_ which kills whole
program immediatly, no need to wait for any other thread to do anything
or even the foregin call running while the signal occured to complete.
(if you don't want to)

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-10 Thread John Meacham




--
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: limitations of newtype-derivings (fixed)

2006-04-08 Thread John Meacham
ooops. sorry, I started with a 'Set' example and moved to a 'Map' one
and didn't fix all the code. here is a fixed version:

=

The newtype deriving extension is one of the most powerful tools for
writing robust, typesafe code. However it suffers from a couple
limitations.

 * you can only newtype derive the last argument to a MPTC.
 * you cannot co-derive an instance for multiple newtype renamings.

it seems that both these can be solved when combined with the other
proposed extension, allowing deriving clauses to be separate from data
definitions.

basically, we would allow deriving anywhere.

 deriving (Show Foo)

means the same thing as

 data Foo = ... 
 deriving (Show)

will derive an instance of Show for Foo.

now we are no longer bound by either of the above constraints..

imagine we have a class

 class MapLike k v m | m - k v where
 insert :: ..
 delete :: ...
 ...

 instance MapLike Int a (IM.IntMap a) where
 insert = IM.insert
  


now, we want a newtype that describes Id's. 

 newtype Id = Id Int
   deriving(Eq,Ord)

now, we want to create a type of substitutions from Ids - Terms

 data Term = ...
 newtype Subst = Subst (IM.IntMap Term)

ideally, we'd like an MapLike instance, but we'd have to tediously write
it ourselves. if we allow the supergeneralized newtype deriving, we can do:

 deriving(MapLike Id Term Subst)

and be done with it.

this would be worlds of useful.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Signals + minimal proposal (was Re: asynchronous exceptions)

2006-04-07 Thread John Meacham
On Fri, Apr 07, 2006 at 02:58:01PM +0100, Simon Marlow wrote:
 Of course you could implement some global flag to say that an exit is in
 progress, but that implies explicit checking of the flag all over the
 place, which is what asynchronous exceptions are designed to avoid.
 
 When *do* we exit, in fact?  When all the exit handlers have finished?

I think we might be thinking of different things. here is a complete
implementation of exit.

exitMVar :: MVar () -- starts full
exitMVar = ..

handlerMVar :: MVar [IO ()]  -- starts with []
handlerMVar = ...

onExit :: IO () - IO ()
onExit action = modifyMVar handlerMVar (action:)

exitWith status = do
takeMVar exitMVar -- winner takes all
let handleLoop = do
hs - swapMVar handlerMVar []
sequence_ hs
if null hs then return () else handleLoop
handleLoop
exitWith_ status

exitWith_ calls the underlying 'exit' routine of the operating system
immediatly. no waiting.

I'll get to why you can't have handlers building up indefinitly below.

  I think you have that backwards, releasing resources is the right
  thing 
  to do when you get an exception, but there are lots of other reasons
  you 
  want to release resources that have nothing to do with exceptions. you
  don't use 'throwTo' to close all your files :)
 
 No, but you do use an exception handler, or something built using
 exception handlers like 'finally'.  I don't want to have to use *both*
 exception handlers and exit handlers.

they serve different purposes. You might use both at different places in
the same program, but never for the same resource. 

 The situation is the same as in your proposal - the foreign call
 continues running.  However, as soon as it returns, the Haskell thread
 will receive an exception.
 
 I propose this:
 
   When System.Exit.exitWith is called, all currently running
   threads are sent an exit exception as soon as possible.
   Exit handlers registered with onExit are started immediately.
   The system exits when (a) the main thread has stopped, and (b)
   all exit handlers have completed.  Subsequent calls to exitWith
   simply throw an exit exception in the current thread.

this seems the wrong way round. exitWith is something you call in
_response_ to an exception, telling the program you want to exit. not
something that generates an exception. In particular, you often won't
know what 'status' to exit with until you have had everything clean up
properly (or fail to clean up properly). We have 'throwTo' to throw
exceptions around.

what I would expect from dealing with other languages is:

exitWith does as it does above in my example, nothing more, nothing
less. in particular it is not special in any way when it comes to
exceptions or concurrency other than using standard MVars.


falling off the end of the main thread is equivalent to calling
exitWith Success, an exception falling off the end is equivalent to
exitWith Failure.

the main thread is not special in any way other than being wrappen in
the equivalent of.

-- user written main function
main = do ...

-- what the implementation uses as its main thread
realMain = catch (\_ - exitFailure) main  exitSuccess


if you want to die and clean up via exceptions, use 'throwTo' to throw a
'PleaseExit' exception to whatever threads you like.

if you are writing a library that uses threads internally, where you
have a particular thread you want to clean up via exceptions, do an

myThreadId = onExit . throwTo PleaseExit

now you will get an exception on exit. if you need the exit to wait
until you complete something, you can have your handler wait on an MVar.

advantages of this set up.

1. base case requires no concurrency or exceptions
2. abstract threads possible, if you don't let your ThreadId escape,
there is no way to get an exception you don't bring upon yourself.
3. simple rules. expressable in pure haskell.
4. can quit immediatly on a SIGINT since the exitWith routine runs on
whatever thread called exit, rather than throwing responsibility back to
the other threads which might be stuck in a foreign call. (unless you
explicitly ask it to)
5. you don't have to worry about 'PleaseExit' if you don't want to.
6. modularity modularity. now that concurrency is part of the standard,
we will likely see a lot of libraries using concurrency internally for
little things that it wants to keep abstract, or concurrent programs
composed with each other. having a global 'throw something to all
threads on the system' doesn't feel right.
7. subsumes the exitWith throws exceptions everywhere policy.

John







-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Signals + minimal proposal (was Re: asynchronous exceptions)

2006-04-06 Thread John Meacham
withExitHandler :: IO () - IO a - IO a
withExitHandler = 

-- | register a handler to be run on exiting the program
onExit :: IO () - IO ()
onExit = 

-- | block exiting during this call for critical sections.
blockExit :: IO a - IO a
blockExit = ...

although thees are less powerful than exceptions in that you can only
catch a single event, exit they are more powerful in the sense that
the exception handlers are global, so when you register an exit handler
it happens no matter what thread is in scope.
 

in addition, an exit_ routine should be added that bypasses the exit
handlers, quiting the program immediatly.


John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-05 Thread John Meacham
On Wed, Apr 05, 2006 at 10:34:09AM -0500, Spencer Janssen wrote:
 How about an implementation that sets the deepSeq'd bit *after* each
 field has been successfully deepSeq'd?  deepSeq'ing a cyclic structure
 would behave just like an infinite structure.

what would be the point of having a bit then?

in any case, we should talk about the meaning of deepseqing something,
not its implementation.

depth limited recursive seq seems like the best route to me.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Concurrency

2006-04-04 Thread John Meacham
On Tue, Apr 04, 2006 at 02:25:11PM +0100, Simon Marlow wrote:
 On 31 March 2006 22:15, John Meacham wrote:
 
  On Fri, Mar 31, 2006 at 04:21:26PM +0100, Simon Marlow wrote:
  Great.  Apart from my misgivings about allowing cooperative
  scheduling at all, here's a few comments on the proposal:
  
  much much preferable to a standard that not everyone can implement. :)
  
- I wouldn't include threadWaitRead, threadWaitWrite,
  or threadDelay at all.  These can all be implemented using
  FFI, so don't belong in the concurrency library.  Their
  presence is largely historical.
  
  They all have special implementations on a 'epoll' based system.
  threadDelay turns into the timeout parameter to select, waitread/write
  turn into the basic building blocks of your epoll wait-list. We
  definitly want these in the interface as primitves.
 
 Still not convinced.  Most applications can use the standard IO library
 in a multithreaded program to get I/O multiplexing.  The library might
 be implemented by using a clever epoll/kqueue/whatever interface
 underneath, but I don't see a reason to expose that as a standard
 library.  And it's perfectly reasonable to implement concurrent IO
 without doing any clever epoll stuff: GHC on Windows does just that.
 
 IMHO, concurrency gives you a way to *avoid* needing an event interface
 in your language.

Oh, it was always my plan to expose the epoll/Event library, it is
something lacking in haskell currently which is a pain. Often, an EDSM
loop is the best way to express an algorithm. Concurrency is great, but
it is far from a panacea.

 
  In particular, foregin concurrent calls will most likely be
  implemented in _terms_ of threadWaitRead on cooperative systems.
 
 By all means, but that still doesn't mean that threadWaitRead needs to
 be in the standard.

Here are a couple of uses. We need waiting routines for every
interesting event, they are darn useful, and they admit a very optimized
implementation.

A C library which reads a file descriptor, calling threadWaitRead
beforehand and then the call is much more efficient than calling the
library directly.

A consumer-producer set up, you don't want to read into core memory the
producers data until you are sure you have somewhere to write it to, so
you have a 'threadWaitWrite-read-write' loop.


UI design, a common issue is displaying continuously updating
information on the screen. You communicate with the X11 server via a
pipe, so it is possible to just completely fill the X11 buffer with
drawing requests and get a backlog killing your apps responsibility.
also, by the time these backloged events actually get to the screeen
they may be out of date and your app quickly crashes and burns if your
incoming data rate exceeds the speed at which you can draw to the
screen.

Concurrency admits a nice solution, you have your thread that generates
the interesting info, (say, reading data from a DSP), continually
updating a shared location. your drawing routine is in a
'threadWaitWrite-readlocation-drawit' loop. notice that threadWaitWrite
is needed because otherwise you would be forced to send outdated data to
the screen if you couldn't separate what you write from when you write
it.


A C call that uses a file, but expects some precondition to be set
before it can be run. One that I ran into is a curses library that
waited for user input, but wanted the screen to be cleared before it
could be run. clearing the screen right away would have left the user
sitting staring at a blank screen with no instructions until they
pressed a key, the right thing to do was to do a threadWaitRead, clear
the screen, then call the routine.

Efficient scheduling is another use. you might want to wait for
several clients to become ready before deciding which one to actually
service.


Basically, they are needed any time the data you are processing is
time-dependent. any time you need to decide what to read or write on the
current conditions rather than what they were when you started the read
or write.


John


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: 'deriving Tree (Eq,Ord)'

2006-04-04 Thread John Meacham
On Tue, Apr 04, 2006 at 01:13:32PM -0400, Robert Dockins wrote:
 The obvious solution is to allow out-of-defining-module deriving only  
 for data types where all constructors are exported.  Presumably, if  
 someone explicitly hid (at least some of) the constructors of a data  
 type, they did it for a reason and we can hope that they carefully  
 considered the external interface of that type (including instances).

indeed, that is actually a requirement of the original proposal.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-04 Thread John Meacham
On Tue, Apr 04, 2006 at 11:52:55AM -0700, Andy Adams-Moran wrote:
 I'm not convinced Simon's argument holds, as I don't think you can use
 deepSeq to write a Haskell function that will distinguish cyclic
 structures from infinite ones. If we can't do that, then we haven't
 really added any new semantic observational capability to the theory, so
 I think the morally correct reasoning argument holds.

compiler optimizations don't necessarily preserve cyclic structures. in
practice they probably do, but there is no guarentee and we wouldn't
want to start making one.

another option would be for the DeepSeq class (or whatver) have a depth
limited version,

deepSeqSome :: DeepSeq a = Int - a - a

which would only traverse a limited depth into a structure.


Another issue is that being able to detect cyclic structures would make
it impossible to express deepSeq as a Haskell - Haskell translation.
which is no good.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: deeqSeq proposal

2006-04-04 Thread John Meacham
On Tue, Apr 04, 2006 at 02:53:36PM -0700, Andy Gill wrote:
 Another issue is that being able to detect cyclic structures would  
 make
 it impossible to express deepSeq as a Haskell - Haskell translation.
 which is no good.
 
 I am trying to understand this requirement. For the sake of what must
 all primitives be expressible as a Haskell - Haskell translation?

Mainly it is an excellent proof that no undue burden is being placed on
any implementation, current or future. It also gives a way to reason
about its behavior and is a way to ensure you don't accidentally miss
defining any behavior or break referential transparency or any of the
other properties haskell programmers expect.

not that it has to be implemented via the translation of course. things
like DeepSeq and Typeable will most likely have optimized versions on
various compilers which is why I'd like to see the restriction that the
only way to create instances for these two classes is via the deriving
mechanism of the compiler. for the record, jhc can do a super optimized
Typeable, but not a DeepSeq, so will likely have to use the standard
class definition of DeepSeq (which it can already derive, under a
different name).

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


state threads

2006-04-03 Thread John Meacham
In case anyone was wondering what this state-threads thing I keep
talking about is, here is a sample implementation (in C) as well as a
lot of documentation and FAQs that apply to haskell as well.

http://state-threads.sourceforge.net/

it should be noted that the chief disadvantage of state threads in C is
not an issue for haskell (requiring an alternate IO library)


A form of state threads can be implemented in pure haskell using the Poor Man's
Concurrency monad described here:
http://citeseer.ist.psu.edu/claessen99functional.html
assuming you have the ability to use an 'epoll' or 'select' mechanism.
However, this is probably not a suitable implementation method for high
performance haskell implementations and does not address foreign
concurrent calls.

John
-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: FFI, safe vs unsafe

2006-04-03 Thread John Meacham
On Sat, Apr 01, 2006 at 02:30:30PM +0400, Bulat Ziganshin wrote:
 new stacks can be allocated by alloca() calls. all these
 alloca-allocated stack segments can be used as pool of stacks assigned
 to the forked threads. although i don't tried this, my own library
 also used processor-specific method.

so you alloca new big areas and then use 'longjmp' to jump back and
forth within the same stack simulating many stacks?

that is a neat trick. will confuse the hell out of the bohem garbage
collector but I don't want to rely on that much longer anyway :)

however, it would be a good thing to fall back to if no processor
specific stack creation routine is available.

this minimal threads library 
http://www.cs.uiowa.edu/%7Ejones/opsys/threads/
uses an interesting trick where it probes the setjmp structure to find
the SP reasonably portably on any stack-based architecture. pretty
clever.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Concurrency

2006-04-03 Thread John Meacham
On Mon, Apr 03, 2006 at 11:38:08AM +0100, Ross Paterson wrote:
 On Fri, Mar 31, 2006 at 01:15:03PM -0800, John Meacham wrote:
  On Fri, Mar 31, 2006 at 04:21:26PM +0100, Simon Marlow wrote:
   Great.  Apart from my misgivings about allowing cooperative scheduling
   at all, here's a few comments on the proposal:
  
  much much preferable to a standard that not everyone can implement. :)
 
 Are there potential users for the compromise interface?  I had the
 impressions that those wanting concurrency needed the fairness
 guarantees.

quite the opposite IMHO. I think for most uses cooperative
implementations will be not just just fine, but preferable.

We really shouldn't call it a compromise interface, cooperative
threading is often considered superior to pthreads/pre-emptive threading
for a wide variety of tasks. After a lot of experience writing pthreads
code from both the OS and application side, I find I agree. cooperative
state-threads should always be the way to go by default when writing new
code unless you absolutely need one of the features of pre-emptive
threading.

the tasks for which state-threads work well for are IO bound
multiplexing tasks, pthreads are better for CPU-bound tasks. 

However, most uses of concurrency are for programs that interact with
the user or the external world, as in they wait for an event from a
variety of sources and respond to it quickly. The limiting factor isn't
processing power, but how fast the events come, how fast you can redraw
the screen, your network speed, etc.  exactly what state-threading is
best at. Most CPU bound tasks tend to be batch processing type things
like compilers, which don't need concurrency to begin with.

some info on the advantages and tradeoffs
http://state-threads.sourceforge.net/docs/st.html

although written from the point of view of network servers, a lot is
relevant to other fields. 

Ideally, I'd like to provide both in jhc. But cooperative is a whole lot
of bang for the buck.

John



-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: MVar semantics: proposal

2006-03-31 Thread John Meacham
Of course, let me know if I am just being overly paranoid about crazy
future NUMA machines. We can just say full read-write memory barrier on
every putMVar, takeMVar and leave it at that. :)

John


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: MVar semantics: proposal

2006-03-31 Thread John Meacham
On Fri, Mar 31, 2006 at 01:43:15PM +0100, Simon Marlow wrote:
  We should drop atomicModifyIORef since we have MVars, for
  architectures 
  with only a test and set instruction and no atomic exchange,
  supporting atomicModifyIORef would entail the same overhead as MVars.
 
 Slightly less overhead than an MVar, because you only need one
 lock/release to implement atomicModifyIORef, but two lock/release
 combinations are involved in an update of an MVar.

hmm.. is atomicModifyIORef meant to be atomic with respect to all other
IORef calls or _just_ other atomicModifyIORef calls? because if the
second then that is a whole lot easier to implement and I could be on
board with that. :)

 
  atomicModifyIORef also cannot (easily) be implemented on
  implementations 
  that use update-in-place rather than indirections for thunk updates.
 
 I don't follow you - how would that make it harder?

for instance in a TIM implementation (do any exist?) you have both a
code pointer and a frame address to represent a value, most arches don't
have an atomic way to set two memory locations at once. However, these
implementations perhaps could use a single indirection just for
implementing IORefs... jhc would be in this boat as it modifies values
by rewriting nodes, not by swizzling pointers, but I can make IORefs go
through an indirection if needed.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Concurrency

2006-03-31 Thread John Meacham
On Fri, Mar 31, 2006 at 04:21:26PM +0100, Simon Marlow wrote:
 Great.  Apart from my misgivings about allowing cooperative scheduling
 at all, here's a few comments on the proposal:

much much preferable to a standard that not everyone can implement. :)

   - I wouldn't include threadWaitRead, threadWaitWrite,
 or threadDelay at all.  These can all be implemented using
 FFI, so don't belong in the concurrency library.  Their
 presence is largely historical.

They all have special implementations on a 'epoll' based system.
threadDelay turns into the timeout parameter to select, waitread/write
turn into the basic building blocks of your epoll wait-list. We
definitly want these in the interface as primitves.

In particular, foregin concurrent calls will most likely be implemented
in _terms_ of threadWaitRead on cooperative systems.


   - yield bothers me a little.  If it weren't for cooperative
 systems, yield would be semantically a no-op, because the
 no-starvation guarantee means you never need it for
 correctness.  I think it's ok, just a bit unsettling.

even pthreads provides it.

noise
I think you place a lot of faith in pre-emption. :)
In my experience, it doesn't actually buy you a whole lot over
state-threading in the non SMP case.

everything would be different if we were thinking of different
processes on the same computer, where you wouldn't want one buggy one
interfering with others, but in general you consider a single program
buggy or bug-free as a unit.
/noise

In any case, IO multiplexing is 90% of the uses of threading anyway,
(ginsu,yi,gui apps that don't do background processing, etc...) which
cooperative threading is ideal for.

not that there arn't itches that only preemptive threads can scratch
too.

   - In the optional OS threads section it says allows multiple
 haskell threads to run at once - actually you can provide
 all that without allowing multiple haskell threads to run
 at once, eg. ghc-6.4.1 with -threaded.  I'll modify it.

okay. yeah, I just sort of outlined the options figuring we would fill
in the details later.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: FFI, safe vs unsafe

2006-03-31 Thread John Meacham
On Fri, Mar 31, 2006 at 03:16:50PM -0500, Wolfgang Thaller wrote:
 Before adding non-concurrent, reentrant calls to the language  
 standard, please take some time to think about what that means. If  
 you have forkIO'ed multiple threads, things start to interact in  
 strange ways. I think this is a can of worms we don't want to open.  
 (Or open again. It's still open in GHC's non-threaded RTS, and the  
 worms are crawling all over  the place there).

I am still digesting your message, but a quick note is that when you
specify non-concurrent, you arn't saying it can't be concurrent but
rather I don't absolutely need it to be

so GHC would still treat all reentrant calls as concurrent and that is
a-okay by the spec.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Concurrency

2006-03-31 Thread John Meacham

I just realized that my mailer futzed this one and its headers don't
match where it was actually sent. so if you are responding to it, the
mail most likely is not going out to the list.

make sure it is to haskell-prime and not hasuell-prime. 

John


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: FFI, safe vs unsafe

2006-03-31 Thread John Meacham
On Fri, Mar 31, 2006 at 03:16:50PM -0500, Wolfgang Thaller wrote:
 So I'm going to ask a few questions about the semantics of non- 
 concurrent reentrant calls, and if people can provide answers that  
 don't scare me, I'll concede that they have a place in the language  
 standard.

first of all, a quick note, for GHC, the answers will be the same thing
it does now with -threaded. but I will try to answer with what a simple
cooperative system would do.

 1.) Assume thread A and B are running. Thread A makes a non- 
 concurrent, reentrant call to Foreign Lands. The foreign function  
 calls a foreign-exported Haskell function 'foo'.
 While 'foo' is executing, does thread B resume running?

if 'foo' blocks on a mvar,read,write,etc... then yes.

 2.) Assume the same situation as in 1, and assume that the answer to  
 1 is yes. While 'foo' is running, (Haskell) thread B makes a non- 
 concurrent, reentrant foreign call. The foreign function calls back  
 to the foreign-exported Haskell function 'bar'. Because the answer to  
 1 was yes, 'foo' will resume executing concurrently with 'bar'.
 If 'foo' finishes executing before 'bar' does, what will happen?

I am confused, why would anything in particular need to happen at all?

the threads are completly independent.  The non-concurrent calls could
just be haskell code that happens to not contain any pre-emption points
for all it cares. in particular, in jhc, non-concurrent foreign imports
and exports are just C function calls. no boilerplate at all in either
direction.  calling an imported foreign function is no different than
calling one written in haskell so the fact that threads A and B are
calling foregin functions doesn't really change anything.

 3.) Same situation as in 1. When 'foo' is called, it forks (using  
 forkIO) a Haskell thread C. How many threads are running now?

3 potentially runable.

 4.) Should there be any guarantee about (Haskell) threads not making  
 any progress while another (Haskell) thread is executing a non- 
 concurrent call?

I don't understand why we would need that at all.

 Two more questions, not related to semantics:
 
 5.) Assume that Haskell Programmer A writes a Haskell library that  
 uses some foreign code with callbacks, like for example, the GLU  
 Tesselator (comes with OpenGL), or, as a toy example, the C Standard  
 Library's qsort function. Should Programmer A specify concurrent  
 reentrant on his foreign import?
 Programmer B will say please don't, as he wants to use a Haskell  
 implementation which doesn't support concurrent reentrant.  
 Programmer C will say please do, as he wants his application's GUI  
 to stay responsive while the library code is executing. So what  
 should the poor library programmer A do?

He should say just 'reentrant' since concurrent isn't needed for
correctness because the tessalation routines are basic calculations and
will return.

However, on a system like GHC that actually can run code concurrently
and actually would have issues enforcing a 'non-concurrent' guarentee it
would run concurrently anyway. It would be hard not to on an
implementation that supported true OS threads actually.

everyone wins. in the absolute worst case there are always #ifdefs but I
doubt they will be needed.

 6.) Why do people consider it too hard to do interthread messaging  
 for handling a foreign export from arbitrary OS threads, when they  
 already agree to spend the same effort on interthread messaging for  
 handling a foreign import concurrent? Are there any problems that I  
 am not aware of?

it is not that it is hard (well it is sort of), it is just absurdly
inefficient and you would have no choice but to pay that price for
_every_ foregin export. even when not needed which it mostly won't be.
the cost of a foreign export should be a simple 'call' instruction
(potentially) when an implementation supports that.  

the cost of a foreign import concurrent nonreentrant is only paid when
actually using such a function, and quite cheap. on linux at least, a
single futex, a cached pthread and it gets rolled into the main event
loop. so a couple system calls max overhead.


John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Concurrency

2006-03-31 Thread John Meacham
On Fri, Mar 31, 2006 at 04:29:59PM -0600, Taral wrote:
 On 3/31/06, John Meacham [EMAIL PROTECTED] wrote:
 - I wouldn't include threadWaitRead, threadWaitWrite,
   or threadDelay at all.  These can all be implemented using
   FFI, so don't belong in the concurrency library.  Their
   presence is largely historical.
 
  They all have special implementations on a 'epoll' based system.
  threadDelay turns into the timeout parameter to select, waitread/write
  turn into the basic building blocks of your epoll wait-list. We
  definitly want these in the interface as primitves.
 
 And they're all a pain because they don't take sets of files, only
 single ones. Can we please have something like:
 
 threadWait :: Timeout - [Handle] - IO ?

Oh, that is definitly planned as part of an 'epoll' interface I have
been calling Event.

depending on the compiler, Concurrent might be implemented on top of
Event or Event might be implemented on top of Concurrent :)

In any case, I left it out of the proposal here because it is relatively
orthogonal (from a design, not an implemenatition point of view) but I
definitly think it should exist.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: FFI, safe vs unsafe

2006-03-30 Thread John Meacham
On Thu, Mar 30, 2006 at 10:44:36AM +0100, Simon Marlow wrote:
 You're optimising for the single-threaded case, and that's fine.  In
 GHC, a call-in is similar to what I outlined above except that we can
 optimise away the RPC and perform the call directly in the OS thread
 that requested it, due to the way bound threads are implemented.  Doing
 that requires that a lot more of the runtime needs to be thread-safe,
 though. 


yeah, if you actually have a OS threaded RTS, then everything is a whole
different ball of wax. But there is a lot to be said for a
state-threaded version like hugs. Even in C-land many people choose
state-threads over posix threads or vice versa depending on many
criteria and we shouldn't assume that one is necessarily superior.
state-threads arn't second class, just a different way to go.

Although I was skeptical at the beginning that we could come up with a
standard based on forkIO that could encompass both models without
compromising performance or implementation flexability, I now think that
we can! and that is good, because it means we won't need to make
concurrency an addendum or just accept the fact that many haskell-prime
implementations will be incomplete!


mainly, I think we need to keep a couple goals in mind, which are sometimes
in opposition, but not really so much:

 * not require anything that will rule out or arbitrarily reduce the
  efficiency of a absolutely-zero-overhead in the non-concurrent case
  implementation of straightforward state-threads.

 * not require anything that will inhibit the SMP scalability or
   scheduling freedom of OS threaded implementations. 

I think if we stick to these 'caps' at both ends then all the
intermediate implementations we have talked about will be accomodated
and since state-threads can _almost_ be implemented in pure haskell, we
can be pretty sure we arn't constraining future as yet to be thought of
implementation models too much.

A sticky point might be whether we say anything about duplicated work,
however, the haskell report never really says anything about guarenteed
sharing anyway so we can probably be silent on the matter.

we certainly shouldn't treat state-threads as second class or a lesser
implementation of the standard though! they can often be faster than OS
threads but with their own set of tradeoffs.

glossary:

OS threaded - ghc -threaded, context switching at arbitrary points, not
necessarily under the control of the haskell runtime.

state-threading - hugs,jhc context switching at block-points chosen by the
implementation and user via yield.

yhc is somewhere in between. basically state-threading, but with more
context switching under the control of the yhc run-time.

 It's true that this is a fairly large overhead to impose on all Haskell
 implementations.  I'm coming around to the idea that requiring this is
 too much, and perhaps multi-threaded call-ins should be an optional
 extra (including concurrent/reentrant foreign calls).

yeah, a much touted feature of haskell concurrency is that it is _fast_
_fast_, we shouldn't compromise that or its potential without very good
reason.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Pre-emptive or co-operative concurrency (was: Concurrency)

2006-03-30 Thread John Meacham
On Thu, Mar 30, 2006 at 10:54:01AM +0100, Simon Marlow wrote:
 Not true - in GHC with SMP a thread doing no allocation can be running
 concurrently with any number of other threads.  It's only the
 single-threaded implementation that has this bug where a thread that
 doesn't allocate can starve the other threads.  In fact, even on a
 uniprocessor, you can use GHC's SMP mode to work around the bug by
 pretending you have 2 CPUs.

it should be noted that I don't consider this a bug, but a design
choice. of course, since you made the choice differently then for GHC it
is a bug :)


 GHC's SMP mode is truly preemptive, operations from multiple threads can
 be arbitrarily interleaved.  So let's stop saying that all known
 implementations are non-preemptive, please ;-)

well, as preemptive as the pthreads implementation at least. which is
usually very, but not so with some userspace implementations of
pthreads.

Both are allowed by the standard so counting on preemption is a bad
idea in general, even with ghc. (though, perhaps this isn't true, ghc
has its own mini-threads underneath OS threads in -threaded mode if I
understand it properly and that makes things less simplistic.)

however, this is all just reiteration of the never count on the
scheduler rule when writing threaded apps when you didn't write the
operating system :) (hard real-time bug-free systems exempt)

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


  1   2   >