<html><head></head><body style="word-wrap: break-word; -webkit-nbsp-mode: space; -webkit-line-break: after-white-space; ">Inversion seems like the right name. That's typically what people call it when f . g = g . f = id<div><br></div><div>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.</div><div><br></div><div>Alex</div><div><br><div><div><div>On 2014-06-04, at 10:46 AM, Omari Norman wrote:</div><br class="Apple-interchange-newline"><blockquote type="cite"><div dir="ltr">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.<div><br></div><div><div>module Builders where</div>
<div><br></div><div>import Test.QuickCheck</div><div><br></div><div>-- | Takes a single value, x.  Applies a function to that value,</div><div>-- and then applies a second function to the result of the</div><div>-- application of the first function.  Passes if the result of the</div>
<div>-- second function equals the original value.</div><div><br></div><div>inversion</div><div>  :: (Eq a, Show a)</div><div>  => (a -> b)</div><div>  -- ^ Apply this function to the original value</div><div>  -> (b -> a)</div>
<div>  -- ^ Apply this function to the result of the first function</div><div>  -> a</div><div>  -> Property</div><div>inversion f1 f2 a = f2 (f1 a) === a</div></div><div><br></div></div><div class="gmail_extra"><br>
<br><div class="gmail_quote">On Wed, Jun 4, 2014 at 10:42 AM, David Thomas <span dir="ltr"><<a href="mailto:davidleothomas@gmail.com" target="_blank">davidleothomas@gmail.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
If you have associativity, this seems roughly the same as saying there<br>
is an additive inverse for every x, because x + x - x = x => x + (x -<br>
x) = x => x + 0 = x.<br>
<div><div class="h5"><br>
On Wed, Jun 4, 2014 at 7:34 AM, Omari Norman <<a href="mailto:omari@smileystation.com">omari@smileystation.com</a>> wrote:<br>
> It's not quite idempotence, because more than one function is involved.<br>
><br>
> It's a common property and I figure I can write a higher order function to<br>
> build QuickCheck tests for it.  I was just wondering if it has a name.<br>
><br>
</div></div>> _______________________________________________<br>
> Haskell-Cafe mailing list<br>
> <a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
> <a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
><br>
</blockquote></div><br></div>
_______________________________________________<br>Haskell-Cafe mailing list<br><a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>http://www.haskell.org/mailman/listinfo/haskell-cafe<br></blockquote></div><br></div></div></body></html>