 
            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)
 
            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
On Fri, Jul 23, 2010 at 12:04 PM, Johann Bach 
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
 
            Hi Johann A simple metric to help you decide is to ask the question "Do I need type changing?" as that's somewhat the essence of the Functor class. It doesn't look like any of you types are parametric - so thus far you don't need type changing. You could open up your datatypes making them parametric on maybe Note or Pitch. For instance you might decide you want two representations of Pitch: a) Integer for generating MIDI, b) Symbolic for printing - Pitch letters plus octave - C | Cs | Db | D ... As MusicDoc, Part etc must be made parametric to accommodate this, it would be obvious to make them instances of Functor and the related classes Traversable and Foldable which give you nice operations for generic traversals. But if then you want to be parametric on Duration as well, then you have a problem - there aren't common classes for BiFunctor, BiFoldable, BiTraversable... I've represented music myself with a TriFunctor - parametric on Pitch, Duration and Annotation - in practice it wasn't a good way to do it. The other alternative is to use a "generics" library - currently Uniplate is considered the simplest. Generics libraries provide generic traversals of data structures without the restriction to Functor types. Best wishes Stephen
 
            Johann Bach wrote:
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?
You could make the types polymorphic to be able to make a functor instance, but it's not necessarily a good idea. In any case, you may want to have a look at functional references http://article.gmane.org/gmane.comp.lang.haskell.cafe/28094 One implementation of functional references is http://hackage.haskell.org/package/data-accessor Then, you can for instance write parts :: Accessor MusDoc [Part] notes :: Accessor Part [Notes] example :: MusDoc -> MusDoc example = modify parts . map . modify notes $ filter (== CSharp) where notes and parts are two appropriate functional references, which are best generated automatically. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com
 
            Thanks, everyone. I will look up some of these ideas. I hadn't thought of the fact that Functor has kind *->*. (Googly-eyed Pinnochio? Just kidding.) I just thought that my data types contained other types. -Johann
participants (4)
- 
                 edgar klerks edgar klerks
- 
                 Heinrich Apfelmus Heinrich Apfelmus
- 
                 Johann Bach Johann Bach
- 
                 Stephen Tetley Stephen Tetley