He Johann,
Functors have the type * -> *, so your MusicDoc type doesn't match. But if you fix that it is easy to create a functor, especially when using DeriveFunctor, if you are a lazy person:
{-# LANGUAGE DeriveFunctor #-}
import qualified Data.Map as M
data PartInfo = Void
deriving Show
type PartId = Int
newtype MusDoc a = MusDoc { docParts :: M.Map PartId (PartInfo, a) }
deriving (Functor,Show)
singleton a = MusDoc $ M.singleton 1 (Void, a)
Test:
*Main> fmap (+1) $ singleton 1
Loading package array-0.3.0.0 ... linking ... done.
Loading package containers-0.3.0.0 ... linking ... done.
MusDoc {docParts = fromList [(1,(Void,2))]}
*Main>
Greets,
Edgar
I'm wondering if the following problem might reveal a use for Functor
or Applicative, or just generally something cooler than I'm doing now.
I have a music document as type MusDoc. It has [Part]. Part has
[Note]. I have defined them using field names because I am
deliberating allowing for this to get more complicated later.
The question is about mapping functions over the individual parts. I
often find myself wanting to alter or
filter all the parts. In the following example I define filterDoc with
a couple of helper functions. What I
would like to know: is there a cooler way to do this using instances
of Functor or something? Defining
operators?
import Map(Map)
import qualified Map as M
type PartId = String -- identification of a part in a music document
data PartInfo = .. -- ancillary information about a part
-- the notes, markings, etc in a part
-- It is conceivable other fields could be added later.
data Part = Part { partNotes :: [Note] }
-- Main music document, consisting of parts.
data MusDoc = MusDoc { docParts :: Map PartId (PartInfo,Part) }
-- Helper function to map over parts
mapParts :: (Part -> Part) -> MusDoc -> MusDoc
mapParts g (MusDoc parts) = MusDoc $ M.map (second g) parts
-- Filter notes that meet a predicate
filterDoc :: (Note -> Bool) -> MusDoc -> MusDoc
filterDoc pred doc = mapParts (filterPart pred) doc
-- Helper function to filterDoc.
filterPart :: (Note -> Bool) -> Part -> Part
filterPart pred (Part notes) = Part (filter pred notes)
_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners