ClassyPrelude has two map functions, namely:1. "map"2. "omap""map" works on any Functor. However, things like "Text" are not functors as they aren't generic containers. As can be seen in the following code:module Main whereimport Prelude ()import ClassyPreludeimport qualified Data.Text as Timport Data.Char as Cmain = dolet l = [1,2,3] :: [Int]let t = (T.pack "Hello")let m = Just 5print $ map (*2) lprint $ map (*2) mprint $ omap C.toUpper treturn ()Notice one has to use "omap" to deal with the Text. The thing is, I found it trivially easy to get "map" to work for both calls. Here's the code:{-# LANGUAGE MultiParamTypeClasses #-}{-# LANGUAGE TypeFamilies #-}module Main whereimport Prelude hiding (map)import qualified Data.Text as Timport Data.Char as Cimport Control.Monad (Functor)class CanMap a b wheretype Element a :: *type Container a b :: *map :: (Element a -> b) -> a -> Container a binstance (Functor f) => CanMap (f a) b wheretype Element (f a) = atype Container (f a) b = f bmap = fmapinstance CanMap T.Text Char wheretype Element T.Text = Chartype Container T.Text Char = T.Textmap = T.mapmain = dolet l = [1,2,3] :: [Int]let m = Just 5let t = (T.pack "Hello")print $ map (*2) lprint $ map (*2) mprint $ map C.toUpper treturn ()All that's required is to add instances to CanMap for any monomorphic containers. ClassyPrelude already does this anyway with "omap" in the Data.MonoTraversable module. I suspect however there's a good reason I'm missing about why there should be two separate map functions to deal with these alternate situations, but I'm wondering what that is.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe