Re: replacing guile with haskell?

2003-10-23 Thread Graham Klyne
At 01:14 22/10/03 +0200, Peter Simons wrote:
Graham Klyne writes:

  I'm thinking in particular that a function that turned a regular
  expression into a Parsec parser function could be useful, as in:
  regexp.compile :: String - GenParser Char st [String]

Just curious: Why would you want something like that? I thought that
the good thing(tm) about regular expressions is that they can be
parsed by a finite state machine rather than a recursive descent
parser, so for all I know, the C regular expression library that comes
with your system is most likely much faster than any Parsec code would
every be.
The comment was motivated by my finding that Parsec to be very useful for 
handling higher-level syntactic constructs, but dealing with lexical 
constructs can be more complex.  It had occurred to me that a 
regexp-matching component could provide a useful ad-hoc lexer for parsec.

Another reason that occurred to me was that one can start out with a regexp 
being a quick (and-maybe-dirty) way to get a textual value parsed.  Then 
increasing requirements, feature creep, etc., mean that the regexp ends up 
getting embodied in ad-hoc code to deal with non-finite aspects of an 
evolving syntax.  If the regexp processing were already handled within the 
Parsec framework, it seems to me a natural evolutionary path to use it with 
other Parsec combinators.

These may not be good reasons, just the ones that happened to be in my head 
when I made that comment.

I also noted ajb's comments about overloading of terminology here ... and 
agree, I was using the term rather loosely ... in this case I was thinking 
of the kind of regular expression that can be handled with a finite 
automaton -- I've never mastered all the full complexities of 
Perl-compatible regexes and the like.  The extension of regexes beyond this 
form is IMO symptomatic of the second of my points above.

#g


Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: replacing guile with haskell?

2003-10-23 Thread Graham Klyne
At 20:40 21/10/03 -0400, [EMAIL PROTECTED] wrote:
I've done it for regular expressions (e.g. lex, alex etc), but not for
regexps (e.g. Text.Regex).  This particular terminology overload annoys
me no end, by the way.
I checked the code into haskell-libs.  It hasn't propagated through to
the web view of the repository yet, but you should eventually be able
to find it here:
http://cvs.sourceforge.net/viewcvs.py/haskell-libs/libs/text/

Look for Dfa.lhs.
Thanks for this... it turns out I have an immediate use for it.  I've 
downloaded it but I'm having a little trouble figuring out how to drive 
it.  Is there any description anywhere?

Absent that, this is what I am figuring (am I getting this right?):

+ The supplied regex is a value of type Re t, which describes an expression 
to match a sequence of tokens of type t.  In common use, t might be Char.

+ The constructors for Re are:
ReOr [Re t]-- matches any one of the Re's in the list
  | ReCat [Re t]   -- matches a sequence of the RE's in the list
  | ReStar (Re t)  -- matches zero or more of the given Re
  | RePlus (Re t)  -- matches one or more of the given Re
  | ReOpt (Re t)   -- matches zero or one of the given Re
  | ReTerm [t] -- matches a sequence of tokens exactly matching
  the given list.
That last is very much guesswork:  is it true that
ReTerm ts = ReCat $ map (\t ReTerm [t]) ts
?
A function to construct an (Re Char) from a simple textual representation 
would be handy.  Maybe I'll tackle that.

...

Having got an Re value, matchRe is a function that applies it (after 
compilation) to a sequence of 't', returning True if the expression is 
matched, otherwise False.

Is this about right?

There's another function matchRe2, which seems to do something recursive 
with the regular expression but I can't figure out what.  Is it just a 
different implementation strategy?  It does seem to give the same answers.

...

I also noticed this comment in the code:
[[
Utility typeclasses for enforcing all the constraints we need
on our monad's free type variables.  Note that this requires both
-fglasgow-exts and -fallow-undecidable-instances in GHC to work
properly.
]]
I was wondering if the use of -fallow-undecidable-instances might cause 
problems with Hugs, though it does seem to work.

I'm also wondering if there's a way to use this to match a leading 
subsequence (rather than the entire sequence of tokens supplied), and to 
discover which parts of the regexp have been matched.

...

[later]

I've also looked at the Haskell Dynamic Lexer Engine
(http://www.nondot.org/sabre/Projects/HaskellLexer/) that Derek pointed out 
... it looks a closer fit to my current goals, though I do like the 
purity of your approach (i.e. its focus on the core engine).

#g


Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: replacing guile with haskell?

2003-10-22 Thread Peter Simons
Graham Klyne writes:

  I'm thinking in particular that a function that turned a regular
  expression into a Parsec parser function could be useful, as in:

  regexp.compile :: String - GenParser Char st [String]

Just curious: Why would you want something like that? I thought that
the good thing(tm) about regular expressions is that they can be
parsed by a finite state machine rather than a recursive descent
parser, so for all I know, the C regular expression library that comes
with your system is most likely much faster than any Parsec code would
every be.

Not that I have tried it, though ...

Peter

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


Re: replacing guile with haskell?

2003-10-22 Thread Derek Elkins
On Tue, 21 Oct 2003 13:47:51 +0100
Graham Klyne [EMAIL PROTECTED] wrote:

 At 04:17 21/10/03 -0400, [EMAIL PROTECTED] wrote:
 I think I might have mentioned this previously, but here's an
 interesting implementation of Knuth-Morris-Pratt substring searching
 (which is indeed a little language) which illustrates something or
 other:
 
  http://haskell.org/hawiki/RunTimeCompilation
 
 Nice.  Do you know if anyone has done anything like this for regular 
 expressions?  I'm thinking in particular that a function that turned a
 regular expression into a Parsec parser function could be useful, as
 in:
 
 regexp.compile :: String - GenParser Char st [String]
 
 where GenParser is defined by the Parsec library [1], and the parsed
 result is a list of substrings corresponding to the (...) parts of the
 regexp (if matched, of course).  (The parser result type might warrant
 some refinement.)

This page is full of strange and wonderful things,
http://www.haskell.org/libraries/

How 'bout the Haskell Dynamic Lexer Engine
http://www.nondot.org/sabre/Projects/HaskellLexer/

It doesn't create a Parsec parser, but it would be very easy to make a
function with it that did.

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


Re: replacing guile with haskell?

2003-10-22 Thread ajb
G'day all.

Quoting Peter Simons [EMAIL PROTECTED]:

 Just curious: Why would you want something like that? I thought that
 the good thing(tm) about regular expressions is that they can be
 parsed by a finite state machine rather than a recursive descent
 parser, [...]

Regular expressions can be parsed by a finite state machine.  POSIX
regexes can't.  Or, at least, not quite, particularly when you have
substring extraction and substitution to take into account.  At the
very least, you need some kind of backtracking NFA.

The story is even worse for Perl-compatible regexes.  Nobody is
entirely sure what classes of computation can be done with this
language but, for example, it's possible to construct a Perl regex
which only matches strings of prime length.

 so for all I know, the C regular expression library that comes
 with your system is most likely much faster than any Parsec code would
 every be.

Well, you never know until you try.  There _is_ overhead in converting
strings from Haskell to C and back again.  Yes, Parsec is probably the
wrong fit, but I think there might be merit in at least trying a full
Haskell implementation.

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


Re: replacing guile with haskell?

2003-10-21 Thread Graham Klyne
At 18:17 17/10/03 -0400, Isaac Jones wrote:
 H.  I may be able to get by without calling haskell functions from C.
 Most of the work would be done in C, and haskell would just be the glue
 language to let the user flexibly specify what he/she wants done.
I've always wanted to see some way to do embed Haskell in an
application the way you can for Guile.  This would be great for
Embedded Domain-Specific languages :)
Is that what you've got here?
Separately from this thread, it has recently occurred to me that Haskell is 
an ideal tool for implementing little languages [1], particularly when 
they are declarative in nature.

