
Having struglled over this for the better part of a day and only becoming more frustrated the more i try to understand it, i once again seek help :) I understand how basic folds work, i.e foldr replaces (:) with some parameter and [] by another i.e foldr (+) 0 [1,2,3] becomes 1+(2+(3+0)) I also understand how to write my own fold function. What i don't understand quite is how to use them. given this data type and this fold function i wrote: data Music = Note Pitch Octave Duration | Silence Duration | PlayerPar Music Music | PlayerSeq Music Music | Tempo (Ratio Int) Music data Pitch = Cf | C | Cs type Octave = Int type Duration = Ratio Int foldMusic :: (Pitch -> Octave -> Duration -> a) -> (Duration -> a) -> (a -> a -> a) -> (a -> a -> a) -> (Ratio Int -> a -> a) -> Music -> a foldMusic n _ _ _ _ (Note pitch octive duration) = n pitch octive duration foldMusic _ s _ _ _ (Silence duration) = s duration foldMusic n s p1 p2 t (PlayerPar partOne partTwo) = p1 (foldMusic n s p1 p2 t partOne)(foldMusic n s p1 p2 t partTwo) foldMusic n s p1 p2 t (PlayerPar partA partB) = p2 (foldMusic n s p1 p2 t partA)(foldMusic n s p1 p2 t partB) foldMusic n s p1 p2 t (Tempo rate part) = t rate (foldMusic n s p1 p2 t part) I understand that when i use the foldMusic function i need to pass it 5 parameters. given the type signiature, why can i pass (+) as a parameter for p1 but not for n, what determines what can be passed as a parameter, because they all have the return type a?? I attempted to create a function that utilises the foldMusic function that counts the number of notes: count_notes :: Music -> Integer count_notes = foldMusic (\_-> \_ -> \_ -> 1) (\_ -> 0) (+) (+) (\_ -> \_ -> 0) it appears to work, i think. Yet i'm still not certain of how it does so. This confuses me, Is there anyway to represent other fold functions in a tree like representation as foldr (+) 0 would appear as such? + 1 \ + 2 \ + 3 \ 0 Regards, confused Patrick _________________________________________________________________ Hot chart ringtones and polyphonics. Go to http://ninemsn.com.au/mobilemania/default.asp

patty, what you have written is not a fold. A fold operates over a list. There is no list in your code, only some sort of tree structure.
foldMusic :: (Pitch -> Octave -> Duration -> a) -> (Duration -> a) -> (a -> a -> a) -> (a -> a -> a) -> (Ratio Int -> a -> a) -> Music -> a
I understand that when i use the foldMusic function i need to pass it 5 parameters. given the type signiature, why can i pass (+) as a parameter for p1 but not for n, what determines what can be passed as a parameter, because they all have the return type a?? The first argument of your function is of type, (Duration -> a) (+) has the type, a -> a -> a, so it is nothing like the first argument.
countNotes :: Music -> Int countNotes Silence _ = 0 countNotes Note_ = 1 countNotes PlayerPar m1 m2 = (countNotes m1) + (countNotes m2) countNotes PlayerSeq m1 m2 = (countNotes m1) + (countNotes m2) countNotes Tempo _ m = countNotes m Tom

On Thu, Nov 06, 2003 at 03:41:32PM +1100, Thomas L. Bevan wrote:
patty,
what you have written is not a fold. A fold operates over a list. There is no list in your code, only some sort of tree structure.
I think you are wrong. Folds are not restricted to lists and lists are also "some sort of tree structure". See http://www.haskell.org/hawiki/WhatIsaFold Best regards, Tom -- .signature: Too many levels of symbolic links

