Re: [Haskell-cafe] Comparing functions

2013-07-12 Thread Vlatko Basic
Thanks Roman. Tried it and implemented, but had troubles until I realized that 
for String, 10 test take quite long. :-)


However, I decided to solve this problem in a more natural way


 Original Message  
Subject: Re: [Haskell-cafe] Comparing functions
From: Roman Cheplyaka r...@ro-che.info
To: Vlatko Basic vlatko.ba...@gmail.com
Cc: Haskell-Cafe haskell-cafe@haskell.org
Date: 11.07.2013 20:10


* Vlatko Basic vlatko.ba...@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



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


[Haskell-cafe] Comparing functions

2013-07-11 Thread Vlatko Basic

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?



br,
vlatko


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


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread Brandon Allbery
On Thu, Jul 11, 2013 at 1:33 PM, Vlatko Basic vlatko.ba...@gmail.comwrote:

 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')


The problem here isn't quite what you think it is; (==) is not a
constructor, therefore it is a *variable*. It's exactly the same problem as

a = 5
-- ...
foo a = 3 -- this does NOT compare with the previous value of a; it's
identical to the next line!
foo x = x

Just as with the above, the normal way to do it would be to use a guard...
but functions don't have an Eq instance, and *can't* have one. How do you
meaningfully compare them? And for a typeclass function like (==), do you
want (==) instantiated for Int to compare equal to (==) instantiated for
Integer? Does a native-compiled function compare equal to an interpreted
function? Remember referential transparency; the concept of comparing
pointers used in some languages is not applicable to Haskell.

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread Timon Gehr

On 07/11/2013 07:33 PM, Vlatko Basic wrote:

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')



Yes, (==) is a variable name in a pattern. Hence you are creating a new 
definition for (==) bound to the constructor argument to CF, which hides 
the (==) defined within the Eq type class.



Is it possible at all to compare two functions


Function types are opaque and values do not have an identity.


or how to solve this problem, to show some string for a specific function?


br,
vlatko


You could store the string alongside the function inside the data type 
in some way.



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


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread Vlatko Basic

  
  



 Original Message 
  Subject: Re: [Haskell-cafe] Comparing functions
  From: Brandon Allbery allber...@gmail.com
  To: Vlatko Bašić vlatko.ba...@gmail.com
  Cc: Haskell-Cafe haskell-cafe@haskell.org
  Date: 11.07.2013 19:50



  
  On Thu, Jul 11, 2013 at 1:33 PM, Vlatko Basic vlatko.ba...@gmail.com
wrote:

  
    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')



The problem here isn't quite what you think it
  is; (==) is not a constructor, therefore it is a
  *variable*. It's exactly the same problem as


    a = 5
    -- ...
    foo a = 3 -- this does NOT compare with
  the previous value of "a"; it's identical to the next
  line!
    foo x = x


  

  
  
Hm, I thought it is a pattern match with constant, as in f ('a':xs)
== 



  

  
Just as with the above, the normal way to do
  it would be to use a guard... but functions don't have an
  Eq instance, and *can't* have one. How do you meaningfully
  compare them? And for a typeclass function like (==), do
  you want (==) instantiated for Int to compare equal to
  (==) instantiated for Integer? Does a native-compiled
  function compare equal to an interpreted function?
  Remember referential transparency; the concept of
  comparing pointers used in some languages is not
  applicable to Haskell.


  
  -- 
  
brandon s allbery kf8nh                              
  sine nomine associates
allber...@gmail.com
                                   ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonad        http://sinenomine.net
  

  
  

  


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


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread Roman Cheplyaka
* Vlatko Basic vlatko.ba...@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

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


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread David Thomas
On Thu, Jul 11, 2013 at 10:50 AM, Brandon Allbery allber...@gmail.comwrote:


 ... but functions don't have an Eq instance, and *can't* have one.



Not a general one that's interesting.

There are two Eq instances that'll compile for all functions (not that it's
advisable):

instance Eq ((-) a b) where
 (==) _ _ = True

instance Eq ((-) a b) where
 (==) _ _ = False


You can't get more interesting in the general case, because you can't
inspect the arguments.