Specifically, Haskell's provision of higher order functions makes it 
relatively easy to translate some input language into a corresponding 
function which can then be directly evaluated, without the need for an 
explicit compilation or interpretation component.  (These are some thoughts 
that I hope to explore further in my own work.)

(Of course, this would apply to any language (ML springs to mind) that 
supports higher order functions.)

#g
--
[1] [1] Jon Bentley, Little languages, Communications of the ACM, 
29(8):711--21, August 1986.






Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: replacing guile with haskell?

2003-10-21 Thread ajb
G'day all.

Quoting Graham Klyne [EMAIL PROTECTED]:

 Separately from this thread, it has recently occurred to me that Haskell is
 an ideal tool for implementing little languages [1], particularly when
 they are declarative in nature.

Absolutely.  This is especially true in Haskell because there's a
fairly mechanical (if potentially tedious) procedure for removing a
layer of interpretation from a little language implementation.  If you're
careful, you can even do this at run-time.

I think I might have mentioned this previously, but here's an interesting
implementation of Knuth-Morris-Pratt substring searching (which is indeed
a little language) which illustrates something or other:

http://haskell.org/hawiki/RunTimeCompilation

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


Re: replacing guile with haskell?

2003-10-21 Thread Graham Klyne
At 04:17 21/10/03 -0400, [EMAIL PROTECTED] wrote:
I think I might have mentioned this previously, but here's an interesting
implementation of Knuth-Morris-Pratt substring searching (which is indeed
a little language) which illustrates something or other:
http://haskell.org/hawiki/RunTimeCompilation
Nice.  Do you know if anyone has done anything like this for regular 
expressions?  I'm thinking in particular that a function that turned a 
regular expression into a Parsec parser function could be useful, as in:

   regexp.compile :: String - GenParser Char st [String]

where GenParser is defined by the Parsec library [1], and the parsed result 
is a list of substrings corresponding to the (...) parts of the regexp (if 
matched, of course).  (The parser result type might warrant some refinement.)

#g
--
[1] http://www.cs.uu.nl/~daan/parsec.html

ParsecPrim.hs defines GenParser thus:
[[
---
-- Parser definition.
-- GenParser tok st a:
--  General parser for tokens of type tok,
--  a user state st and a result type a
---
type Parser a   = GenParser Char () a
newtype GenParser tok st a  = Parser (State tok st - Consumed (Reply tok 
st a))
runP (Parser p) = p

data Consumed a = Consumed a--input is consumed
| Empty !a  --no input is consumed
data Reply tok st a = Ok !a !(State tok st) ParseError--parsing 
succeeded with a
| Error ParseError--parsing failed

data State tok st   = State { stateInput :: ![tok]
, statePos   :: !SourcePos
, stateUser  :: !st
}
]]



Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: replacing guile with haskell?

2003-10-18 Thread David Roundy
On Fri, Oct 17, 2003 at 06:17:00PM -0400, Isaac Jones wrote:
 David Roundy [EMAIL PROTECTED] writes:
 
  Do you want to embed Haskell code or to embed a Haskell interpreter?
 
  I actually would like to embed a Haskell interpreter.
 
 (snip)
 
  H.  I may be able to get by without calling haskell functions from C.
  Most of the work would be done in C, and haskell would just be the glue
  language to let the user flexibly specify what he/she wants done.  
 
 I've always wanted to see some way to do embed Haskell in an
 application the way you can for Guile.  This would be great for
 Embedded Domain-Specific languages :)
 
 Is that what you've got here?

