<div dir="ltr">  Hi Christopher,<div><br></div><div style>a data type can be an instance of Category only if it has kind * -&gt; * -&gt; *. It must have 2 type parameters so that you could have types like &#39;cat a a&#39;.</div>

<div style><br></div><div style>Some simple examples:</div><div style><br></div><div style><div>import Prelude hiding (id, (.))</div><div>import Control.Category</div><div>import Data.Monoid</div><div><br></div><div>-- See <a href="https://en.wikipedia.org/wiki/Opposite_category">https://en.wikipedia.org/wiki/Opposite_category</a></div>

<div>newtype Op c a b = Op (c b a)</div><div>instance Category c =&gt; Category (Op c) where</div><div>    id = Op id</div><div>    (Op x) . (Op y) = Op (y . x)</div><div><div><br></div><div>-- A category whose morphisms are bijections between types.</div>

<div>data Iso a b = Iso (a -&gt; b) (b -&gt; a)</div><div>instance Category Iso where</div><div>    id = Iso id id</div><div>    (Iso f1 g1) . (Iso f2 g2) = Iso (f1 . f2) (g2 . g1)</div></div><div><div><br></div><div>-- A product of two categories forms a new category:</div>

<div>data ProductCat c d a b = ProductCat (c a b) (d a b)</div><div>instance (Category c, Category d) =&gt; Category (ProductCat c d) where</div><div>    id = ProductCat id id</div><div>    (ProductCat f g) . (ProductCat f&#39; g&#39;) = ProductCat (f . f&#39;) (g . g&#39;)</div>

</div><div><br></div><div>-- A category constructed from a monoid. It</div><div>-- ignores the types. Any morphism in this category</div><div>-- is simply an element of the given monoid.</div><div>newtype MonoidCat m a b = MonoidCat m</div>

<div>instance (Monoid m) =&gt; Category (MonoidCat m) where</div><div>    id = MonoidCat mempty</div><div>    MonoidCat x . MonoidCat y = MonoidCat (x `mappend` y)</div><div><br></div><div style>Many interesting categories can be constructed from various monads using Kleisli. For example, Kleisli Maybe is the category of partial functions.</div>

<div style><br></div><div style>Best regards,</div><div style>Petr</div></div></div><div class="gmail_extra"><br><br><div class="gmail_quote">2012/12/20 Christopher Howard <span dir="ltr">&lt;<a href="mailto:christopher.howard@frigidcode.com" target="_blank">christopher.howard@frigidcode.com</a>&gt;</span><br>

<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">I&#39;ve perhaps been trying everyones patiences with my noobish CT<br>
questions, but if you&#39;ll bear with me a little longer: I happened to<br>
notice that there is in fact a Category class in Haskell base, in<br>
Control.Category:<br>
<br>
quote:<br>
--------<br>
class Category cat where<br>
<br>
A class for categories. id and (.) must form a monoid.<br>
<br>
Methods<br>
<br>
id :: cat a a<br>
<br>
the identity morphism<br>
<br>
(.) :: cat b c -&gt; cat a b -&gt; cat a c<br>
<br>
morphism composition<br>
--------<br>
<br>
However, the documentation lists only two instances of Category,<br>
functions (-&gt;) and Kleisli Monad. For instruction purposes, could<br>
someone show me an example or two of how to make instances of this<br>
class, perhaps for a few of the common types? My initial thoughts were<br>
something like so:<br>
<br>
code:<br>
--------<br>
instance Category Integer where<br>
<br>
  id = 1<br>
<br>
  (.) = (*)<br>
<br>
-- and<br>
<br>
instance Category [a] where<br>
<br>
  id = []<br>
  (.) = (++)<br>
-------<br>
<br>
But these lead to kind mis-matches.<br>
<span class="HOEnZb"><font color="#888888"><br>
--<br>
<a href="http://frigidcode.com" target="_blank">frigidcode.com</a><br>
<br>
</font></span><br>_______________________________________________<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>