Re: [Haskell-cafe] trivial function application question

2007-01-05 Thread Jules Bean

tphyahoo wrote:

So the core question (speaking as a perler) is how do you write

  my $s= 'abcdefg';
  $s =~ s/a/z/g;
  $s =~ s/b/y/g;
  print $s\n;

 in haskell? There are various haskell regex libraries out there,
  


But that's such a perler attitude. When all you have is a regex, 
everything looks like a s///!


This really doesn't look like much of a regex question to me. A more 
haskelly answer might be as simple as:


m 'a' = 'z'
m 'b' = 'y'
m  x  = x

test1 = map m abcdefg

...which is general in the sense that 'm' can be an arbitrary function 
from Char - Char, and avoids the 'overlapping replace' behaviour 
alluded to elsewhere in this thread, but is limited if you wanted to do 
string-based replacement.


To do string-based replacement you do have to think careful about what 
semantics you're expecting though (w.r.t. overlapping matches, repeated 
matches, priority of conflicting matches).


Jules
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] trivial function application question

2007-01-05 Thread Chris Kuklewicz
tphyahoo wrote:
 So the core question (speaking as a perler) is how do you write
 
   my $s= 'abcdefg';
   $s =~ s/a/z/g;
   $s =~ s/b/y/g;
   print $s\n;
 
  in haskell? There are various haskell regex libraries out there,
  including ones that advertise they are PCRE (Perl Compatible Reg Ex).
 

I updated the regex libraries for GHC 6.6. ( All the regex-* packages. )  The
old API is still supported in Text.Regex.  The old API has a replacement
function, while the new API does not have one (yet).

For simple regular expressions, where Posix and Perl agree, you can just use
Text.Regex.subRegex which comes with GHC.  In 6.6 this comes in the regex-compat
package, and which calls the regex-posix backend via the interfaces defined in
regex-base.  All of these come with GHC, since GHC needs regex support to
compile itself.

So if you do not need more syntax than POSIX regex (with back references) then

http://www.haskell.org/ghc/docs/latest/html/libraries/regex-compat/Text-Regex.html#v%3AsubRegex

works, but depends on the low performance posix-regex backend.  This will run
your example above, for instance.

Better regex searching performance can be had by using the new interface via
Text.Regex.Base with better backends and/or with Data.ByteString.  In the future
there will be Data.Sequence (of Char and perhaps Word8) support added to the
backends.

There is no updated API for performing replacements using a pluggable backend.
The design space is too large with conflicting needs to be lazy or strict, time
or space efficient, etc.  The best thing is to write the replacement function
that your application needs.  You can use the new searching API (see
micro-tutorial below) to write a replacement routine in less than a screen of 
code.

For instance, the regex-compat version of Text.Regex.subRegex is

 {- | Replaces every occurance of the given regexp with the replacement string.
 
 In the replacement string, @\\\1\@ refers to the first substring;
 @\\\2\@ to the second, etc; and @\\\0\@ to the entire match.
 @\\@ will insert a literal backslash.
 
 This is unsafe if the regex matches an empty string.
 -}
 subRegex :: Regex  -- ^ Search pattern
   - String -- ^ Input string
   - String -- ^ Replacement text
   - String -- ^ Output string
 subRegex _  _ = 
 subRegex regexp inp repl =
 let bre = mkRegex (|[0-9]+)
 lookup _ [] _ = []
 lookup [] _ _ = []
 lookup match repl groups =
 case matchRegexAll bre repl of
 Nothing - repl
 Just (lead, _, trail, bgroups) -
 let newval = if (head bgroups) == \\
  then \\
  else let index = (read (head bgroups)) - 1
   in
   if index == -1
  then match
  else groups !! index
 in
 lead ++ newval ++ lookup match trail groups
 in
 case matchRegexAll regexp inp of
 Nothing - inp
 Just (lead, match, trail, groups) -
   lead ++ lookup match repl groups ++ (subRegex regexp trail repl)

