[Haskell-cafe] Dealing with invertible functions

Antonio Nikishaev me at lelf.lu
Mon Jun 29 15:04:02 UTC 2015


Look at Control.Lens.Iso




Clinton Mead <clintonmead at gmail.com> writes:

> I was trying to think of a way to deal with invertible functions, say
> if I want to set up a one-to-one mapping from A<->B without having to
> maintain two sets of functions (and worry about them getting out of
> sync).
>
> So I thought about making an "invertible" function. This is a function
> that knows it's own inverse, and you can compose them and get the
> inverses for free. Of course you need to set up the base functions
> manually, but then after that the composed functions don't have to be
> maintained separately both ways.
>
> Below I'm going to include some code, and I have a few questions:
>
> 1) Am I (badly) reinventing the wheel.
> 2) Is there otherwise something terrible with this approach.
> 3) I ended up wanting a function with signature "f a b -> a -> b".
> This feels strangly like applicative but not exactly. Am I reinventing
> the wheel here also or should I be doing this differently?
>
> Any advise appreciated, the ideone link is here:
> https://ideone.com/HlUHUd
> But I've also copied the code below:
>
> ---
>
> import Prelude hiding ((.))
> import Control.Category ((.), (<<<), (>>>), Category)
>
> data InvertibleFunction a b = InvertibleFunction (a -> b) (b -> a)
>
> instance Category InvertibleFunction where
> (InvertibleFunction b_c c_b) . (InvertibleFunction a_b b_a) =
> InvertibleFunction (b_c . a_b) (b_a . c_b)
>
> inv (InvertibleFunction x y) = InvertibleFunction y x
>
> add :: (Num n) => n -> InvertibleFunction n n
> add x = InvertibleFunction (+x) (\y -> y - x)
>
> class KindaApplicative f where
> (<$>) :: f a b -> a -> b
>
> instance KindaApplicative InvertibleFunction where
> (InvertibleFunction f _) <$> x = f x
> main = print $ ((inv (add 2)) <$> 5)
>



More information about the Haskell-Cafe mailing list