[Haskell] Overriding Prelude functions

André Pang ozone at algorithm.com.au
Mon Jul 5 03:59:45 EDT 2004


Hi all,

Inspired by a bit of hackery today, I managed to find a nice way to 
re-define Prelude functions in modular way.  There may be some 
functions in the Prelude that you would like to redefine: in this 
example, we redefine the "lookup" function, which normally has a type 
signature of

   lookup :: forall b a. (Eq a) => a -> [(a, b)] -> Maybe b

Here, we make lookup a bit more generic, so that we can look up any 
data structure that is "lookupable" -- we override the Prelude's lookup 
function with our own.  The motivation is that there may be a module 
which provides you many useful functions, but unfortunately has 
namespace clashes with your own module.  One example is that you've 
defined a generic 'zip' function named gzip, which could substitute 
perfectly for the Prelude's own zip function, but you have to call it 
gzip only because the function name 'zip' is already taken.  The 
advantage of this is that you can smoothly integrate extra 
functionality with already-existing functions by overriding them -- and 
by providing the extra functionality in a module, you leave it up to 
the module user whether they want to take advantage of that 
functionality or not.

The essential idea is to define a module (e.g. MyPrelude), which does 
the following:

   module MyPrelude(module Prelude, lookup) where

   import qualified Prelude as P
   import Prelude hiding (lookup)

   lookup = ... (your own definition here) ...

That module re-exports the Prelude and its own lookup function.  Then, 
a module which wants to use the overridden lookup function does the 
following:

   {-# OPTIONS -fno-implicit-prelude #-}

   module UseLookup where

   import MyPrelude

   ... now uses MyPrelude's lookup function instead of Prelude's lookup 
...

A concrete implementation of this idea is below.  Have the appropriate 
amount of fun :).

MyPrelude.hs

   {-# OPTIONS -fglasgow-exts #-}

   module MyPrelude(module Prelude, lookup) where

   import qualified Prelude as P
   import Prelude hiding (lookup)

   import Data.FiniteMap
   import Data.Set

   -- override the lookup function, defined in the Prelude as:
   --
   -- lookup :: forall b a. (Eq a) => a -> [(a, b)] -> Maybe b

   class Lookup lookupable key value | lookupable -> key value where
     lookup :: Ord key => lookupable -> key -> Maybe value

   instance Lookup (FiniteMap key value) key value where
     lookup = lookupFM

   instance Lookup [(key, value)] key value where
     lookup = lookupListOfTuples

   instance Lookup (Set value) value value where
     lookup container element
       | elementOf element container = Just element
       | otherwise                   = Nothing

   lookupListOfTuples [] _ = Nothing
   lookupListOfTuples ((key, value):xs) key'
       | key == key' = Just value
       | otherwise   = lookupListOfTuples xs key'

UseLookup.hs:

   {-# OPTIONS -fno-implicit-prelude #-}

   module UseLookup where

   import Data.FiniteMap
   import Data.Set
   import MyPrelude

   fm = addToFM emptyFM "foo" "bar"

   set = mkSet ["foo"]

   tupleList = [("foo", "bar")]

An example session:

   *UseLookup> lookup fm "foo"
   Just "bar"
   *UseLookup> lookup fm "baz"
   Nothing
   *UseLookup> lookup set "foo"
   Just "foo"
   *UseLookup> lookup tupleList "foo"
   Just "bar"
   *UseLookup>


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



More information about the Haskell mailing list