You could just paste that code into a file that imports a different backend and
it should work since it uses just the type class API. You might also improve on
the above routine or specialize it.  The above handle \0 \1 \2 substitutions
(and \\ escaping) in the replacement string, including multi-digit references
such as \15 for very large regular expressions.  It operation only on [Char] and
is somewhat lazy.

  But which one to use? How hard to install? With the libs mentioned
  above, the PCRE-ness seems only to be for matching, not for
  substitutions.
 

I think if you paste the subRegex code above underneath an import
Text.Posix.PCRE declaration then you get what you are looking for.

To install:

The regex-* package hosting is via darcs and has been copied/moved to

http://darcs.haskell.org/packages/   (The stable regex-* versions)
http://darcs.haskell.org/packages/regex-unstable/  (The unstable regex-* 
versions)

so darcs get --partial http://darcs.haskell.org/packages/regex-pcre; might be
useful.

They have (hopefully working) cabal files to make compiling and installing easy.
 Note that regex-pcre and regex-tre need libpcre and libtre to be installed
separately.  regex-posix needs a posix library, but GHC already provides this
package with a working libary.

These 3 come with GHC:

regex-base defines the type classes and APIs and most RegexContext instances
regex-compat imitates the old Text.Regex API using regex-posix
regex-posix backend has awful performance.  Not for heavy use.

These 4 backends can be downloaded using darcs:

regex-pcre uses libpcre 

Re: [Haskell-cafe] trivial function application question

2007-01-05 Thread Yitzchak Gale

tphyahoo wrote:

There are various haskell regex libraries out there,


Jules Bean wrote:

But that's such a perler attitude. When all you have is a regex,
everything looks like a s///!


Not always, sometimes it is right to use regexes in Haskell
also.

If there are more than a few patterns to match in the same
string, or if the patterns are more than a few characters long,
then the simple approach will start becoming expensive.

You need to use a more sophisticated algorithm - building
up trees of potential matches, backtracking in some cases,
etc. Why re-invent the wheel? Just use the regex library,
where that is already done.

Regards,
Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] trivial function application question

2007-01-05 Thread Jules Bean

Yitzchak Gale wrote:


You need to use a more sophisticated algorithm - building
up trees of potential matches, backtracking in some cases,
etc. Why re-invent the wheel? Just use the regex library,
where that is already done.



It's merely a question of selecting the right wheel. Some problems are 
so simple that regexes are overkill. Some problems are so complex that 
regexes are insufficient. Some problems generate extraordinarily ugly 
regexes, which are then hard-to-debug.


Some problems are perfectly suited to regexes.

Jules

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


Re: [Haskell-cafe] trivial function application question

2007-01-05 Thread Brandon S. Allbery KF8NH


On Jan 5, 2007, at 9:38 , Jules Bean wrote:


Yitzchak Gale wrote:

You need to use a more sophisticated algorithm - building
up trees of potential matches, backtracking in some cases,
etc. Why re-invent the wheel? Just use the regex library,
where that is already done.


It's merely a question of selecting the right wheel. Some problems  
are so simple that regexes are overkill. Some problems are so  
complex that regexes are insufficient. Some problems generate  
extraordinarily ugly regexes, which are then hard-to-debug.


I will note that the most common use for regexes in Perl is for  
parsing (which is why perl6 has generalized regexes into a parsing  
mechanism).


--
brandon s. allbery[linux,solaris,freebsd,perl] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH



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


Re: [Haskell-cafe] trivial function application question

2007-01-05 Thread Bill Wood
It would seem that for a regular expression facility to constitute a
parser it would have to be able to work on token streams. So my question
is, does either the the perl6 generalization or any of the Haskell regex
facilities support regular expressions over any free monoid other than
finite character sequences?

 -- Bill Wood



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


Re: [Haskell-cafe] trivial function application question

2007-01-05 Thread Chris Kuklewicz
Bill Wood wrote:
 It would seem that for a regular expression facility to constitute a
 parser it would have to be able to work on token streams. So my question
 is, does either the the perl6 generalization or any of the Haskell regex
 facilities support regular expressions over any free monoid other than
 finite character sequences?
 
  -- Bill Wood
 

