On 24/02/2004, at 1:30 AM, Andre Pang wrote:

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 :).

And, just for kicks, here's Perl 6's "smart match" (~~) operator, which works much like ==, but in a more "Do What I Mean!" fashion, matching any type to any other type:


---
{-# OPTIONS -fglasgow-exts -fallow-undecidable-instances -fallow-overlapping-instances #-}


module SmartMatch where

import Text.Regex

class TruthValue a where
  truth :: a -> Bool

instance TruthValue Bool where
  truth = id

instance TruthValue Int where
  truth 0 = False
  truth _ = True

instance TruthValue String where
  truth "" = False
  truth _  = True

instance TruthValue a => TruthValue [a] where
  truth = all truth


class SmartMatch a b where (~~) :: a -> b -> Bool

instance Eq a => SmartMatch a a where
  a ~~ b = a == b

instance SmartMatch c d => SmartMatch d c where
  a ~~ b = b ~~ a

instance TruthValue a => SmartMatch Bool a where
  a ~~ b = a == truth b

instance SmartMatch String Regex where
  s ~~ re = case matchRegex re s of
    Nothing -> False
    Just x -> True
---


-- % Andre Pang : trust.in.love.to.save _______________________________________________ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to