I'm having trouble embedding unconstrained monads into the NewMonad:

> {-# LANGUAGE ...,UndecidableInstances #-}
>
> instance Monad m => Suitable m v where
>     data Constraints m v = NoConstraints
>     constraints _        = NoConstraints
>
> instance Monad m => NewMonad m where
>     newReturn   = return
>     newBind x k =
>       let   list2Constraints = constraints result
>             result = case list2Constraints of
>                            NoConstraints -> (x >>= k)
>          in result

SetMonad.hs:25:9:
    Conflicting family instance declarations:
      data instance Constraints Set val -- Defined at SetMonad.hs:25:9-19
      data instance Constraints m v -- Defined at SetMonad.hs:47:9-19

Since Set is not an instance of Monad, there is no actual overlap between (Monad m => m) and Set, but it seems that Haskell has no way of knowing that.

Is there some trick (e.g. newtype boxing/unboxing) to get all the unconstrained monads automatically instanced? Then the do notation could be presumably remapped to the new class structure.

Dan

Wolfgang Jeltsch wrote:
Am Montag, 24. März 2008 20:47 schrieb Henning Thielemann:
[…]

Here is another approach that looks tempting, but unfortunately does not
work, and I wonder whether this can be made working.

module RestrictedMonad where

import Data.Set(Set)
import qualified Data.Set as Set

class AssociatedMonad m a where

class RestrictedMonad m where
    return :: AssociatedMonad m a => a -> m a
(>>=) :: (AssociatedMonad m a, AssociatedMonad m b) => m a -> (a -> m b) -> m b

instance (Ord a) => AssociatedMonad Set a where

instance RestrictedMonad Set where
    return = Set.singleton
    x >>= f = Set.unions (map f (Set.toList x))

[…]

The problem is that while an expression of type

    (AssociatedMonad Set a, AssociatedMonad Set b) =>
    Set a -> (a -> Set b) -> Set b

has type

    (Ord a, Ord b) => Set a -> (a -> Set b) -> Set b,

the opposite doesn’t hold.

Your AssociatedMonad class doesn’t provide you any Ord dictionary which you need in order to use the Set functions. The instance declaration

    instance (Ord a) => AssociatedMonad Set a

says how to construct an AssociatedMonad dictionary from an Ord dictionary but not the other way round.

But it is possible to give a construction of an Ord dictionary from an AssociatedMonad dictionary. See the attached code. It works like a charm. :-)
Best wishes,
Wolfgang


------------------------------------------------------------------------

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to