Currently: The regular expressions themselves are finite, but some Haskell
regex-* backend packages can run searches on infinite [Char], since they are
lazy.  This is true of regex-parsec and regex-dfa.  In particular they take care
not to consume extra Char's from the input stream, though Parsec insists on
looking at the next character.

The regex-base type class API in Text.Regex.Base.RegexLike does not limit you to
any particular source of the regex or any particular type of thing to be
searched.  There is a limit that comes from using Int as the index of choice.
If you are searching something more that 2 billion units long then you would run
into API problems.  (One could just make a parallel BigRegex type class API and
make instances for it for the backends that can handle it.
).  Or I may expand it to take any (Num).  Hmmm.

Specifically, the RegerMaker is parameterized over source and regex and so
is completely generic.  This source is what specifies how to build the the
compiled regex opaque type.

Specifically, the Extract is parameterized over source (but limits the index
to Int).  This source is the type being searched.

Specifically, the RegexLike class is parameterized over regex and source,
where regex is the supposed to be the opaque compiled type from RegexMaker and
source is the type being searched.

Currently the RegexMaker source can be [Char] or ByteString and the
RegexLike/Extract source can be [Char] or ByteString.

Adding (Data.Sequence Char) would make sense, and perhaps (Data.Sequence Word8)
as ASCII.  If you write a very generic backend then you may be able to make more
generic instances of the API.  Note that the instances should be obvious because
your generic backend uses a unique opaque regex type.

Also not that the API is named Regex in several places but there is no need to
use anything like a Regex syntax.  In fact you could use something other than
RegexMaker to create the regex type used for specifying the
searching/matching.  I have not considered it until now, but maybe one could
create an instance of RegexLike based around Parsec's GenParser.

-- 
Chris
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] trivial function application question

2007-01-05 Thread Donald Bruce Stewart
tphyahoo:
 
 So the core question (speaking as a perler) is how do you write
 
   my $s= 'abcdefg';
   $s =~ s/a/z/g;
   $s =~ s/b/y/g;
   print $s\n;

Simple patterns like this you'd just use a 'map' of course:

main = print (clean abcdefg)

clean = map (by . az)
  where by c = if c == 'b' then 'y' else c
az c = if c == 'a' then 'z' else c

Running this:

$ runhaskell A.hs
zycdefg

Now, using regexes instead we can get by with just the regex-compat lib,
providing:

import Text.Regex

I usually flip the arguments to subRegex, since they're in the wrong
order for composition (anyone else noticed this?):

sub   re y s = subRegex re s y
regex= mkRegex


Now , using proper regexes, we can write:

main  = print (clean abcdefg)

clean = sub (regex b) y
  . sub (regex a) z

Running this:

$ runhaskell A.hs
zycdefg


Similar results will be achieved with the other regex-* packages:


http://haskell.org/haskellwiki/Libraries_and_tools/Compiler_tools#Regular_expressions

I think TRE might be preferred for high performance cases.

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] trivial function application question

2007-01-04 Thread brad clawsie
greetings to this helpful and informative list

i have a small problem that will be certainly trivial for almost
everyone reading this, i would appreciate a little help

lets say i have a string

s = abcdefg

now i have two lists of strings, one a list of patterns to match, and
a list of replacement strings:

patterns = [a,b]
replace = [Z,Y]

from which my intent is that a be replaced by Z, b by Y etc

now using the replace function from MissingH.Str (which i know is now 
renamed), i wish to apply replace to s using (pattern[0], replace[0]), 
(pattern[1], replace[1])...(pattern[N], replace[N]).

i am sure there is an elegant way to apply replace to s for all of
these argument pairs without composing replace N times myself, but the
solution escapes me.

thanks in advance for any help you can provide for this trivial issue
brad

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


Re: [Haskell-cafe] trivial function application question

2007-01-04 Thread Neil Mitchell

Hi Brad,


i have a small problem that will be certainly trivial for almost
everyone reading this, i would appreciate a little help


