
Inversion seems like the right name. That's typically what people call it when f . g = g . f = id So in the case of x + (x - x) = x we can think of it as (f . g) x where f y = x + y and g y = y - x, and all we're saying is that f . g = g . f = id i.e. f and g are inverse. Alex On 2014-06-04, at 10:46 AM, Omari Norman wrote:
Is there a more general name for it? Here's what I'm thinking of. I would think there's a name for it rather than "inversion", which I made up.
module Builders where
import Test.QuickCheck
-- | Takes a single value, x. Applies a function to that value, -- and then applies a second function to the result of the -- application of the first function. Passes if the result of the -- second function equals the original value.
inversion :: (Eq a, Show a) => (a -> b) -- ^ Apply this function to the original value -> (b -> a) -- ^ Apply this function to the result of the first function -> a -> Property inversion f1 f2 a = f2 (f1 a) === a
On Wed, Jun 4, 2014 at 10:42 AM, David Thomas
wrote: If you have associativity, this seems roughly the same as saying there is an additive inverse for every x, because x + x - x = x => x + (x - x) = x => x + 0 = x. On Wed, Jun 4, 2014 at 7:34 AM, Omari Norman
wrote: It's not quite idempotence, because more than one function is involved.
It's a common property and I figure I can write a higher order function to build QuickCheck tests for it. I was just wondering if it has a name.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe