
I am just starting to learn MonadComprehensions and I'm following its type rules to their logical conclusion. So I can have [ x | x <- "abc", then group by EXPR using PNT ] where EXPR is an expression of my choosing, PNT is a function of type forall a. (a -> E) -> [a] -> M (F a) where E is the type of EXPR, M is a Monad instance of my choosing, and F is a Functor instance of my choosing. (And even the [a] can be replaced by N a, as long as "abc" has type N Char.) (My freedom over M and F isn't quite documented in the GHC user's guide, but there is very little you can't discover by putting a few typed holes here and there >:) ) So I choose EXPR = ord x, E = Int, M = IO, F = IntMap, so I can have: {-# LANGUAGE MonadComprehensions, TransformListComp #-} module F where import Data.Char (chr, ord) import qualified Data.IntMap.Strict as IntMap foo :: IO (IntMap.IntMap Char) foo = [ x | x <- "a\r\n", then group by ord x using whee ] whee :: (a -> Int) -> [a] -> IO (IntMap.IntMap a) whee f xs = do print (map (chr . f) xs) return (IntMap.fromList (zip (map f xs) (reverse xs))) Warning: I have only proved that it type-checks; I have not understood what good it does. >:)