[Haskell-cafe] Comparing functions

Roman Cheplyaka roma at ro-che.info
Thu Jul 11 20:10:42 CEST 2013


* Vlatko Basic <vlatko.basic at gmail.com> [2013-07-11 19:33:38+0200]
> Hello Cafe,
> 
> I have
> 
>     data CmpFunction a = CF (a -> a -> Bool)
> 
> that contains comparing functions, like ==, <, > ..., and I'm trying
> to declare the Show instance for it like this
> 
>     instance Show (CmpFunction a) where
>       show (CF (==)) = "== "                   -- no good
>       show f = case f of                            -- no good also
>                        CBF (==) -> "=="
>                         _ -> "Other"
> 
> but compiler complains for both with
> 
> This binding for `==' shadows the existing binding
>            imported from `Prelude' at src/Main.hs:6:8-11
>            (and originally defined in `ghc-prim:GHC.Classes')
> 
> Is it possible at all to compare two functions or how to solve this
> problem, to show some string for a specific function?

Depending on why you need that...

  {-# LANGUAGE FlexibleContexts, UndecidableInstances, FlexibleInstances #-}
  import Test.SmallCheck
  import Test.SmallCheck.Series
  import Test.SmallCheck.Drivers
  import Control.Monad.Identity
  import Data.Maybe

  data CmpFunction a = CF (a -> a -> Bool)

  feq :: (Show a, Serial Identity a) => CmpFunction a -> CmpFunction a -> Bool
  feq (CF f1) (CF f2) =
    isNothing $
      runIdentity $
        smallCheckM 10 (\x1 x2 -> f1 x1 x2 == f2 x1 x2)

  instance Show (CmpFunction Integer) where
    show f
      | f `feq` CF (==) = "=="
      | f `feq` CF (/=) = "/="
      | f `feq` CF (<)  = "<"
      | f `feq` CF (<=)  = "<="
      | otherwise = "Unknown function"

This uses SmallCheck to figure out, with some degree of certainty,
whether two functions are equal.

Of course, Rice's theorem still holds, and the above instance is easy
to fool, but it still might be useful in some cases.

Roman



More information about the Haskell-Cafe mailing list