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:
import qualified Data.Text as T
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 #-}
import Prelude hiding (map)
import qualified Data.Text as T
import Control.Monad (Functor)
map :: (Element a -> b) -> a -> Container a b
instance (Functor f) => CanMap (f a) b where
type Container (f a) b = f b
instance CanMap T.Text Char where
type Element T.Text = Char
type Container T.Text Char = T.Text
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.