I stand corrected On Thu, 6 Nov 2003 06:39 pm, Tomasz Zielonka wrote:
On Thu, Nov 06, 2003 at 03:41:32PM +1100, Thomas L. Bevan wrote:
patty,
what you have written is not a fold. A fold operates over a list. There is no list in your code, only some sort of tree structure.
I think you are wrong. Folds are not restricted to lists and lists are also "some sort of tree structure".
See http://www.haskell.org/hawiki/WhatIsaFold
Best regards, Tom
-- It is inconceivable that a judicious observer from another solar system would see in our species -- which has tended to be cruel, destructive, wasteful, and irrational -- the crown and apex of cosmic evolution. Viewing us as the culmination of *anything* is grotesque; viewing us as a transitional species makes more sense -- and gives us more hope. - Betty McCollister, "Our Transitional Species", Free Inquiry magazine, Vol. 8, No. 1

G'day all.
Quoting Patty Fong
I also understand how to write my own fold function. What i don't understand quite is how to use them. given this data type and this fold function i wrote:
data Music = Note Pitch Octave Duration | Silence Duration | PlayerPar Music Music | PlayerSeq Music Music | Tempo (Ratio Int) Music data Pitch = Cf | C | Cs type Octave = Int type Duration = Ratio Int
I know this doesn't answer your question, but for this example, it might be easier to use some kind of iterator. In this example: getNotes :: Music -> [Music] getNotes n@(Note _ _ _) = [n] getNotes (PlayerPar m1 m2) = getNotes m1 ++ getNotes m2 -- etc etc count_notes = length . getNotes See http://haskell.org/hawiki/IterationPattern for some ideas. Cheers, Andrew Bromage

I know this doesn't answer your question, but for this example, it might be easier to use some kind of iterator. In this example:
getNotes :: Music -> [Music] getNotes n@(Note _ _ _) = [n] getNotes (PlayerPar m1 m2) = getNotes m1 ++ getNotes m2 -- etc etc
count_notes = length . getNotes
But of course every function of this form *is a fold* and can be written as such.
Consider the length function, for example:
-- remember lists could be defined by
-- something like the following if they weren't already built in:
-- data [a] = (::) a [a] | []
length :: [a] -> Int
length (x::xs) = 1 + length xs
length [] = 0
This is just a fold:
length xs = foldr (\x r -> 1 + r) 0 xs
or in other words
length = foldr (\x r -> 1 + r) 0
You can see how the two correspond: the first argument corresponds to the first line of the definition, and the second argument corresponds to the second line of the definition.
Now go and do the same for Music.
--KW 8-)
--
Keith Wansbrough

[replying to self, oops]
getNotes n@(Note _ _ _) = [n]
[..] But of course every function of this form *is a fold* and can be written as such.
Oops, I didn't look closely enough at this line. As written, this *isn't* a fold because it examines the item (Note _ _ _ :: Music) directly rather than just looking at its arguments. But (a) it's academic in this case - since none of the arguments are recursive, you can just write getNotes (Note p o d) = [Note p o d] and become a fold again; and (b) you don't need to return the note to count it, you need only to add one to a counter. --KW 8-)

Continuing Keith's self-reply ... the Music type involves types other than Music; so it is fair to say that ultimately you would need generalised folds extended to the case of *systems* of datatypes (cf. "Dealing with large bananas"). Imagine for example getPitches :: Music -> [Pitch]. Even if a function, be it getNotes or otherwise, investigates patterns in addition to just looking at arguments obtained by recursive folding, then this function can be generally turned into a simple fold. This is the step of going from paramorphisms to catamorphisms using the infamous tupling technique that goes back to L. Meertens I think :-). (I am not sure that this the obvious way to think of these things.) Finally, the getNotes function only recurses into Music but not into the structure of Notes, and so I would actually prefer to have a return type [(Pitch,Octave,Duration)] rather than [Music] just to be sure that I am extracting notes and not whatever kind of Music. Need a banana, now :-) Ralf Keith Wansbrough wrote:
[replying to self, oops]
Oops, I didn't look closely enough at this line. As written, this *isn't* a fold because it examines the item (Note _ _ _ :: Music) directly rather than just looking at its arguments. But (a) it's academic in this case - since none of the arguments are recursive, you can just write
getNotes (Note p o d) = [Note p o d]

For what it's worth, I recently wrote a paper on what I call "polymorphic temporal media", of which "music" and "animation" are two examples. The basic data type is: data Media a = Prim a | Media a :+: Media a | Media a :=: Media a From this we can define a Music type: type Music = Media Note data Note = Rest Dur | Note Pitch Dur and an Animation type: type Animation = Media Anim type Anim = (Dur, Time -> Picture) and so on. It's then possible to define a polymorphic fold (i.e. a catamorphism) for the Media type: foldM :: (a->b) -> (b->b->b) -> (b->b->b) -> Media a -> b foldM f g h (Prim x) = f x foldM f g h (m1 :+: m2) = foldM f g h m1 `g` foldM f g h m2 foldM f g h (m1 :=: m2) = foldM f g h m1 `h` foldM f g h m2 and prove several standard laws about it, including: foldM (Prim . f) (:+:) (:=:) = fmap f foldM Prim (:+:) (:=:) = id and more importantly a Fusion Law, which states that if f' x = k (f x) g' (k x) (k y) = k (g x y) h' (k x) (k y) = k (h x y) then k . foldM f g h = foldM f' g' h' In the paper I use foldM to define a number of useful polymorphic functions on temporal media, such as a reverse function, a duration function, and most interestingly, a standard interpretation, or semantics, of polymorphic temporal media. I then prove some properties about these functions in which I avoid the use of induction by using the Fusion Law. Conceptually all of this is pretty "standard", actually, but used I think in an interesting context. If anyone would like a copy of the paper let me know. -Paul

