[Git][ghc/ghc][master] 2 commits: Expand the haddocks for Control.Category

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Thu Oct 17 09:20:22 UTC 2024



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
fbbbd010 by Daan Rijks at 2024-10-17T05:19:19-04:00
Expand the haddocks for Control.Category

- - - - -
076c1a10 by Andrew Lelechenko at 2024-10-17T05:19:19-04:00
documentation: more examples for Control.Category

- - - - -


2 changed files:

- libraries/base/src/Control/Category.hs
- libraries/ghc-internal/src/GHC/Internal/Control/Category.hs


Changes:

=====================================
libraries/base/src/Control/Category.hs
=====================================
@@ -11,9 +11,26 @@
 --
 
 module Control.Category
-  ( Category(..)
+  ( -- * Class
+    Category(..)
+
+    -- * Combinators
   , (<<<)
   , (>>>)
+
+  -- $namingConflicts
   ) where
 
 import GHC.Internal.Control.Category
+
+-- $namingConflicts
+--
+-- == A note on naming conflicts
+--
+-- The methods from 'Category' conflict with 'Prelude.id' and 'Prelude..' from the
+-- prelude; you will likely want to either import this module qualified, or hide the
+-- prelude functions:
+--
+-- @
+-- import "Prelude" hiding (id, (.))
+-- @


=====================================
libraries/ghc-internal/src/GHC/Internal/Control/Category.hs
=====================================
@@ -28,17 +28,81 @@ import GHC.Internal.Data.Coerce (coerce)
 infixr 9 .
 infixr 1 >>>, <<<
 
--- | A class for categories. Instances should satisfy the laws
+-- | A class for categories.
 --
--- [Right identity] @f '.' 'id'  =  f@
--- [Left identity]  @'id' '.' f  =  f@
--- [Associativity]  @f '.' (g '.' h)  =  (f '.' g) '.' h@
+-- In mathematics, a /category/ is defined as a collection of /objects/ and a collection
+-- of /morphisms/ between objects, together with an /identity morphism/ 'id' for every
+-- object and an operation '(.)' that /composes/ compatible morphisms.
+--
+-- This class is defined in an analogous way. The collection of morphisms is represented
+-- by a type parameter @cat@, which has kind @k -> k -> 'Data.Kind.Type'@ for some kind variable @k@
+-- that represents the collection of objects; most of the time the choice of @k@ will be
+-- 'Data.Kind.Type'.
+--
+-- ==== __Examples__
+--
+-- As the method names suggest, there's a category of functions:
+--
+-- @
+-- instance Category '(->)' where
+--   id = \\x -> x
+--   f . g = \\x -> f (g x)
+-- @
+--
+-- Isomorphisms form a category as well:
+--
+-- @
+-- data Iso a b = Iso (a -> b) (b -> a)
+--
+-- instance Category Iso where
+--   id = Iso id id
+--   Iso f1 g1 . Iso f2 g2 = Iso (f1 . f2) (g2 . g1)
+-- @
+--
+-- Natural transformations are another important example:
+--
+-- @
+-- newtype f ~> g = NatTransform (forall x. f x -> g x)
+--
+-- instance Category (~>) where
+--   id = NatTransform id
+--   NatTransform f . NatTransform g = NatTransform (f . g)
+-- @
+--
+-- Using the `TypeData` language extension, we can also make a category where `k` isn't
+-- `Type`, but a custom kind `Door` instead:
+--
+-- @
+-- type data Door = DoorOpen | DoorClosed
+--
+-- data Action (before :: Door) (after :: Door) where
+--   DoNothing :: Action door door
+--   OpenDoor :: Action start DoorClosed -> Action start DoorOpen
+--   CloseDoor :: Action start DoorOpen -> Action start DoorClosed
+--
+-- instance Category Action where
+--   id = DoNothing
+--
+--   DoNothing . action = action
+--   OpenDoor rest . action = OpenDoor (rest . action)
+--   CloseDoor rest . action = CloseDoor (rest . action)
+-- @
 --
 class Category cat where
-    -- | the identity morphism
+    -- | The identity morphism. Implementations should satisfy two laws:
+    --
+    -- [Right identity] @f '.' 'id'  =  f@
+    -- [Left identity]  @'id' '.' f  =  f@
+    --
+    -- These essentially state that 'id' should "do nothing".
     id :: cat a a
 
-    -- | morphism composition
+    -- | Morphism composition. Implementations should satisfy the law:
+    --
+    -- [Associativity]  @f '.' (g '.' h)  =  (f '.' g) '.' h@
+    --
+    -- This means that the way morphisms are grouped is irrelevant, so it is unambiguous
+    -- to write a composition of morphisms as @f '.' g '.' h@, without parentheses.
     (.) :: cat b c -> cat a b -> cat a c
 
 {-# RULES
@@ -70,11 +134,13 @@ instance Category Coercion where
   id = Coercion
   (.) Coercion = coerce
 
--- | Right-to-left composition
+-- | Right-to-left composition. This is a synonym for '(.)', but it can be useful to make
+-- the order of composition more apparent.
 (<<<) :: Category cat => cat b c -> cat a b -> cat a c
 (<<<) = (.)
 
--- | Left-to-right composition
+-- | Left-to-right composition. This is useful if you want to write a morphism as a
+-- pipeline going from left to right.
 (>>>) :: Category cat => cat a b -> cat b c -> cat a c
 f >>> g = g . f
 {-# INLINE (>>>) #-} -- see Note [INLINE on >>>]



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5f67db48bdef51905132d990cfaaa0df6532ea99...076c1a104f55750a49de03694786180bd78eb9b6

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5f67db48bdef51905132d990cfaaa0df6532ea99...076c1a104f55750a49de03694786180bd78eb9b6
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20241017/189b4aa1/attachment-0001.html>


More information about the ghc-commits mailing list