[Haskell-cafe] Monads vs. qualified types

William Lee Irwin III wli at holomorphy.com
Wed Dec 15 04:00:27 EST 2004


To my chagrin, I discovered that the following code was not accepted
while attempting to monadify a small interpreter for a language used
for calculations in permutation representations of groups. One of the
critical notions here is of closure under composition, e.g. a
transcript of a command to generate a set via distinguished elements is:

20> <(1 2),(1 2 3)>
{(), (1 2), (1 2 3), (1 3), (1 3 2), (2 3)}

and augmenting the semantics with group-theoretic joins and
intersections and the like look verbose and redundant, with monadic
properties to exploit for brevity readily apparent.

\begin{code}
data Eq t => Set t = Set [t] deriving (Ord, Read, Show)
instance Eq t => Eq (Set t) where
	(Set xs) == (Set ys) = all (`elem` ys) xs && all (`elem` xs) ys
instance Functor Set where
	fmap f (Set xs) = Set . nub $ map f xs
instance Monad Set where
	return = Set . (:[])
	(Set xs) >>= f = Set $ foldr union [] [ys | Set ys <- map f xs]
\end{code}

This, of course, presents me immediately with some nightmare where
transitive closure semantics and the like are unimplementable as direct
data structure properties within any monad, as constraints on the argument
types of the monadic constructor are (for the moment) verboten.

Is anyone looking into dealing with this so that I can do this? If not,
where (which files) do I hack it into ghc? Are there already patches?


-- wli


More information about the Haskell-Cafe mailing list