On Thu, 06 Nov 2003 04:27:31 +0000
"Patty Fong"
Having struglled over this for the better part of a day and only becoming more frustrated the more i try to understand it, i once again seek help :)
I understand how basic folds work, i.e foldr replaces (:) with some parameter and [] by another i.e foldr (+) 0 [1,2,3] becomes 1+(2+(3+0))
I also understand how to write my own fold function. What i don't understand quite is how to use them. given this data type and this fold function i wrote:
data Music = Note Pitch Octave Duration | Silence Duration | PlayerPar Music Music | PlayerSeq Music Music | Tempo (Ratio Int) Music data Pitch = Cf | C | Cs type Octave = Int type Duration = Ratio Int
foldMusic :: (Pitch -> Octave -> Duration -> a) -> (Duration -> a) -> (a -> a -> a) -> (a -> a -> a) -> (Ratio Int -> a -> a) -> Music -> a
foldMusic n _ _ _ _ (Note pitch octive duration) = n pitch octive duration foldMusic _ s _ _ _ (Silence duration) = s duration foldMusic n s p1 p2 t (PlayerPar partOne partTwo) = p1 (foldMusic n s p1 p2 t partOne)(foldMusic n s p1 p2 t partTwo) foldMusic n s p1 p2 t (PlayerPar partA partB) = p2 (foldMusic n s p1 p2 t partA)(foldMusic n s p1 p2 t partB) foldMusic n s p1 p2 t (Tempo rate part) = t rate (foldMusic n s p1 p2 t part)
I understand that when i use the foldMusic function i need to pass it 5 parameters. given the type signiature, why can i pass (+) as a parameter for p1 but not for n, what determines what can be passed as a parameter, because they all have the return type a??
Because (+) :: Num a => a -> a -> a and that's definitely not Pitch -> Octave -> Duration -> a. But all functions will need to return the same type. Once you apply all five functions to foldMusic the result will be a function with type Music -> a (well, what a was bound to). Since that function can be applied to any particular constructor of Music then the function that will replace a particular constructor needs to return the same type as the others.
I attempted to create a function that utilises the foldMusic function that counts the number of notes:
count_notes :: Music -> Integer count_notes = foldMusic (\_-> \_ -> \_ -> 1) (\_ -> 0) (+) (+) (\_ -> \_ -> 0)
You can use \_ _ _ -> 0 instead of nested lambdas.
it appears to work, i think. Yet i'm still not certain of how it does so.
This confuses me, Is there anyway to represent other fold functions in a tree like representation as foldr (+) 0 would appear as such? + 1 \ + 2 \ + 3 \ 0
All datatypes can be represented in a tree-like (graph-like actually) way and folds follow the structure of the type(s) that they fold over. So for Music a particular instance might look like, Tempo (2%1) | PlayerPar / \ PlayerSeq Note ... / \ Note ... Silence (3%4) folds in general work from the "leaves" of the datatype to the root. Or another way, for more mathematically inclined people, is that folds follow (are) the induction principle of the datatype, it works from base case to inductive cases. A still third way of thinking about it is that a datastructure is an AST (abstract syntax tree) for some language and that a fold (applied to it's parameters) is an intepreter for that language. So for example, you likely want to play the music so you might have a function like, playMusic = foldMusic playNote pause playPar playSeq changeTempo playMusic then interprets a Music data structure as sound. Another "interpreter" you might want is something that lays out the music, so you might have, printMusic = foldMusic drawNote drawRest overlapDrawing nextBar drawTimeSignature printMusic interprets a Music data structure as say a pdf of sheet music.

At 4:27 AM +0000 2003/11/06, Patty Fong wrote:
data Music = Note Pitch Octave Duration | Silence Duration | PlayerPar Music Music | PlayerSeq Music Music | Tempo (Ratio Int) Music data Pitch = Cf | C | Cs type Octave = Int type Duration = Ratio Int
foldMusic :: (Pitch -> Octave -> Duration -> a) -> (Duration -> a) -> (a -> a -> a) -> (a -> a -> a) -> (Ratio Int -> a -> a) -> Music -> a
foldMusic n _ _ _ _ (Note pitch octive duration) = n pitch octive duration foldMusic _ s _ _ _ (Silence duration) = s duration foldMusic n s p1 p2 t (PlayerPar partOne partTwo) = p1 (foldMusic n s p1 p2 t partOne)(foldMusic n s p1 p2 t partTwo) foldMusic n s p1 p2 t (PlayerPar partA partB) = p2 (foldMusic n s p1 p2 t partA)(foldMusic n s p1 p2 t partB) foldMusic n s p1 p2 t (Tempo rate part) = t rate (foldMusic n s p1 p2 t part)
I understand that when i use the foldMusic function i need to pass it 5 parameters.
Actually, 6 parameters are required before the function invocation is complete.
given the type signiature, why can i pass (+) as a parameter for p1 but not for n, what determines what can be passed as a parameter, because they all have the return type a??
A match between two function types requires not only that the return types match, but also that there are the same number of parameters and that the parameter types match.
I attempted to create a function that utilises the foldMusic function that counts the number of notes:
count_notes :: Music -> Integer count_notes = foldMusic (\_-> \_ -> \_ -> 1) (\_ -> 0) (+) (+) (\_ -> \_ -> 0)
it appears to work, i think. Yet i'm still not certain of how it does so.
Very close. The function for "Tempo" needs fixing. Try the following (untested code): count_notes = foldMusic (\_ _ _ -> 1) (\_ -> 0) (+) (+) (\_ m -> m)
Is there anyway to represent other fold functions in a tree like representation as foldr (+) 0 would appear as such? + 1 \ + 2 \ + 3 \ 0
Yes, but it's too late for me to draw the more complicated diagram that would correspond to your Music example. Dean P.S. At 3:41 PM +1100 2003/11/06, Thomas L. Bevan wrote:
what you have written is not a fold. A fold operates over a list. There is no list in your code, only some sort of tree structure.
To me, a "fold" operates over any recursively defined (aka "inductive") data type. With this more general definition, what Patty has written is most certainly a fold. In fact, "count_notes" above corresponds directly to Thomas's "countNotes":
countNotes Silence _ = 0 countNotes Note_ = 1 countNotes PlayerPar m1 m2 = (countNotes m1) + (countNotes m2) countNotes PlayerSeq m1 m2 = (countNotes m1) + (countNotes m2) countNotes Tempo _ m = countNotes m
participants (9)
-
ajb@spamcop.net
-
Dean Herington
-
Derek Elkins
-
Keith Wansbrough
-
Patty Fong
-
Paul Hudak
-
Ralf Laemmel
-
Thomas L. Bevan
-
Tomasz Zielonka