Jonathan Cast wrote:
On Sunday 08 July 2007, Andrew Coppin wrote:
Jonathan Cast wrote:
I think surely you're using existential data types rather than rank-2
types.
You expect *me* to know?
Surely not :) That's why I tried briefly explaining the ideas again.
LOL! Tha
On Sunday 08 July 2007, Andrew Coppin wrote:
> Jonathan Cast wrote:
> > I think surely you're using existential data types rather than rank-2
> > types.
>
> You expect *me* to know?
Surely not :) That's why I tried briefly explaining the ideas again.
> > Existential types: each application of En
Jonathan Cast wrote:
I think surely you're using existential data types rather than rank-2 types.
You expect *me* to know?
Existential types: each application of Encoder2 is to arguments which require
a specific value of x.
Rank-2 types (polymorphic fields, actually): each application of
On Sunday 08 July 2007, Andrew Coppin wrote:
> Jonathan Cast wrote:
> > I wouldn't call rank-2 types extremely rare . . .
>
> Well now, my parser is annoyingly clunky to use, but it *works*.
> However, I just found something where it seems to be *impossible* to
> write the necessary code without ra
Hello Andrew,
Sunday, July 8, 2007, 4:31:32 PM, you wrote:
> Oh, I don't mind not knowing how rank-2 types are *implemented*. ;-) But
> it would be nice to know what they *are*... :-S
concrete types are rank-0:
sin :: Double->Double
polymorphic types are rank-1:
length :: forall a . [a] -> Int
Andrew Coppin wrote:
Oh, I don't mind not knowing how rank-2 types are *implemented*. ;-) But
it would be nice to know what they *are*... :-S
(Thus far, they just seem to be some incomprehensible syntax that makes
the compiler stop complaining. In particular, I have no idea what the
differenc
Brandon S. Allbery KF8NH wrote:
On Jul 8, 2007, at 8:12 , Andrew Coppin wrote:
Aye, you drive a car without knowing how it works - but it was put
together by some people who *do* know these things. Would you drive a
car you built yourself? ;-)
No :) --- but depending on what you're doing, y
On Jul 8, 2007, at 8:12 , Andrew Coppin wrote:
Brandon S. Allbery KF8NH wrote:
On Jul 8, 2007, at 3:21 , Andrew Coppin wrote:
this.) So as of now, my code uses rank-2 types - despite the fact
that I don't actually know what a rank-2 type *is* yet! o_O This
is rather troubling...
Bah --
Brandon S. Allbery KF8NH wrote:
On Jul 8, 2007, at 3:21 , Andrew Coppin wrote:
this.) So as of now, my code uses rank-2 types - despite the fact
that I don't actually know what a rank-2 type *is* yet! o_O This is
rather troubling...
Bah --- I use monads all the time and still don't have muc
On Jul 8, 2007, at 3:21 , Andrew Coppin wrote:
this.) So as of now, my code uses rank-2 types - despite the fact
that I don't actually know what a rank-2 type *is* yet! o_O This is
rather troubling...
Bah --- I use monads all the time and still don't have much of a clue
about category th
Jonathan Cast wrote:
I wouldn't call rank-2 types extremely rare . . .
Well now, my parser is annoyingly clunky to use, but it *works*.
However, I just found something where it seems to be *impossible* to
write the necessary code without rank-2 types...
I tried to write this type:
dat
Claus Reinke wrote:
ah, that suggests yet another specification, a variation of the second
version above, where the parser in control is not p1 itself, but p2,
with p1 acting as an input transformation for p2, and p3 resuming
where p1 left off. the difference being that p2's demand is supposed
Now take decodeRLEb and feed it's output to some nontrivial parser, and
then feed the remainder of the input, unmodified, into another parser:
so the code as posted didn't exhibit a full use case. that specification is
still a bit vague. assuming that p1: decodeRLE, p2: nontrivial parser, and
Stefan O'Rear wrote:
How about . in module names?
Now I'm almost *certain* that's now officially "in" the language... ;-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On Friday 06 July 2007, Andrew Coppin wrote:
> Donald Bruce Stewart wrote:
> > andrewcoppin:
> >> Personally, I just try to avoid *all* language extensions - mainly
> >> because most of them are utterly incomprehensible. (But then, perhaps
> >> that's just because they all cover extremely rare edge
On Friday 06 July 2007, Andrew Coppin wrote:
> Stefan O'Rear wrote:
> > How about . in module names?
>
> Now I'm almost *certain* that's now officially "in" the language... ;-)
Nope. Never made it past candidate status (or version 0.0, for that matter).
http://www.haskell.org/hierarchical-module
Claus Reinke wrote:
source code is always useful, as it is concrete. but some comments about
purpose and important aspects would help, too, lest we optimise away the
parts you're most interested in. as it stands, i must assume that
'decodeRLEb' is the purpose of the exercise, and it isn't clear
Donald Bruce Stewart wrote:
andrewcoppin:
Personally, I just try to avoid *all* language extensions - mainly
because most of them are utterly incomprehensible. (But then, perhaps
that's just because they all cover extremely rare edge cases?)
Some cover edge cases, some are just useful
source code is always useful, as it is concrete. but some comments about
purpose and important aspects would help, too, lest we optimise away the
parts you're most interested in. as it stands, i must assume that 'decodeRLEb'
is the purpose of the exercise, and it isn't clear to me why that requir
Hello Andrew,
Thursday, July 5, 2007, 11:45:14 PM, you wrote:
> Personally, I just try to avoid *all* language extensions - mainly
> because most of them are utterly incomprehensible. (But then, perhaps
> that's just because they all cover extremely rare edge cases?)
> MPTCs and ATs look useful
On Fri, Jul 06, 2007 at 10:56:43AM +1000, Donald Bruce Stewart wrote:
> andrewcoppin:
> > Jonathan Cast wrote:
> > >On Thursday 05 July 2007, Andrew Coppin wrote:
> > >
> > >>...OK, anybody have a solution that works in Haskell 98?
> > >>
> > >
> > >Rank-2 types are perhaps /the/ most common,
andrewcoppin:
> Jonathan Cast wrote:
> >On Thursday 05 July 2007, Andrew Coppin wrote:
> >
> >>...OK, anybody have a solution that works in Haskell 98?
> >>
> >
> >Rank-2 types are perhaps /the/ most common, widely accepted extension to
> >Haskell 98, after the approved addendum for FFI and
On Thursday 05 July 2007, Andrew Coppin wrote:
This version works (I think). Also, using this syntax may make the
distinction between existential constructors and rank-2 constructors a little
clearer.
*AlgoRLE> run decodeRLEb1 $ start () $ encodeRLEb [1, 2, 3]
([1],PState {state = (), source
On Thursday 05 July 2007, Andrew Coppin wrote:
> Jonathan Cast wrote:
> > On Thursday 05 July 2007, Andrew Coppin wrote:
> >> ...OK, anybody have a solution that works in Haskell 98?
> >
> > Rank-2 types are perhaps /the/ most common, widely accepted extension to
> > Haskell 98, after the approved
-- This is probably line-wrapped horribly...
module Process
(
Source (..),
PState (), start,
Process (run),
get_state, set_state, alt_state,
get, eof,
pure, count, many,
stack
)
where
class Source src where
empty :: src x -> Bool
fetch :: src x ->
AC> For the Nth time... The amount of data processed by parser1 needs
AC> to depend on the amount of data processed by parser2. (The amount
AC> of data output by each parser is very nontrivially related to the
AC> amount of data consumed.)
What about lazyness? Let parser1 process ALL the data and
Jonathan Cast wrote:
Andrew:
By the way, could you share your definition of Stack with us? It isn't at all
clear to me how stacked actually decides to terminate the underlying parser.
Yeah, I'll post the complete source here in a little while. I think
that's probably the only way anybody
Jonathan Cast wrote:
On Thursday 05 July 2007, Andrew Coppin wrote:
...OK, anybody have a solution that works in Haskell 98?
Rank-2 types are perhaps /the/ most common, widely accepted extension to
Haskell 98, after the approved addendum for FFI and the draft addendum for
hierarchica
Andrew:
By the way, could you share your definition of Stack with us? It isn't at all
clear to me how stacked actually decides to terminate the underlying parser.
Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
On Thursday 05 July 2007, Andrew Coppin wrote:
> Jonathan Cast wrote:
> > On Wednesday 04 July 2007, Andrew Coppin wrote:
> >> Anybody have a solution to this?
> >
> > newtype Parser state x y
> > = Parser (forall src. Source src => (state, src x) -> (state, src x,
> > y))
>
> ...OK, anybody have
Malcolm Wallace wrote:
I can't help thinking that all you really want to do is parse the same
data twice, through an intermediate representation. That only requires
you to feed the result of one parse into a top-level call to a different
parser. For instance:
this = do
tmp <- parser1
Jonathan Cast wrote:
On Wednesday 04 July 2007, Andrew Coppin wrote:
Anybody have a solution to this?
newtype Parser state x y
= Parser (forall src. Source src => (state, src x) -> (state, src x, y))
...OK, anybody have a solution that works in Haskell 98?
Definition of monad
Andrew Coppin <[EMAIL PROTECTED]> wrote:
> My goal is to be able to stack multiple parsers one on top of the
> other - but be able to *change* the stack half way through parsing if
> needed.
>
> Essentially, I have the "stacked" function, where if I do
>
> x <- stacked foo parser1 bar parser2
On Wednesday 04 July 2007, Andrew Coppin wrote:
> Well, I eventually got it to work correctly... (!)
>
> My goal is to be able to stack multiple parsers one on top of the other
> - but be able to *change* the stack half way through parsing if needed.
> This I eventually succeeded in doing. The exte
Well, I eventually got it to work correctly... (!)
My goal is to be able to stack multiple parsers one on top of the other
- but be able to *change* the stack half way through parsing if needed.
This I eventually succeeded in doing. The external interface is fairly
simple, but the type signatu
35 matches
Mail list logo