If you are okay with distinguishing solely by application you can get a
little more interesting:

instance (Bounded a, Enum a, Eq b) = Eq ((-) a b) where
f == g = all (\ x - f x == g x) [minBound .. maxBound]

*Main () == ()
True
*Main () == (||)
False


Though I'm still not sure I'd say it's a *good idea*...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread Brandon Allbery
On Thu, Jul 11, 2013 at 2:11 PM, Vlatko Basic vlatko.ba...@gmail.comwrote:

 The problem here isn't quite what you think it is; (==) is not a
 constructor, therefore it is a *variable*. It's exactly the same problem as

  a = 5
 -- ...
 foo a = 3 -- this does NOT compare with the previous value of a;
 it's identical to the next line!
 foo x = x

Hm, I thought it is a pattern match with constant, as in f ('a':xs) ==


I wonder what you'd make of this definition, then?

(*) `on` f = \x y - f x * f y

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread Vlatko Basic

  
  



 Original Message 
  Subject: Re: [Haskell-cafe] Comparing functions
  From: Brandon Allbery allber...@gmail.com
  To: Vlatko Bašić vlatko.ba...@gmail.com
  Cc: Haskell-Cafe haskell-cafe@haskell.org
  Date: 11.07.2013 20:45



  
  On Thu, Jul 11, 2013 at 2:11 PM, Vlatko Basic vlatko.ba...@gmail.com
wrote:

  

  

  

  The problem here isn't quite what you think
it is; (==) is not a constructor, therefore it
is a *variable*. It's exactly the same problem
as
  


  

  
  
      a = 5
      -- ...
      foo a = 3 -- this does NOT compare
with the previous value of "a"; it's
identical to the next line!
      foo x = x
  
  

  



Hm, I thought it is a pattern match with constant, as in
f ('a':xs) == 
  



I wonder what you'd make of this definition,
  then?


    (*)
  `on` f =
  \x y - f x * f y
 
  

  
  
According to the enlightenment above, I'd say (*) is a variable that
holds some function/operator that is applied on (f x) and (f y), 
not the multiplication, right?


  

  
-- 

  
  
brandon s allbery kf8nh                              
  sine nomine associates
allber...@gmail.com
                                   ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonad        http://sinenomine.net
  

  
  

  


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


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread Brandon Allbery
On Thu, Jul 11, 2013 at 2:58 PM, Vlatko Basic vlatko.ba...@gmail.comwrote:

 Hm, I thought it is a pattern match with constant, as in f ('a':xs) ==


  I wonder what you'd make of this definition, then?

  (*) `on` f = \x y - f x * f y


 According to the enlightenment above, I'd say (*) is a variable that holds
 some function/operator that is applied on (f x) and (f y),  not the
 multiplication, right?


Correct. But if it's a variable there, why would you expect it to be a
constant in a different pattern?

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Comparing functions

2013-07-11 Thread Vlatko Basic

  
  



 Original Message 
  Subject: Re: [Haskell-cafe] Comparing functions
  From: Brandon Allbery allber...@gmail.com
  To: Vlatko Bašić vlatko.ba...@gmail.com
  Cc: Haskell-Cafe haskell-cafe@haskell.org
  Date: 11.07.2013 21:03



  
  On Thu, Jul 11, 2013 at 2:58 PM, Vlatko Basic vlatko.ba...@gmail.com
wrote:

  

  

  

  

  

  Hm, I thought it is a pattern match with
  constant, as in f ('a':xs) == 

  
  
  
  I wonder what you'd make of this
definition, then?
  
  
      (*) `on` f = \x y - f x * f y
   

  

  
  
According to the enlightenment above, I'd say (*) is a
variable that holds some function/operator that is
applied on (f x) and (f y),  not the multiplication,
right?



Correct. But if it's a variable there, why
  would you expect it to be a constant in a different
  pattern?
  
  
  

  
  
Well, it is confusing that an operator can be a variable. I must get
a habit to understand the meaning by the site, not by the looks.

Thanks for your answers.


  
-- 
  
brandon s allbery kf8nh                              
  sine nomine associates
allber...@gmail.com
                                   ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonad        http://sinenomine.net
  

  
  

  


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