Yeah, that's essentially what I've got.  The only difference being that in
my case usually user's shouldn't need to know that they are using a
programming language.  Which is why using a declarative language sounds so
nice.  I'll have to explain to users the difference between actions and
definitions, but that shouldn't be too hard as long as users don't
realize they are programming!  :)  Declarative statements are how you'd
normally expect an input file to behave (i.e. the order doesn't matter).
-- 
David Roundy
http://www.abridgegame.org/darcs
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


replacing guile with haskell?

2003-10-17 Thread David Roundy
I'm wondering what the possibilities are for replacing the use of guile
with a haskell interpereter? I'd like to be able to embed a haskell
interpereter (presumably hugs) withing my program, so that the input file
could be a haskell program.  The application is a numerical simulation
code, for which the input is (among other things) a photonic crystal
structure.  Practically, this means that the input file needs to be a
program (or the user needs to write a program to generate the input
file--ugly).

Currently my code works as a C++ library, but that isn't particularly
convenient (except for development).  A similar code (mpb--it's available
in debian) by a coworker has the input format in scheme using guile.
That's nice in many ways, except I can't stand scheme.  So I'm wondering
whether there might be some convenient way to accomplish the same goal with
haskell.

Currently, my best (and only) idea is to make the input file a script with
#!/usr/bin/env runhugs
at the top (and compiling an interface module with ffihugs).

There are a couple of issues with this.  The first is that I've heard that
hugs isn't intended for numerical work (which is what I'm doing).  I'm not
sure if this will be a problem, since hugs won't be doing any of the real
work anyways.

The other is that according to the man page, it seems that hugs only
supports ffi on x86, powerpc and sparc, which seems likely to be a show
stopper.  Since I'll need to run the code on supercomputers, I won't always
have a choice of architectures, and at least support for POWER (maybe comes
free with powerpc?) would be necesary--IBM SP machines are quite nice.  In
this regard, ghc seems worse than hugs (the thought of bootstrapping ghc on
a supercomputer gives me the shivers), and nhc98 last time I looked didn't
support 64 bit platforms.

Is there a solution to these problems, or will I be stuck with thousands of
parentheses in my input file?
-- 
David Roundy
http://www.abridgegame.org/darcs
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: replacing guile with haskell?

2003-10-17 Thread Alastair Reid

 I'm wondering what the possibilities are for replacing the use of guile
 with a haskell interpereter? I'd like to be able to embed a haskell
 interpereter (presumably hugs) withing my program, so that the input file
 could be a haskell program.

Do you want to embed Haskell code or to embed a Haskell interpreter?

Embedding Haskell code is supported by the ffi specification and, in 
particular, by GHC which will give good performance and trustworthy numeric 
results.

 Currently, my best (and only) idea is to make the input file a script with
 #!/usr/bin/env runhugs
 at the top (and compiling an interface module with ffihugs).

You might get a little more value out of the Hugs server interface which lets 
you unload and reload modules, etc.

See hugs98/docs/server.{html,tex}.
The documentation on
http://www.reid-consulting-uk.ltd.uk/alastair/publications/hugs-server/
server.ps.gz
is an out of date version of this document but gives a reasonable overview.

Googling for hugs server will find you various articles about using this 
API.

 There are a couple of issues with this.  The first is that I've heard that
 hugs isn't intended for numerical work (which is what I'm doing).  I'm not
 sure if this will be a problem, since hugs won't be doing any of the real
 work anyways.

It's hard to comment on this.  Hugs numeric routines are a lot better than 
when the original don't use advice was written - but people do complain 
every now and then.

 The other is that according to the man page, it seems that hugs only
 supports ffi on x86, powerpc and sparc, which seems likely to be a show
 stopper.  Since I'll need to run the code on supercomputers, I won't always
 have a choice of architectures, and at least support for POWER (maybe comes
 free with powerpc?) would be necesary--IBM SP machines are quite nice.  In
 this regard, ghc seems worse than hugs (the thought of bootstrapping ghc on
 a supercomputer gives me the shivers), and nhc98 last time I looked didn't
 support 64 bit platforms.

It's only calling Haskell functions from C which is non-portable.  
Unfortunately, I'd guess that's the bit you need!

Porting Hugs' ffi to a new platform is pretty easy for someone with assembly 
code experience since you only have to write one function - albeit a tricky 
one.  Less if ghc has already been ported to that platform since we can steal 
code from them :-)  The code involved is the function 'mkThunk' in hugs98/
src/builtin.c

