
On Sep 16, 2010, at 6:45 AM, wren ng thornton wrote:
Given that any functor for adding strictness will have to deal with the same issue of preserving bottom-eating compositions, I postulated that there exists no functor from (all of) Hask to !Hask. But, since !Hask is a subcategory of Hask, it's trivial to go the other direction. In fact, the Strict defined above can be considered as the inclusion functor from !Hask to Hask by making the strictness of !Hask explicit. This also allows Strict to be considered a pointed functor since fmap f . point = point . f for strict functions f.
For fun here's this idea implemented with data-category:
{-# LANGUAGE TypeFamilies #-}
import Prelude hiding ((.), id, Functor) import Data.Category import Data.Category.Functor
The definition of the subcategory of Hask with only strict functions:
newtype StrictHask a b = StrictHask { unStrictHask :: a -> b }
instance Category StrictHask where id _ = StrictHask $ \x -> x `seq` x StrictHask f . StrictHask g = StrictHask $ \x -> f $! g x
The definition of the inclusion functor: ((%) maps morphisms, i.e. fmap, (:%) maps objects)
data StrictIncl = StrictIncl
type instance Dom StrictIncl = StrictHask type instance Cod StrictIncl = (->)
type instance StrictIncl :% a = a
instance Functor StrictIncl where StrictIncl % (StrictHask f) = f
And indeed we have StrictIncl % (f . g) = StrictIncl % f . StrictIncl % g But StrictIncl can't be a pointed functor, only endofunctors can be pointed. -- Sjoerd Visscher http://w3future.com