[Haskell-cafe] Perl-ish =~ operator

ozone at algorithm.com.au ozone at algorithm.com.au
Tue Feb 24 01:30:18 EST 2004


In my effort to turn Haskell into a language more like Perl 
(muahaha)[1], I got a bit fed up and implemented something like Perl 
5's =~ binding operator (a.k.a. "regex" operator); I thought maybe 
somebody else here might find it useful.  Perl has the concept of 
'contexts': a function does something different depending on what type 
its caller expects back from the function.  Sounds like a perfect abuse 
of type classes, to me :).  Code follows:

---
{-# OPTIONS -fglasgow-exts #-}
{-  Need this for "instance Foo [String]" declarations -}

module PLRE where
-- Perl-Like Regular Expressions

import Text.Regex

-- Perl-Like =~ operator, which changes behaviour depending on its 
calling
-- context

class RegExContext a where
   (=~) :: String -> String -> a

instance RegExContext Bool where
   s =~ re = case matchRegex (mkRegex re) s of
     Nothing -> False
     Just x -> True

instance RegExContext [String] where
   s =~ re = case matchRegex (mkRegex re) s of
     Nothing -> []
     Just x -> x

boolContextTest string regEx =
   case string =~ regEx of
     True -> print True
     False -> print False

stringListContextTest string regEx =
   case string =~ regEx of
     (a:x) -> print ("First match: " ++ a)
     _ -> error "No subexpression matches"
---

Some test output for you:

*PLRE> boolContextTest "foo" "^f"
True
*PLRE> boolContextTest "foo" "^g"
False
*PLRE> stringListContextTest "foo" "^(.)"
"First match: f"
*PLRE> stringListContextTest "goo" "^(.)"
"First match: g"
*PLRE> stringListContextTest "" "^(.)"
*** Exception: No subexpression matches

Note that you have a fairly severe restriction if you want to use =~ in 
your code: the Haskell compiler must be able to determine a concrete 
type for the context that =~ is used in.  i.e. if stringListContextTest 
was defined as:

stringListContextTest string regEx =
   case string =~ regEx of
     (a:x) -> print a
     _ -> error "No subexpression matches"

The compiler can't concretise a type for 'a', and it'll complain about 
not having an instance for RegExContext [a] (which is fair enough).  
Even with this restriction, I'm sure it'll still be useful.  It 
shouldn't be a bit leap to define other Perl-ish operators in this 
fashion, such as !~, or even s/.../.  Have the appropriate amount of 
fun!

1. Actually, I wanted to turn Haskell into a language more suitable for 
text processing, but that doesn't sound as evil.


-- 
% Andre Pang : trust.in.love.to.save


More information about the Haskell-Cafe mailing list