Generalising ($) like Control.Category generalises (.)
Asked Answered
T

2

8

I had a thought to generalise ($) like Control.Category generalises (.), and I've done so with the code at the end of this post (also ideone).

In this code I've created a class called FunctionObject. This class has a function ($) with the following signature:

($) :: f a b -> a -> b

Naturally I make (->) an instance of this class so $ continues to work with ordinary functions.

But this allows you to make special functions that, for example, know their own inverse, as the example below shows.

I've concluded there's one of three possibilities:

  1. I'm the first to think of it.
  2. Someone else has already done it and I'm reinventing the wheel.
  3. It's a bad idea.

Option 1 seems unlikely, and my searches on hayoo didn't reveal option 2, so I suspect option 3 is most likely, but if someone could explain why that is it would be good.

import Prelude hiding ((.), ($))
import Control.Category ((.), Category)

class FunctionObject f where
  ($) :: f a b -> a -> b

infixr 0 $

instance FunctionObject (->) where
  f $ x = f x

data InvertibleFunction a b = 
   InvertibleFunction (a -> b) (b -> a)

instance Category InvertibleFunction where
  (InvertibleFunction f f') . (InvertibleFunction g g') =
    InvertibleFunction (f . g) (g' . f')

instance FunctionObject InvertibleFunction where
  (InvertibleFunction f _) $ x = f $ x

inverse (InvertibleFunction f f') = InvertibleFunction f' f

add :: (Num n) => n -> InvertibleFunction n n
add n = InvertibleFunction (+n) (subtract n)

main = do
  print $ add 2 $ 5 -- 7
  print $ inverse (add 2) $ 5 -- 3
Tabethatabib answered 29/6, 2015 at 14:57 Comment(4)
Check the ArrowApply typeclass at downloads.haskell.org/~ghc/latest/docs/html/libraries/base/…Litho
@AJFarmar ArrowApply is equivalent to MonadChantal
You may also like to look into cartesian closed categories, which are those categories that have an "application" operation (and a few other supporting constructs).Scopula
A similar question (with the same usage example: invertible functions) has been discussed at Why isn't there a typeclass for functions?.Spineless
C
6

There are two abstractions used for things like this in Haskell, one usings Arrows and the other Applicatives. Both can be broken down into smaller parts than those used in base.


If you go in the Arrow direction and break down the capabilities of Arrows into component pieces, you'd have a separate class for those arrows that are able to lift arbitrary functions into the arrow.

class ArrowArr a where
    arr :: (b -> c) -> a b c

This would be the opposite of ArrowArr, arrows where any arbitrary arrow can be dropped to a function.

class ArrowFun a where
    ($) :: a b c -> (b -> c)

If you just split arr off of Arrow you are left with arrow like categories that can construct and deconstruct tuples.

class Category a => ArrowLike a where
    fst   :: a (b, d) b
    snd   :: a (d, b) b
    (&&&) :: a b c -> a b c' -> a b (c,c')

If you go in the Applicative direction this is a Copointed "Applicative without pure" (which goes by the name Apply).

class Copointed p where Source
    copoint :: p a -> a

class Functor f => Apply f where
  (<.>) :: f (a -> b) -> f a -> f b

When you go this way you typically drop the Category for functions and instead have a type constructor C a representing values (including function values) constructed according to a certain set of rules.

Chantal answered 29/6, 2015 at 15:31 Comment(0)
C
12

$ applies morphisms to values. The concept of a value seems trivial, but actually, general categories need to have no such notion. Morphisms are values (arrow-values... whatever), but objects (types) needn't actually contain any elements.

However, in many categories, there is a special object, the terminal object. In Hask, this is the () type. You'll notice that functions () -> a are basically equivalent to a values themselves. Categories in which this works are called well-pointed. So really, the fundamental thing you need for something like $ to make sense is

class Category c => WellPointed c where
  type Terminal c :: *
  point :: a -> Terminal c `c` a
  unpoint :: Terminal c `c` a -> a

Then you can define the application operator by

