Full strict functor by abusing Haskell exceptions

I started experiment with strict functors. I come to:
import Control.Exception import Foreign import Prelude hiding (catch)
data StrictMonad a = StrictMonad a deriving Show
instance Functor StrictMonad where f `fmap` StrictMonad v = return $ f v
instance Applicative StrictMonad where pure = return (<*>) = ap
instance Monad StrictMonad where return x = unsafePerformIO $ do (return $! x) `catch` \(SomeException _) -> return x return $! StrictMonad x StrictMonad v >>= f = f v
It seems to be valid IMHO Functor and Monad (I haven't prove it) as long as functions terminates. Some time ago there was post stating that there is not possible strict 'interesting' functor - I guess that the above is 'interesting' (and due to halting problem I guess it is not possible to create strict Functor which would deal with that problem). Regards

On Sep 13, 6:25 pm, Maciej Piechotka
I started experiment with strict functors. I come to:
import Control.Exception import Foreign import Prelude hiding (catch)
data StrictMonad a = StrictMonad a deriving Show
instance Functor StrictMonad where f `fmap` StrictMonad v = return $ f v
instance Applicative StrictMonad where pure = return (<*>) = ap
instance Monad StrictMonad where return x = unsafePerformIO $ do (return $! x) `catch` \(SomeException _) -> return x return $! StrictMonad x StrictMonad v >>= f = f v
It seems to be valid IMHO Functor and Monad (I haven't prove it) as long as functions terminates.
Here, I just believe you, and assume you mean that some non- terminating function would give problems to your strict functor, i.e. it wouldn't satisfy the functor/monad laws. Then, I also wonder if the functor you have is any different from an identity functor - I see why the monad could be strict.
Some time ago there was post stating that there is not possible strict 'interesting' functor - I guess that the above is 'interesting' (and due to halting problem I guess it is not possible to create strict Functor which would deal with that problem).
I'm no expert, but since a functor on the Hask category must work on all functions available there, it looks like you "proved" that yours is not a functor and can't be fixed; maybe, that means that no strict functor exist. Your function is probably valid in a different category, containing mostly the same objects but just total functions - if it is a valid category; I wonder what would happen when arrows in this category were applied on undefined, but maybe this means that objects in this category should not contain undefined as an element; at that point, you are in a strongly normalizing programming language and probably "strict" makes no sense. Then, I would also like to understand what exactly a strict functor is, in detail, and/or a link to the post you reference. Best regards Paolo

On 9/13/10 6:23 PM, Paolo G. Giarrusso wrote:
Then, I would also like to understand what exactly a strict functor is, in detail, and/or a link to the post you reference.
I'm assuming the OP was referring to a functor for strictness I mentioned recently in the discussion about pointed functors. That is, newtype Strict a = Strict a instance Functor Strict where -- This isn't a lawful endofunctor fmap f (Strict a) = Strict (f $! a) instance Pointed Strict where -- This isn't lawful either, as an endofunctor point = Strict The idea being that we make all applications strict. However, that definition of fmap isn't lawful because we don't have that fmap(f . g) = (fmap f).(fmap g) for all f and g. In particular, it fails when (f . g) is bottom eating, i.e. when (g x == _|_) =/=> (f (g x) == _|_). We can, however, define strict composition: (f .! g) x = f $! g x And we do have that fmap(f .! g) = (fmap f).(fmap g) for Strict. So, Strict is a (category theoretic) functor, it's just not an endofunctor on Hask. 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. I haven't looked through the suggested code to see if it can actually work around the problem. -- Live well, ~wren

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

On Thu, Sep 16, 2010 at 2:12 PM, Ben Franksen
Sjoerd Visscher wrote:
But StrictIncl can't be a pointed functor, only endofunctors can be pointed.
Could someone tell me what exactly a pointed functor is? I googled but did not find a definition.
Here you will find what a Pointed Functor would be => http://haskell.org/sitewiki/images/8/85/TMR-Issue13.pdf Look up for the Typeclassopedia, start reading functor, next thing you will find is the Pointed typeclass
Thanks Ben
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Román González wrote:
On Thu, Sep 16, 2010 at 2:12 PM, Ben Franksen
wrote: Sjoerd Visscher wrote:
But StrictIncl can't be a pointed functor, only endofunctors can be pointed.
Could someone tell me what exactly a pointed functor is? I googled but did not find a definition.
Here you will find what a Pointed Functor would be => http://haskell.org/sitewiki/images/8/85/TMR-Issue13.pdf
Look up for the Typeclassopedia, start reading functor, next thing you will find is the Pointed typeclass
Thanks for the link. What I actually wanted was a mathematical definition, though. From the TMR article I gather that a pointed functor could be defined as an endo-functor F: C -> C together with a natural transformation pure: Id -> F where Id: C -> C is the identity functor. No additional laws (beside naturality of pure) are imposed. Right so far? Why is this an interesting structure? Cheers Ben

On 9/17/10 4:39 PM, Ben Franksen wrote:
Thanks for the link. What I actually wanted was a mathematical definition, though. From the TMR article I gather that a pointed functor could be defined as an endo-functor
F: C -> C
together with a natural transformation
pure: Id -> F
where Id: C -> C is the identity functor.
No additional laws (beside naturality of pure) are imposed.
Right so far?
Why is this an interesting structure?
A functor F gives us a category containing an image of the domain. That is, it gives us a collection of image objects and arrows between those image objects. However, for F an endofunctor, we have no way to get from the domain object to the image object; i.e., even though we can correlate the types, we have no way to correlate the values of those types. The natural transformation says that hom_C(X,FX) is inhabited, and moreover that it has a natural inhabitant. In other words, it incorporates the action of F into the category. Instead of leaving the category and then coming back again (along F), we can perform the mapping from X to FX within the category itself. That is, it gives us image values, gives us a way to get from the domain subcategory to the image subcategory while remaining within the category. F : types -> types fmap@F : morphisms -> morphisms pure@F : values -> values Embedding the action of an endofunctor into the category it operates on strikes me as a very interesting structure. We encounter these all the time in programming because we want to implement the operations of the language within the language being defined. -- Live well, ~wren

On Sep 17, 2010, at 10:39 PM, Ben Franksen wrote:
What I actually wanted was a mathematical definition, though.
Here's a definition of pointed objects: http://ncatlab.org/nlab/show/pointed+object -- Sjoerd Visscher sjoerd@w3future.com

On 9/18/10 8:00 AM, Sjoerd Visscher wrote:
On Sep 17, 2010, at 10:39 PM, Ben Franksen wrote:
What I actually wanted was a mathematical definition, though.
Here's a definition of pointed objects: http://ncatlab.org/nlab/show/pointed+object
pointed objects, pointed sets/groups/topospaces, pointed categories, pointed functors, etc aren't all the same though. The Joy of Cats[1] has info on all of them except pointed functors. [1] http://katmat.math.uni-bremen.de/acc/acc.pdf -- Live well, ~wren

On Saturday 18 September 2010 6:03:39 pm wren ng thornton wrote:
pointed objects, pointed sets/groups/topospaces, pointed categories, pointed functors, etc aren't all the same though.
The definition of pointed objects could be massaged to yield pointed functors, though. Instead of a category with a terminal object, we could relax the definition to include categories with a distinguished object I. Then, a pointed object in such a category is an object X together with x : I -> X. This isn't always very interesting. For any category with an initial object 0, the category of objects pointed over 0 is isomorphic to the original category, for instance. However, categories with arbitrary distinguished objects could be viewed as a precursor to monoidal categories, and pointed objects are then precursors to monoid objects. And then when you instantiate all that to the category of endofunctors over some category, you get pointed functors being precursors to monads. -- Dan

On 13/09/10 17:25, Maciej Piechotka wrote:
import Control.Exception import Foreign import Prelude hiding (catch)
data StrictMonad a = StrictMonad a deriving Show
instance Monad StrictMonad where return x = unsafePerformIO $ do (return $! x) `catch` \(SomeException _) -> return x return $! StrictMonad x StrictMonad v>>= f = f v
It seems to be valid IMHO Functor and Monad (I haven't prove it) as long as functions terminates.
I'm not sure if I'm allowed to use unsafePerformIO in my counter-example, but you used it so why not ;-) The first monad law says: "return a >>= k = k a" let k = const (StrictMonad ()) a = unsafePerformIO launchMissiles In "k a" no missiles will be launched, in "return a >>= k", they will be launched. You can construct a similar example against "m >>= return = m". Although, if you changed your definition of bind to: StrictMonad v >>= f = return v >>= f >>= return Then as long as "return x >>= return = return x" (which it does for you) then you automatically satisfy the first two monad laws! Which is an interesting way of solving the problem -- haven't checked the third law though. Thanks, Neil.

On Tue, 2010-09-14 at 11:27 +0100, Neil Brown wrote:
On 13/09/10 17:25, Maciej Piechotka wrote:
import Control.Exception import Foreign import Prelude hiding (catch)
data StrictMonad a = StrictMonad a deriving Show
instance Monad StrictMonad where return x = unsafePerformIO $ do (return $! x) `catch` \(SomeException _) -> return x return $! StrictMonad x StrictMonad v>>= f = f v
It seems to be valid IMHO Functor and Monad (I haven't prove it) as long as functions terminates.
I'm not sure if I'm allowed to use unsafePerformIO in my counter-example, but you used it so why not ;-) The first monad law says: "return a >>= k = k a"
let k = const (StrictMonad ()) a = unsafePerformIO launchMissiles
In "k a" no missiles will be launched, in "return a >>= k", they will be launched.
I guess we enter a grey area - I did use unsafePerformIO but without side-effects.
You can construct a similar example against "m >>= return = m".
Assuming StrictMonad (constructor) is hidden - I don't think so.
Although, if you changed your definition of bind to:
StrictMonad v >>= f = return v >>= f >>= return
Then as long as "return x >>= return = return x" (which it does for you) then you automatically satisfy the first two monad laws! Which is an interesting way of solving the problem -- haven't checked the third law though.
My error.
Thanks,
Neil.
Regards
participants (8)
-
Ben Franksen
-
Dan Doel
-
Maciej Piechotka
-
Neil Brown
-
Paolo G. Giarrusso
-
Román González
-
Sjoerd Visscher
-
wren ng thornton