GHC is available for powerpcs so it's probably just the operating system that 
will cause trouble.

I would guess that nhc is easy to port to 64 bit machines since (at least 
some) C compilers provide flags to compile for 32-bits.  But I could easily 
be wrong...

[Note: both GHC and NHC will need pretty much the same assembly code magic 
that Hugs needs.]

--
Alastair Reid www.haskell-consulting.com

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


Re: replacing guile with haskell?

2003-10-17 Thread David Roundy
On Fri, Oct 17, 2003 at 02:08:06PM +0100, Alastair Reid wrote:
 
  I'm wondering what the possibilities are for replacing the use of guile
  with a haskell interpereter? I'd like to be able to embed a haskell
  interpereter (presumably hugs) withing my program, so that the input file
  could be a haskell program.
 
 Do you want to embed Haskell code or to embed a Haskell interpreter?

I actually would like to embed a Haskell interpreter.

  There are a couple of issues with this.  The first is that I've heard that
  hugs isn't intended for numerical work (which is what I'm doing).  I'm not
  sure if this will be a problem, since hugs won't be doing any of the real
  work anyways.
 
 It's hard to comment on this.  Hugs numeric routines are a lot better than 
 when the original don't use advice was written - but people do complain 
 every now and then.

That's good news.  I'll hope that since the heavy lifting is in C++ I
should be fine...

  The other is that according to the man page, it seems that hugs only
  supports ffi on x86, powerpc and sparc, which seems likely to be a show
  stopper.  Since I'll need to run the code on supercomputers, I won't always
  have a choice of architectures, and at least support for POWER (maybe comes
  free with powerpc?) would be necesary--IBM SP machines are quite nice.  In
  this regard, ghc seems worse than hugs (the thought of bootstrapping ghc on
  a supercomputer gives me the shivers), and nhc98 last time I looked didn't
  support 64 bit platforms.
 
 It's only calling Haskell functions from C which is non-portable.  
 Unfortunately, I'd guess that's the bit you need!

H.  I may be able to get by without calling haskell functions from C.
Most of the work would be done in C, and haskell would just be the glue
language to let the user flexibly specify what he/she wants done.  It
*would* be nice, however, to let the user specify the dielectric function
as a function of position as a haskell function!  But in most cases, the
user will build up the structure out of primitives (cylinders, spheres,
etc), and that can be done without calling haskell from C.

 Porting Hugs' ffi to a new platform is pretty easy for someone with
 assembly code experience since you only have to write one function -
 albeit a tricky one.  Less if ghc has already been ported to that
 platform since we can steal code from them :-) The code involved is the
 function 'mkThunk' in hugs98/ src/builtin.c

That's encouraging, but alas I have no real assembly code experience.

 I would guess that nhc is easy to port to 64 bit machines since (at least
 some) C compilers provide flags to compile for 32-bits.  But I could
 easily be wrong...

H.  The catch is that you'd then be using 32 pointers, and I doubt that
the MPI libraries will run in 32 bit mode...

Thanks for the advice! I'm a bit more optimistic now that the runhugs
solution will work.  I've still got a week or two of C++ work to go, plus
putting a C wrapper around everything, before I can seriously consider
starting work on a haskell interface.
-- 
David Roundy
http://civet.berkeley.edu/droundy/
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: replacing guile with haskell?

2003-10-17 Thread Isaac Jones
David Roundy [EMAIL PROTECTED] writes:

 Do you want to embed Haskell code or to embed a Haskell interpreter?

 I actually would like to embed a Haskell interpreter.

(snip)

 H.  I may be able to get by without calling haskell functions from C.
 Most of the work would be done in C, and haskell would just be the glue
 language to let the user flexibly specify what he/she wants done.  

I've always wanted to see some way to do embed Haskell in an
application the way you can for Guile.  This would be great for
Embedded Domain-Specific languages :)

Is that what you've got here?


peace,

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