($) :: WellPointed c => c a b -> a -> b
f $ p = unpoint $ f . point p

The obvious instance for WellPointed is of course Hask itself:

instance WellPointed (->) where
  type Terminal c = ()
--point :: a -> () -> a
  point a () = a
--unpoint :: (() -> a) -> a
  unpoint f = f ()

The other well-known category, Kleisli, is not an instance of WellPointed as I wrote it (it allows point, but not unpoint). But there are plenty of categories which would make for a good WellPointed instance, if they could properly be implemented in Haskell at all. Basically, all the categories of mathematical functions with particular properties (LinK, Grp, {{•}, Top}...). The reason these aren't directly expressible as a Category is that they can't have any Haskell type as an object; newer category libraries like categories or constrained-categories do allow this. For instance, I have implemented this:

instance (MetricScalar s) => WellPointed (Differentiable s) where
  unit = Tagged Origin
  globalElement x = Differentiable $ \Origin -> (x, zeroV, const zeroV)
  const x = Differentiable $ \_ -> (x, zeroV, const zeroV)

As you see, the class interface is actually a bit different from what I wrote above. There isn't one universally accepted way of implementing such stuff in Haskell yet... in constrained-categories, the $ operator actually works more like what Cirdec described.

Catlaina answered 29/6, 2015 at 16:6 Comment(6)
I'm a bit confused. Can you add an instance for 'WellPointed'?Tabethatabib
May I recommend using "final" instead of "terminal"? The meaning of the latter depends on who's writing it.Kaon
What are the fors and againsts of making WellPointed Category's direct subclass? Why wasn't it chosen for Control.Arrow.Constrained? Related.Reportorial
@ZhiltsoffIgor you mean why is it currently PreArrow a => WellPointed a instead of Category a => WellPointed a? Well, I kind of started from the view to cartesian closed categories and ravelled it up. But you're right, mathematically it would actually be nicer to put WellPointed higher in the hierarchy, separate from the Cartesian branch, and have a dedicated class (PreArrow a, WellPointed a, UnitObject a ~ Terminal a) => CartesianClosed a, though I may be overlooking some practical issue right now. — If you would like that changed, feel free to file a pull request.Catlaina
@Catlaina truth be told, I feel a bit lost. Haven't we got Control.Category.Constrained.Curry for cartesian closed categories (at least locally small ones)? I guess cartesian closed categories could be written down in Haskell different ways, yet Curry always felt very neat. Or am I missing the point of some the classes?Reportorial
Ah yes, Curry. It is rather me that's lost, not you! I think that's the reason why I made no class actually named CartesianClosed: I couldn't decide where to put it in the hierarchy. — Goes to show the problems you get when kind of balancing between keeping it close to the base.Arrow hierarchy and making it proper mathematically category theory.Catlaina
C
6

There are two abstractions used for things like this in Haskell, one usings Arrows and the other Applicatives. Both can be broken down into smaller parts than those used in base.


If you go in the Arrow direction and break down the capabilities of Arrows into component pieces, you'd have a separate class for those arrows that are able to lift arbitrary functions into the arrow.

class ArrowArr a where
    arr :: (b -> c) -> a b c

This would be the opposite of ArrowArr, arrows where any arbitrary arrow can be dropped to a function.

class ArrowFun a where
    ($) :: a b c -> (b -> c)

If you just split arr off of Arrow you are left with arrow like categories that can construct and deconstruct tuples.

class Category a => ArrowLike a where
    fst   :: a (b, d) b
    snd   :: a (d, b) b
    (&&&) :: a b c -> a b c' -> a b (c,c')

If you go in the Applicative direction this is a Copointed "Applicative without pure" (which goes by the name Apply).

class Copointed p where Source
    copoint :: p a -> a

class Functor f => Apply f where
  (<.>) :: f (a -> b) -> f a -> f b

When you go this way you typically drop the Category for functions and instead have a type constructor C a representing values (including function values) constructed according to a certain set of rules.

Chantal answered 29/6, 2015 at 15:31 Comment(0)

© 2022 - 2024 — McMap. All rights reserved.