If you have trivial problems, its often useful to ask on Haskell IRC
(http://www.haskell.org/haskellwiki/IRC_channel)


from which my intent is that a be replaced by Z, b by Y etc

i am sure there is an elegant way to apply replace to s for all of
these argument pairs without composing replace N times myself, but the
solution escapes me.


In your example all strings are one letter long, is that how this
works? If so, then you can simplify the problem significantly to use
Char's, and use the following library functions:

First off, if you want to apply the same transformation to each item
of a list, namely to either replace it or leave it the same. This
calls out for map.

Secondly you want to do lookups in some sort of table. The lookup
function can be very handy here. The lookup function works on
associative lists, so you'd need to zip patterns and replace into an
associative list.

If you really want to operate on strings, rather than characters, then
you have to be more clever. Also replace called multiple times
probably won't be enough, consider replacing 1 with 2, 2 with 3. If
you just call replace multiple times, 1 may well end up at 3, when 2
is more likely to be the right answer.

Thanks

Neil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] trivial function application question

2007-01-04 Thread J. Garrett Morris

On 1/4/07, brad clawsie [EMAIL PROTECTED] wrote:

lets say i have a string

s = abcdefg

now i have two lists of strings, one a list of patterns to match, and
a list of replacement strings:

patterns = [a,b]
replace = [Z,Y]

from which my intent is that a be replaced by Z, b by Y etc

now using the replace function from MissingH.Str (which i know is now
renamed), i wish to apply replace to s using (pattern[0], replace[0]),
(pattern[1], replace[1])...(pattern[N], replace[N]).


You can create the replacing functions using zipWith :: (a - b - c)
- [a] - [b] - [c] (from the Prelude) as follows:

replacers = zipWith patterns replace

You then need to apply these functions to your starting string s.  I
would probably use foldr for that, something like this:

foldr ($) s replacers

Where ($) performs function application.

As Neil points out, if your replacements overlap, this could cause
replacement text to itself be replaced.

/g

--
It is myself I have never met, whose face is pasted on the underside of my mind.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] trivial function application question

2007-01-04 Thread tphyahoo

So the core question (speaking as a perler) is how do you write

  my $s= 'abcdefg';
  $s =~ s/a/z/g;
  $s =~ s/b/y/g;
  print $s\n;

 in haskell? There are various haskell regex libraries out there,
 including ones that advertise they are PCRE (Perl Compatible Reg Ex).

 But which one to use? How hard to install? With the libs mentioned
 above, the PCRE-ness seems only to be for matching, not for
 substitutions.

 http://www.cs.chalmers.se/~d00nibro/harp/
 http://repetae.net/john/computer/haskell/JRegex/

 So, I would like to know a good answer to this as well.

 thomas.




brad clawsie-2 wrote:
 
 greetings to this helpful and informative list
 
 i have a small problem that will be certainly trivial for almost
 everyone reading this, i would appreciate a little help
 
 lets say i have a string
 
 s = abcdefg
 
 now i have two lists of strings, one a list of patterns to match, and
 a list of replacement strings:
 
 patterns = [a,b]
 replace = [Z,Y]
 
 from which my intent is that a be replaced by Z, b by Y etc
 
 now using the replace function from MissingH.Str (which i know is now 
 renamed), i wish to apply replace to s using (pattern[0], replace[0]), 
 (pattern[1], replace[1])...(pattern[N], replace[N]).
 
 i am sure there is an elegant way to apply replace to s for all of
 these argument pairs without composing replace N times myself, but the
 solution escapes me.
 
 thanks in advance for any help you can provide for this trivial issue
 brad
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

-- 
View this message in context: 
http://www.nabble.com/trivial-function-application-question-tf2922232.html#a8173692
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] trivial function application question

2007-01-04 Thread J. Garrett Morris

Oops, I seem not to have proofread my message.

On 1/4/07, J. Garrett Morris [EMAIL PROTECTED] wrote:

On 1/4/07, brad clawsie [EMAIL PROTECTED] wrote:
 s = abcdefg
 patterns = [a,b]
 replacements = [Z,Y]


I changed the name here so as not to conflict with the replace function.

snip


You can create the replacing functions using zipWith :: (a - b - c)
- [a] - [b] - [c] (from the Prelude) as follows:

replacers = zipWith replace patterns replacements


This line was previously incorrect.

/g
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe