[Haskell-cafe] Parsec question

2004-11-19 Thread John Goerzen
Hi,

I'm porting a parser over from an OCamllex/Ocamlyacc version and I'm
using Parsec for both the tokenizer and the resulting token stream parser.

I have both of them working fine, but now my question is: how do I
combine them?  I can't quite figure out how to say "take the output from
this GenParser Char () Tok and use it as the input for this
GenParser Tok () ParserOutput".

Well, I have figured out an ugly way involving manually starting up both
parsers, but it makes position calculations very complex.  I suspect I'm
missing something.

Ideas?



___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Parsec question

2004-11-19 Thread Tomasz Zielonka
On Fri, 19 Nov 2004 14:28:07 + (UTC), John Goerzen
<[EMAIL PROTECTED]> wrote:
> Hi,
>
> I'm porting a parser over from an OCamllex/Ocamlyacc version and I'm
> using Parsec for both the tokenizer and the resulting token stream parser.
>
> I have both of them working fine, but now my question is: how do I
> combine them?  I can't quite figure out how to say "take the output from
> this GenParser Char () Tok and use it as the input for this
> GenParser Tok () ParserOutput".
>
> Well, I have figured out an ugly way involving manually starting up both
> parsers, but it makes position calculations very complex.

Did you try to pair tokens with their SourcePos'es?

What I did in my program was this:

tokenize :: CharParser st tok -> CharParser st [(SourcePos, tok)]
tokenize tp = do
l <- many t
eof
return l
  where
t = do
pos <- getPosition
tok <- tp
return (pos, tok)

token :: (Show tok) => (tok -> Maybe a) -> GenParser (SourcePos, tok) st a
token f = Parsec.token (show . snd) fst (f . snd)

This has a space leak, but I didn't care, because my inputs are at
most 10kb long.
You can do a lazy version with getInput.

BTW, it would be useful if Parsec allowed to throw a ParseError from one type
of parser in another parser. It would help me in a situation, where I parse the
whole file with one parser, but I retokenize some parts of it and parse them
with another parser type. Right now I am using this workaround, but it doesn't
work well:

cs <- chars
pos <- getPosition
x <- case p pos cs of
Left err -> do
setPosition (errorPos err)
fail (messageString (head (errorMessages err)))
Right x -> return x

How about making an instance for

  instance Control.Monad.Error.MonadError ParseError (GenParser tok st)

PS. I guess I could do this myself.

Best regards,
Tomasz
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Parsec question

2004-11-19 Thread Bayley, Alistair
I've also used Parsec for separated lexer + parser and currently have
something like this to invoke them:

testParse inputString = do
  case (parse myLexer "" inputString) of
Left err -> fail ("lexical error: " ++ err)
Right tokens ->
  case (parse myParser "" tokens) of
Left err -> fail ("parse error: " ++ err)
Right result -> return result

... or was this the "manual startup" that you were referring to? The above
seems clunky to me, so I'd also welcome suggestions for piping the lexer
output into the parser.

What do you mean by "makes position calculations very complex"? Are you
talking about reporting the position of lexical or parse errors? (If so,
Parsec supports this quite well.)

Alistair.

