kindly-functors: A category polymorphic `Functor` typeclass

[ categories, control, library, mit ] [ Propose Tags ]

A category polymorphic Functor typeclass.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0, 0.1.0.1
Change log CHANGELOG.md
Dependencies base (>4 && <5), mtl (>=2.2.2 && <2.4), profunctors (>=5.6.2 && <5.7), semigroupoids (>=6.0.0 && <6.1), these (>=1.2 && <1.3), witherable (>=0.4.2 && <0.5) [details]
License MIT
Author Solomon Bothwell
Maintainer ssbothwell@gmail.com
Category Control, Categories
Home page https://www.github.com/solomon-b/kindly-functors
Uploaded by solomon at 2024-02-05T05:53:20Z
Distributions NixOS:0.1.0.1
Downloads 44 total (6 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2024-02-05 [all 1 reports]

Readme for kindly-functors-0.1.0.1

[back to package description]

Kindly Functors

🚨 WORK IN PROGRESS 🚨

kindly-functors::CI kindly-functors::CI

A category polymorphic Functor typeclass based on the work of IcelandJack and Ed Kmett allowing you to pick out arbitrary kinds and variances for your functors.

This library offers direct access to the FunctorOf and Functor classes defined in the above work but also a slightly more familiar API for one, two, and three parameter functors.

type Functor f = FunctorOf (->) (->)
type Contravariant f = FunctorOf Op (->)
type Invariant f = FunctorOf (<->) (->)
type Filterable f = FunctorOf (Star Maybe) (->)
type Bifunctor p = FunctorOf (->) (Nat (->) (->))
type Profunctor p = FunctorOf Op (Nat (->) (->))
type Trifunctor p = FunctorOf cat1 (Nat cat2 (Nat cat3 cat4))

fmap, bimap, lmap, and rmap have been made polymorphic over variances:

> fmap show (Identity True)
Identity "True"

> getPredicate (fmap (Op read) (Predicate not)) "True"
False

> lmap show (True, False)
("True",False)

> lmap (Op read) not "True"
False

> rmap show (True, False)
(True,"False")

> bimap show read (Left True)
Left "True"

> bimap (read @Int) show ("1", True)
(1,"True")

> bimap (Op (read @Int)) show (+1) "0"
"1"

> trimap show show show (True, False, ())
("True","False","()")

How does this work?

The above functions are all just instantions of map1, map2, and map3:

> map1 show (True, False, ())
(True,False,"()")

> map1 show (Left True)
Left True

> map2 show (True, False, ())
(True,"False",())

> map3 show (True, False, ())
("True",False,())

Becareful when using these directly as GHC might pick out a surprising instance:

> map2 show (Left True)
Left "True"

These functions themselves are a frontend for map from the (kindly) Functor class:

type Functor :: (from -> to) -> Constraint
class (Category (Dom f), Category (Cod f)) => Functor (f :: from -> to) where
  type Dom f :: from -> from -> Type
  type Cod f :: to -> to -> Type

  map :: Dom f a b -> Cod f (f a) (f b)

-- NOTE: These these classes are labeled from right to left:
k
class (FunctorOf cat (->) p) => MapArg1 cat p | p -> cat where
  map1 :: (a `cat` b) -> p a -> p b
  map1 = map

class (FunctorOf cat1 (cat2 ~> (->)) p) => MapArg2 cat1 cat2 p | p -> cat2 cat2 where
  map2 :: (a `cat1` b) -> forall x. p a x -> p b x
  map2 = runNat . map

class (FunctorOf cat1 (cat2 ~> cat3 ~> (->)) p) => MapArg3 cat1 cat2 cat3 p | p -> cat1 cat2 cat3 where
  map3 :: (a `cat1` b) -> forall x y. p a x y -> p b x y
  map3 f = runNat (runNat (map f))