I stood up and suggested rebindable record syntax at Anglohaskell
earlier this year, but never got round to posting a proposal. Given the
TDNR discussion, it seems timely to link everyone to what I'd got round
to writing:
http://flippac.org/RebindableRecordSyntax.html
Apologies for the lack o
On 03/07/2010 21:11, Stephen Tetley wrote:
For an applicative parser - many is the same combinator as Parsec's
many and some is many1.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Exce
On 14/06/2010 23:17, Ivan Lazar Miljenovic wrote:
Emmanuel Castro writes:
In practice, g is an optimised version of f when working on large
amount of elements.
It's a list, and map is lazy; not too sure you can get anything more
optimised than that for long lists.
It may be po
Hi everyone. It's just over three months until the traditional time for
Anglohaskell, so I wanted to ask: is anyone willing to step up and run
it this year? We had a volunteer at last year's event, but I've
forgotten who. It was also suggested that emails about the organisation
and planning of
On 10/04/2010 13:57, Yves Parès wrote:
I answered my own question by reading this monad-prompt example:
http://paste.lisp.org/display/53766
But one issue remains: those examples show how to make play EITHER a human
or an AI. I don't see how to make a human player and an AI play SEQUENTIALLY
(to
On 28/03/2010 22:07, Günther Schmidt wrote:
Hi Fraser, hi all,
one thing I did notice is the total absence of a sense of humor on
this list. The only funny thing that on this list was "Don't play with
your monads ..."
Yes, us humourless feminists have clearly poisoned the list as a whole.
On 28/03/2010 21:38, Günther Schmidt wrote:
Hi guys,
judging by the responses so far it seems that the gay haskellers have
more balls than the female haskellers to come out of the closet.
Uhm.
So we can expect childish comments for not displaying ourselves on
demand now? Good to know.
-
On 27/03/2010 21:27, Günther Schmidt wrote:
Hi guys (and I mean it),
so, in short, no female haskellers ...
Bare one which sent me an email directly, but it looks like she's not
ready to come out of the closet yet.
And those of us already named for you. And there're a few others around
-
Luke Palmer wrote:
It's very hard to tell what is going on without more details. If you
*at least* give the ghci session, and possibly the whole code (while
it might be too much to read, it is not to much to load and try
ourselves).
This looks like a monomorphism restriction, which shouldn't ha
I have some mildly complicated parsing code, that uses parsec to return
a computation (in a state monad) that handles operator precedence - so I
can handle scoped precedence/fixities, much like in Haskell. I just
spent a while bolting on some new features. More time than I'd like, I'd
left it a
Nicolas Pouillard wrote:
Excerpts from Edward Kmett's message of Fri Oct 09 20:04:08 +0200 2009:
I have idiom brackets in that toy library already, but the ado syntax is
fairly useful if you want to refer to several intermediate results by name.
To work with idiom brackets you need to manuall
Robert Atkey wrote:
On Fri, 2009-10-09 at 18:06 +0100, Philippa Cowderoy wrote:
This leads us to the bikeshed topic: what's the concrete syntax?
I implemented a simple Camlp4 syntax extension for Ocaml to do this. I
chose the syntax:
applicatively
let x = foo
let y
I do a lot of work with parsers, and want to do more using Applicatives.
That said, I'm finding it a little tedious being forced to use pointless
style for a task that's well-suited to having a few names around. The
idea of an applicative do notation's been kicked around on #haskell a
few times
Wifi signups are Anglohaskell are now on the wiki - please add your
details by the 31st of July if you want a wifi account at MS Research
for the Friday. Alternatively, reply to this email with your full name,
institution, country of residence and email address.
The Anglohaskell wiki page can
ing list - I really think that is too
> heavy-weight. We want people to create a login (for the ML) and go
> through the ML, just to get wiki access?
>
Who said anything about creating mailing list logins? Probably the
easiest-for-user thing us a form that sends th
eJournal has a problem with spambots gaining free
accounts, and it provides OpenID. They may not be exploited for the
OpenID account yet, but I imagine they will be sooner rather than later
- OpenID is more useful to tie in people's existing identities.
--
Philippa Cowderoy
___
t?
> >
>
> Why not just list everyone's email and let the requester pick who to
> send the request to?
>
A mailing list, possibly attached to a ticketing/queue system, seems a
good idea? If it's just a list, admins should ack when they've added
s
and who already has an account) have to make
edits on others' behalf, which is a serious inconvenience for both
myself and attendees, as well as something of a barrier to entry.
What's going on, and how can we speed things up?
--
Philippa Cowderoy
___
t and yields
input. If you're not doing disk I/O, pretty much the entire program's
plain functional stuff.
--
Philippa Cowderoy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
x27;s free!
If anyone wants to offer a talk, help with running the event,
accomodation for haskellers from out of town or some ideas, please feel
free to edit the wiki page appropriately and/or give us a yell in
#anglohaskell.
--
Philippa Cowderoy
_
those who're new or don't remember,
http://www.haskell.org/haskellwiki/AngloHaskell contains links to info
from previous years - the idea's a get-together with lots of talks from
hobbyist to academic, and plenty of chat.
--
Philippa Cowderoy
GHC manual if you
haven't already?), but IIRC they're part of how GHC handles boxing.
--
Philippa Cowderoy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On Thu, 2009-03-12 at 14:56 -0700, Bryan O'Sullivan wrote:
> However, it's also arguably the case that you shouldn't care about port
> number ordering. That smells dodgy to me.
>
Port ranges aren't that uncommon.
--
Philippa Cowderoy
__
7;re not after a theory channel though - architectural discussion,
compiler implementation, possible type system extensions, library
design, all are good subjects.
Anyway, I shouldn't ramble on for too long here - #haskell-in-depth is
open for business and we look forward to seeing you there!
--
On Fri, 16 Jan 2009, Duncan Coutts wrote:
> If you or anyone else has further concrete suggestions / improvements
> then post them here now! :-)
>
Spell out what associativity means and what it means for that operation to
have an identity. List a few examples (stating that they're not all
inst
On Thu, 15 Jan 2009, John Goerzen wrote:
> Several people have suggested this, and I think it would go a long way
> towards solving the problem. The problem is: this documentation can
> really only be written by those that understand the concepts,
> understand how they are used practically, and h
On Thu, 15 Jan 2009, Andrew Coppin wrote:
> I was especially amused by the assertion that "existential quantification" is
> a more precise term than "type variable hiding". (The former doesn't even tell
> you that the feature in question is related to the type system! Even the few
> people in my p
On Thu, 15 Jan 2009, Andrew Coppin wrote:
> I don't know about you, but rather than knowing that joinFoo is associative,
> I'd be *far* more interested in finding out what it actually _does_.
A good many descriptions won't tell you whether it's associative though,
and sometimes you need to know
On Thu, 15 Jan 2009, Lennart Augustsson wrote:
> If I see Monoid I know what it is, if I didn't know I could just look
> on Wikipedia.
And if you're a typical programmer who is now learning Haskell, this will
likely make you want to run screaming and definitely be hard to
understand. We at leas
onically enough, plenty of combinator libraries for such tasks form
monads themselves. Finding the right domain for DSL programs is also
important, but this is not necessarily as neatly functional. If you
start with a deep embedding rather than a shallow one then this isn't
much of
On Wed, 12 Nov 2008, Andrew Coppin wrote:
> I have a small question...
>
> Given that interactivity is Really Hard to do in Haskell, and that mutable
> state is to be strongly avoided, how come Frag exists? (I.e., how did they
> successfully solve these problems?)
>
Because the givens are bull
On Wed, 22 Oct 2008, Ariel J. Birnbaum wrote:
> This is the part when the Lisp hackers in the audience chuckle, as one of
> them
> raises a hand and asks "What happens when you grow tired of writing TH
> boilerplate? Wait for another extension? And what after that?".
>
To be fair, the TH boil
On Tue, 21 Oct 2008, Andrew Coppin wrote:
> If I'm understanding this correctly, Template Haskell is a way to
> auto-generate repetative Haskell source code.
>
Amongst other things, yes. It's also a way to perform repetitive
transformations on code, for example.
> The thing that worries me is.
On Sun, 19 Oct 2008, Bulat Ziganshin wrote:
> Hello Philippa,
>
> Sunday, October 19, 2008, 3:25:26 PM, you wrote:
>
> >> ... that, like everything else, should be multiplied by 2-3 to
> >> account GC effect
>
> > Unless I'm much mistaken, that isn't the case when you're looking at the
> > mini
On Sun, 19 Oct 2008, Bulat Ziganshin wrote:
> Hello Bertram,
>
> Sunday, October 19, 2008, 6:19:31 AM, you wrote:
>
> > That's 5 words per elements
>
> ... that, like everything else, should be multiplied by 2-3 to
> account GC effect
>
Unless I'm much mistaken, that isn't the case when you'r
On Thu, 16 Oct 2008, Andrew Coppin wrote:
> Actually, I added this to my real parser, and it actually seems to do exactly
> what I want. Give it an invalid expression and it immediately pinpoints
> exactly where the problem is, why it's a problem, and what you should be doing
> instead. Neat!
>
On Wed, 15 Oct 2008, Andrew Coppin wrote:
> Philippa Cowderoy wrote:
> > expressions = do es <- many1 expression
> > eof
> > return es
> >
>
> Ah - so "eof" fails if it isn't the end of the input?
>
On Wed, 15 Oct 2008, Andrew Coppin wrote:
> Suppose this is the top-level parser for my language. Now suppose the user
> supplies an expression with a syntax error half way through it. What I *want*
> to happen is for an error to be raised. What *actually* happens is that Parsec
> just ignores all
On Wed, 15 Oct 2008, Andrew Coppin wrote:
> Suppose this is the top-level parser for my language.
> Does anybody know how to fix this irratiting quirk? I can see why it happens,
> but not how to fix it.
>
One of:
expressions = many1 (try expression <|> myFail)
where myFail = {- eat your wa
On Wed, 1 Oct 2008, Don Stewart wrote:
> malcolm.wallace:
> > Just a small nuance to what Don wrote:
> > > so opinion seems to be that LGPL licensed *Haskell
> > > libaries* are unsuitable for any projects you want to ship
> > > commercially, without source code.
> >
> > Unles
On Sun, 21 Sep 2008, Andrew Coppin wrote:
> Actually, none of these things were mentioned. The things people have
> *actually* complained to me about are:
> - Haskell expressions are difficult to parse.
This is partly an "it's not braces, semicolons and function(application)"
complaint, though n
On Thu, 2008-09-04 at 20:38 +, Duncan Coutts wrote:
> On Thu, 2008-09-04 at 19:41 +0100, Philippa Cowderoy wrote:
> > On Thu, 4 Sep 2008, John Van Enk wrote:
> >
> > > I'm looking for a document describing the differences between Parsec 3 and
> > > Parse
On Thu, 4 Sep 2008, John Van Enk wrote:
> I'm looking for a document describing the differences between Parsec 3 and
> Parsec 2. My google-foo must be off because I can't seem to find one. Does
> any one know where to find that information?
>
Unfortunately there isn't currently a good one - in f
Oops, forgot to send to list.
On Mon, 2008-09-01 at 01:27 +0100, Philippa Cowderoy wrote:
> On Mon, 2008-09-01 at 01:11 +0100, David House wrote:
> > 2008/8/31 Ryan Ingram <[EMAIL PROTECTED]>:
> > > My proposal is to allow "ad-hoc" overloading of names; if a
7;. You're not the only one to want it, and if it's not fixed this
time it may never get fixed.
--
Philippa Cowderoy <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On Wed, 20 Aug 2008, Johannes Waldmann wrote:
> On parsers: yes, LL/LR theory and table-based parsers have been
> developed for a reason and it's no easy decision to throw them out.
> Still, even Parsec kind of computes the FIRST sets?
>
No, it doesn't. That's not actually possible for monadic p
Warning for Andrew: this post explains a new-to-you typed lambda calculus
and a significant part of the innards of Hindley-Milner typing in order to
answer your questions. Expect to bang your head a little!
On Tue, 27 May 2008, Andrew Coppin wrote:
> - A function starts out with a polymorphic t
On Sat, 17 May 2008, Achim Schneider wrote:
> There's at least one token before any recursion, so I guess not. After
> all, it terminates. It's my state that does not succeed in directing
> the parser not to mess up, so I'm reimplementing the thing as a
> two-pass but stateless parser now.
In mos
On Fri, 16 May 2008, Andrew Coppin wrote:
> Obviously most people would prefer to write declarative code and feel secure
> that the compiler is going to produce something efficient.
>
Ultimately the only way to do this is to stick to Einstein's advice - make
things as simple as possible but no
On Fri, 16 May 2008, Achim Schneider wrote:
> My problem is that realTopLevel = expr, and that I get into an infinite
> recursion, never "closing" enough parens, never hitting eof.
Have you run into the left-recursion trap, by any chance?
This doesn't work:
expr = do expr; ...
You can cover co
On Fri, 16 May 2008, Don Stewart wrote:
> I don't understand what's ugly about:
>
> go s l x | x > m = s / fromIntegral l
> | otherwise = go (s+x) (l+1) (x+1)
>
I suspect you've been looking at low-level code too long. How about the
total lack of domain concepts?
On Fri, 16 May 2008, Achim Schneider wrote:
> Philippa Cowderoy <[EMAIL PROTECTED]> wrote:
>
> > On Fri, 16 May 2008, Achim Schneider wrote:
> >
> > Guess who ran into that with a separate token for
> > layout-inserted braces?
> >
> It can't be
On Fri, 16 May 2008, Philippa Cowderoy wrote:
> Confusing, isn't it? It's almost the right message, too. I'm pretty sure
> the misbehaviour's because eof doesn't consume - see what happens if you
> put an error message on all of whiteSpace?
>
It is indee
On Fri, 16 May 2008, Achim Schneider wrote:
> Andrew Coppin <[EMAIL PROTECTED]> wrote:
>
> > Wait... "unexpected end of input; expecting [...] end of input [...]"
> >
> > That's just *wrong*...! ;-)
> >
> > But don't despaire - show us your parser and what it's supposed to
> > parse, and I'm s
On Fri, 16 May 2008, Achim Schneider wrote:
> "test.l" (line 7, column 1):
> unexpected end of input
> expecting "(", Lambda abstraction, Let binding, Atom, end of input or
> Function application
>
> I obviously don't know anything about Parsec's inner workings. I'm
> going to investigate as soon
On Tue, May 13, 2008 5:53 am, Neal Alexander wrote:
> I can post the full profiling info if anyone really cares.
>
Any info is helpful. It's taking a while to get round to things, but the
more relevant info we have to hand when we do the easier it is to improve
things and the less begging for data
On Mon, 25 Feb 2008, Ben wrote:
> :1:8:
>Ambiguous type variable `t' in the constraints:
> `Fractional t' arising from a use of `/' at :1:8-10
> `Integral t' arising from a use of `^' at :1:7-15
>Probable fix: add a type signature that fixes these type variable(s)
>
/ doesn't d
On Sun, 24 Feb 2008, Daniel Fischer wrote:
> Hi all,
> I try not to be too rude, although I'm rather disgusted.
> I know there are several sites out on the web where solutions to PE problems
> are given. That is of course absolutely against the sporting spirit of
> Project Euler, but hey, not al
On Sun, 24 Feb 2008, Daniel Fischer wrote:
> b) posting C/C++ code there indicates that the reason for that is to be a
> spoil-sport, not to further learning/thinking Haskell.
>
No, it doesn't. It provides code that people can port - an obvious step in
building a more complete wiki page.
--
On Sun, 24 Feb 2008, Daniel Fischer wrote:
> Agreed, and the page with the code may indeed be considered a valid
> contribution. However, it certainly would be more valuable if it wasn't bare
> code, but also included explanations of the mathematical or programmatical
> ideas behind it.
>
> Th
For a while I've been meaning to propose something along the lines of
this class:
class (MonadError m e, MonadError m' e') =>
MonadErrorRelated m e m' e' | m -> e, m' -> e', m e' -> m' where
catch' :: m a -> (e -> m' a) -> m' a
rethrow :: m a -> (e -> e') -> m' a
with an example insta
On Sun, 17 Feb 2008, Anton van Straaten wrote:
> Is there a benefit to reusing a generic Either type for this sort of thing?
> For code comprehensibility, wouldn't it be better to use more specific
> names? If I want car and cdr, I know where to find it.
>
It's Haskell's standard sum type, with
On Sat, 16 Feb 2008, Alan Carter wrote:
> I'm a Haskell newbie, and this post began as a scream for help.
Extremely understandable - to be blunt, I don't really feel that Haskell
is ready as a general-purpose production environment unless users are
willing to invest considerably more than usual
On Thu, 7 Feb 2008, Albert Y. C. Lai wrote:
> Is it good or bad to add:
>
> instance (MonadIO m) => MonadIO (ParsecT s u m)
>
I don't see any reason not to add it - it's not as if we can prevent
people lifting to IO! Good catch.
--
[EMAIL PROTECTED]
A problem that's all in your head is stil
I'm having a little difficulty finding full properties for Parsec3's
Stream class, largely because I don't want to overspecify it with regard
to side-effects. Here's the class:
> class Stream s m t | s -> t where
>uncons :: s -> m (Maybe (t,s))
The idea is that:
* unfoldM uncons gives th
On Sun, 3 Feb 2008, Antoine Latter wrote:
> Another picky nit:
>
> The monad transformer type is defined as such:
>
> > data ParsecT s u m a
> > = ParsecT { runParsecT :: State s u -> m (Consumed (m (Reply s u
a))) }
>
> with the Consumed and reply types as:
>
> > data Consumed a = Consumed a
On Sat, 2 Feb 2008, Antoine Latter wrote:
> To expand on this point, side-effect instances of Stream don't play
> nice with the backtracking in Text.Parsec.Prim.try:
>
> > import Text.Parsec
> > import Text.Parsec.Prim
> > import System.IO
> > import Control.Monad
>
> > type Parser a = (Stream s
On Sat, 2 Feb 2008, Antoine Latter wrote:
> I'm not a fan of parameterizing the "Stream" class over the monad
> parameter `m':
> I looked through the sources and I didn't see anywhere where this
> parameterization gained anything. As a proof of this I did a
> mechanical re-write removing the cl
On Sat, 22 Dec 2007, Cristian Baboi wrote:
> On Sat, 22 Dec 2007 17:13:55 +0200, Philippa Cowderoy <[EMAIL PROTECTED]>
> wrote:
>
> > Here's a trivial example that does so:
> >
> > (\x -> x) (\x -> x)
> >
> > A lambda calculus classic tha
On Sat, 22 Dec 2007, Cristian Baboi wrote:
> The thing is I think that for a language to have "first-class" functions,
> it must be "homoiconic" if I understand the terms correctly.
>
You're confusing functions with the terms that are used to define them.
The terms aren't first-class, the funct
On Sat, 22 Dec 2007, Cristian Baboi wrote:
> On Sat, 22 Dec 2007 16:55:08 +0200, Miguel Mitrofanov
> <[EMAIL PROTECTED]> wrote:
>
> > > > > In Haskell I cannot pass a function to a function, only its
> > > > > expansion.
> > >
> > > > What do you mean by "expansion"? Can you clarify this?
> > >
On Thu, 18 Oct 2007, [EMAIL PROTECTED] wrote:
> Felipe Lessa writes:
> > On 10/17/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:
> > > ... And it frustrates the hell out of me that 100% of the human
> > > population consider Haskell to be an irrelevant joke language. ...
>
> > I feel this way as w
On Thu, 18 Oct 2007, PR Stanley wrote:
> Hi
> Do you trust mathematical materials on Wikipedia?
> Paul
>
To a first approximation - trust but verify.
--
[EMAIL PROTECTED]
"I think you mean Philippa. I believe Phillipa is the one from an
alternate universe, who has a beard and programs in BASI
On Sun, 14 Oct 2007, David Stigant wrote:
> However, most widely-used programs (ex: web browsers, word processors,
> email programs, data bases, IDEs) tend to be 90% IO and 10% (or less)
> computation.
No, they don't. They look it, but there's always a fair amount of
computation going on to de
On Fri, 12 Oct 2007, Steve Schafer wrote:
> On Fri, 12 Oct 2007 21:51:46 +0100 (GMT Daylight Time), you wrote:
>
> >Which is nevertheless the kind of power you need in order to also be able
> >to prove precise properties.
>
> We're not talking about POWER, we're talking about SYNTAX.
Which has
On Fri, 12 Oct 2007, Steve Schafer wrote:
> On Fri, 12 Oct 2007 13:25:28 -0700, you wrote:
>
> >I'm not sure what sanity has to do with it. Presumably we all agree
> >that it's a good idea for the compiler to know, at compile-time, that
> >head is only applied to lists. Why not also have the comp
On Wed, 10 Oct 2007, Andrew Coppin wrote:
> (I'm less sold on whether you really need to learn a particular dialect
> well enough to *program* in it...)
>
If you don't then you won't be able to see how complicated things actually
get done. It's also an important exercise in abstracting things
On Wed, 10 Oct 2007, Yitzchak Gale wrote:
> I wrote:
> >>> Perhaps Data.HashTable is what you are looking
> >>> for then?
>
> Jerzy Karczmarczuk wrote:
> > extract from Data.Hash what you need...
> > why not try tries?
>
> apfelmus wrote:
> > There's always Data.Map
>
> Those are log n. I would
On Tue, 25 Sep 2007, Seth Gordon wrote:
> Are Benjamin C. Pierce's _Types and Programming Languages_ and/or _Basic
> Category Theory for Computer Scientists_ suitable for self-study?
>
Basic Category Theory depends on your mindset somewhat. TaPL is great
though, and frequently recommended. The
On Tue, 25 Sep 2007, Lennart Augustsson wrote:
> It's reasonably easy to read.
> But you could make it more readable. Type signatures, naming the first
> lambda...
>
It might be reasonable to define something like mapMatrix that happens to
be map . map, too. Along with at least a type synonym
On Mon, 24 Sep 2007, Vimal wrote:
> Wow, half an hour, about 7 replies :) I dont know which one to quote!
>
> Okay. So, why is GHC finding it difficult to conclude that
> length is always > 0? Suppose I define length like:
>
> length [] = 0
> length (x:xs) = 1 + length xs
>
> Hmm, well, I think
On Mon, 24 Sep 2007, Vimal wrote:
> Hi all,
>
> I was surprised to find out that the following piece of code:
>
> > length [1..] > 10
>
> isnt lazily evaluated! I wouldnt expect this to be a bug, but
> in this case, shouldnt the computation end when the length function
> evaluation goes somethi
On Mon, 17 Sep 2007, Adrian Hey wrote:
> Ideally the way to deal with this is via standardised interfaces (using
> type classes with Haskell), not standardised implementations. Even this
> level of standardisation is not a trivial clear cut design exercise.
> e.g we currently have at least two com
On Sun, 26 Aug 2007, Ulrich Vollert wrote:
> I compiled Hugs for my Sharp Zaurus SL-C3200 (http://www.trisoft.de)
> which is a PDA with an ARM processor.
>
Any chance of a package or a HOWTO?
> So, it is possible to use graphics on the Zaurus, too. I didnt dare to
> port ghc or Yhc - which woul
On Sat, 25 Aug 2007, Andrew Coppin wrote:
> Would be nice if I could build something in Haskell that overcomes these.
> OTOH, does Haskell have any way to talk to the audio hardware?
>
It would definitely be nice if someone wrote a binding to the VST SDK or a
wrapper for it. Unfortunately I sus
On Sat, 25 Aug 2007, Neil Mitchell wrote:
> Hi
>
> > > Flippi (google: Haskell Flippi)
> >
> > ...and yet haskell.org uses WikiMedia? (Which is written in something
> > bizzare like Perl...)
>
> Yes, but WikiMedia is a result of years of work, Flippi is a lot less.
The original version was the
On Sat, 25 Aug 2007, Andrew Coppin wrote:
> Neil Mitchell wrote:
> >
> > > - A wiki program. (Ditto.)
> > >
> >
> > Flippi (google: Haskell Flippi)
> >
>
> ...and yet haskell.org uses WikiMedia? (Which is written in something
> bizzare like Perl...)
>
Flippi is... rather minimalistic
On Wed, 8 Aug 2007, peterv wrote:
> PS: It would be very nice for beginners to have a special tool / text editor
> that allows you see the desugared form of monads and other constructs.
>
An editor that can be configured to display various inferred details,
annotations and desugarings in the mi
Two pieces of news regarding AngloHaskell:
1) We've been offered WiFi access at Microsoft Research for any attendees
who want it. We'll need a name, email address and company/institution
affiliation where appropriate - see wiki for details.
2) We're being given lunch on Friday!
Finally, a requ
On Sun, 15 Jul 2007, Andrew Coppin wrote:
> [EMAIL PROTECTED] wrote:
> > G'day all.
> >
> > Quoting Andrew Coppin <[EMAIL PROTECTED]>:
> >
> >
> > > The "Haskell ray tracer" seems to be a pretty standard and widely-used
> > > example program. But has anybody ever seriously tried to make a
> >
On Sat, 14 Jul 2007, Bulat Ziganshin wrote:
> Hello Andrew,
>
> Saturday, July 14, 2007, 10:09:03 PM, you wrote:
>
> > Ooo... that's not far from here...
>
> > Does this mean if I turn up, I can meet random Haskellers?
>
> no, you will meet undefined Haskeller because randomness is impure
> co
On Fri, 13 Jul 2007, Neil Mitchell wrote:
> Hi,
>
> We are pleased to announce AngloHaskell 2007
>
> http://www.haskell.org/haskellwiki/AngloHaskell
>
> Dates: 10th-11th of August (Friday-Saturday)
> Location: Cambridge, with talks at Microsoft Research on Friday
>
Just to add, because I've j
On Fri, 13 Jul 2007, brad clawsie wrote:
> to improve the list, might i suggest
>
> - push chatter to IRC
>
This is problematic for some kinds of techie chatter, where email makes it
easier to get all the maths down.
> - take this service off of email entirely. try a web forum system (you
>
On Fri, 13 Jul 2007, Donald Bruce Stewart wrote:
> How do people feel about allowing posts in -cafe to be placed on the
> wiki, without extensive prior negotiation? What copyright do -cafe@
> posts have?
>
Currently, snagging the whole post for non-archive purposes isn't
necessarily legit.
> I
On Fri, 13 Jul 2007, Dave Bayer wrote:
> As a newcomer I was stunned that this otherwise very sophisticated
> community was using an email list rather than a bulletin board. The
> shear torrent of email was impacting my mail program performance.
>
This is a cultural thing, and assuming that it
On Fri, 13 Jul 2007, Simon Peyton-Jones wrote:
> We need at least one forum in which it's acceptable to ask anything, no
> matter how naive, and get polite replies. (RTFM isn't polite; but "The
> answer is supposed to be documented here (\url); let us know if that
> doesn't answer your qn" is
On Tue, 10 Jul 2007, Aaron Denney wrote:
> On 2007-07-10, Dan Piponi <[EMAIL PROTECTED]> wrote:
> > On 7/10/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:
> >> But what does, say, "Maybe x -> x" say?
> >
> > Maybe X is the same as "True or X", where True is the statement that
> > is always true. Rem
On Sat, 30 Jun 2007, Claus Reinke wrote:
> for all that i like monadic programming in general, i often feel
> that it is biased towards handling only the success path well,
> by offering built-in support for a single continuation only.
Certainly one path gets privileged over the others, I don't k
On Fri, 29 Jun 2007, Dave Bayer wrote:
> One is immediately led back to the same idea as Haskell do expressions:
> Two pieces of program, juxtaposed next to each other, silently
> "multiply" to combine into a larger program, with type rules guiding the
> multiplication process.
>
They don't,
On Fri, 22 Jun 2007, Andrew Coppin wrote:
> Woah... What the hell? I just switched to Data.ByteString.Lazy and WHAM! Vast
> speed increases... Jeepers, I can transform 52 KB so fast I can't even get to
> Task Manager fast enough to *check* the RAM usage! Blimey...
>
> OK, just tried the 145 KB te
1 - 100 of 159 matches
Mail list logo