> -Original Message-
> From: John Goerzen [mailto:[EMAIL PROTECTED] 
> Sent: 19 November 2004 14:28
> To: [EMAIL PROTECTED]
> Subject: [Haskell-cafe] Parsec question
> 
> Hi,
> 
> I'm porting a parser over from an OCamllex/Ocamlyacc version and I'm
> using Parsec for both the tokenizer and the resulting token 
> stream parser.
> 
> I have both of them working fine, but now my question is: how do I
> combine them?  I can't quite figure out how to say "take the 
> output from
> this GenParser Char () Tok and use it as the input for this
> GenParser Tok () ParserOutput".
> 
> Well, I have figured out an ugly way involving manually 
> starting up both
> parsers, but it makes position calculations very complex.  I 
> suspect I'm
> missing something.
> 
> Ideas?

-
*
Confidentiality Note: The information contained in this 
message, and any attachments, may contain confidential 
and/or privileged material. It is intended solely for the 
person(s) or entity to which it is addressed. Any review, 
retransmission, dissemination, or taking of any action in 
reliance upon this information by persons or entities other 
than the intended recipient(s) is prohibited. If you received
this in error, please contact the sender and delete the 
material from any computer.
*

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec question

2004-11-19 Thread John Goerzen
On Fri, Nov 19, 2004 at 02:56:38PM -, Bayley, Alistair wrote:
> I've also used Parsec for separated lexer + parser and currently have
> something like this to invoke them:
> 
> testParse inputString = do
>   case (parse myLexer "" inputString) of
> Left err -> fail ("lexical error: " ++ err)
> Right tokens ->
>   case (parse myParser "" tokens) of
> Left err -> fail ("parse error: " ++ err)
> Right result -> return result
> 
> ... or was this the "manual startup" that you were referring to? The above
> seems clunky to me, so I'd also welcome suggestions for piping the lexer
> output into the parser.

Yep, that is exactly the idea I took.  Works, but just doesn't seem
right.

> What do you mean by "makes position calculations very complex"? Are you
> talking about reporting the position of lexical or parse errors? (If so,
> Parsec supports this quite well.)

The parse errors.  I did take to passing around pairs of SourcePos, Tok
around.  It works, but I had to then write custom token functions to
handle them.  I'd rather be able to just access the other parser like
normal (refer to it in a do block or whatever), so I don't have to
manually handle it.  I suppose "very complex" was an exaggeration,
looking back.

-- John
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Arrows for Sample rate inference

2004-11-19 Thread Henning Thielemann

On Fri, 12 Nov 2004, Koji Nakahara wrote:

> > On Thu, 11 Nov 2004 10:49:13 +0100 (MEZ)
> > Henning Thielemann <[EMAIL PROTECTED]> wrote:
> > 
> > >  The computation sample rate should be propagated through the network as
> > > follows:
> > >   If in a component of equal sample rate some processors have the same
> > > fixed sample rate, all uncertain processors must adapt that. 
> > >   If some processors have different fixed sample rates this is an error. 
> > >   If no processor has a fixed sample rate, the user must provide one
> > > manually.
> > >  To me this looks very similar to type inference. Is there some mechanism
> > > in Haskell which supports this programming structure? 
> 
> I fall on Arrows and come up with the following.
> I'm not sure this is a proper usage of Arrows, though.

I needed some time to think this over, I'm still not finished. I had no
experiences with Arrows so far, but I read that Arrows are good for
describing networks of processors. Is it possible to model each directed
graph using Arrows? Including all kinds of loops (ArrowLoop?)? 

Your code looks very promising. I tried to simplify it a bit:

module SampleRateInferenceArrow where

import Control.Arrow
import Data.List (intersect)
data Rates = Rates [Int] | Any deriving Show
data Processor b c = P Rates (Rates -> b -> c)

-- test Stream
type Stream = String

intersectRates Any y = y
intersectRates x Any = x
intersectRates (Rates xs) (Rates ys) = Rates $ intersect xs ys

instance Arrow Processor where
  arr f = P Any (const f)
  (P r0 f0) >>> (P r1 f1) =
 P (intersectRates r0 r1) (\r -> f1 r . f0 r)
  first (P r f) = P r (\r (x, s) -> (f r x, s))

runProcessor (P r f) s = f r s

-- test processors
processor1 = P (Rates [44100, 48000]) (\r -> ( ++ show r))
processor2 = P Any(\r -> ( ++ show r))
processor3 = P (Rates [48000])(\r -> ( ++ show r))

process = processor1 >>> processor2 >>> processor3

test = runProcessor process "bla"


 Now, since you gave me an answer to my question I become aware, that my
question was wrong. :-) One must model the signal processor networks more
detailed. We need wires (the sample streams), sockets and processors. Each
processor has a number of input and output sockets. The number of sockets
may not be fixed at compile time, say for example a list of input stream
is allowed. A wire connects an output with an input socket. A processor
may work with different sampling rates (e.g. a resampling process), but a
wire has always one sample rate. This is the point where I see the
similarity to type inference. Imagine that a processor is a function and
the sample rates are types, then for example a processor of type (a,b,b) 
-> (c,b) takes three inputs, two of them having the same sample rate, and
two outputs, where one output shares the sample rate of the second and the
third input stream.
 I wonder if I can re-use the Processor data above as Socket data. But
since I can connect only two sockets, I wouldn't need Arrow notation. But
if I want to connect processors with (>>>) I don't know how to address
certain sockets.
 Without Arrows I would try to label processors and wires and solve the
problem by a search for connectivity components using Data.Graph. But I
don't want to have the burden of creating and preserving uniqueness of
labels. 

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] No need for integer literals

2004-11-19 Thread Henning Thielemann

In addition to Paul Hudak's "The Haskell School of Expression", Appendix A
"Built-in types are not special" I want to note that there is also hardly
a need for integer literals. :-]


module Digits where

infixl 9 #

(#) :: a -> (a -> b) -> b
x # f = f x

int :: Num a => a
int = 0

d0, d1, d2, d3, d4, d5, d6, d7, d8, d9 :: (Enum a, Num a) => a -> a

d0 n = n+n+n+n+n+n+n+n+n+n
d1 = succ . d0
d2 = succ . d1
d3 = succ . d2
d4 = succ . d3
d5 = succ . d4
d6 = succ . d5
d7 = succ . d6
d8 = succ . d7
d9 = succ . d8

test :: (Enum a, Num a) => a
test = int#d1#d4#d2#d8#d5#d7 * int#d2#d1

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe