Re: Another fold question

2003-11-06 Thread Thomas L. Bevan
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
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Type tree traversals [Re: Modeling multiple inheritance]

2003-11-06 Thread Ralf Laemmel
Brandon Michael Moore wrote:

Great. But I can't build from the source: I'm getting errors about a
missing config.h.in in mk. I'm just trying autoconf, comfigure. I'll look
closer over the weekend.
 

Use the following (more specifically autoREconf).
The GHC build guide is behind.
cvs -d cvs.haskell.org:/home/cvs/root checkout fpconfig
or use anonymous access.

cd fptools
cvs checkout ghc hslibs libraries testsuite
testsuite is optional and many other nice things are around.

find . -name configure.ac -print
to find all dirs that need autoreconf (not autoconf anymore)

autoreconf
(cd ghc; autoreconf)
(cd libraries; autoreconf)
./configure
allmost done

cp mk/build.mk.sample mk/build.mk
Better this sample than no mk/build.mk at all.

gmake
Builds a nice stage2 compiler if you have ghc for bootstrap, alex, 
happy, ...,
but otherwise configure would have told you.

Ralf

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: Type tree traversals [Re: Modeling multiple inheritance]

2003-11-06 Thread Brandon Michael Moore


On Wed, 5 Nov 2003, Simon Peyton-Jones wrote:

> | More overlapping:
> | Allow any overlapping rules, and apply the most specific rule that
> | matches our target. Only complain if there is a pair of matching
> | rules neither of which is more specific than the other.
> | This follow the spirit of the treatment of duplicate imports...
>
> Happy days.  I've already implemented this change in the HEAD.  If you
> can build from source, you can try it.

Great. But I can't build from the source: I'm getting errors about a
missing config.h.in in mk. I'm just trying autoconf, comfigure. I'll look
closer over the weekend.

> | Backtracking search:
> | If several rules matched your target, and the one you picked didn't
> | work, go back and try another.
> |
> | This isn't as well through out: you probably want to backtrack through
> all
> | the matching rules even if some are unordered by being more specific.
> It
> | would probably be godd enough to respect specificity, and make other
> | choices arbitrarilily (line number, filename, etc. maybe Prolog has a
> | solution?). This probably isn't too hard if you can just add
> | nondeterminism to the monad the code already lives in.
>
> I didn't follow the details of this paragraph.  But it looks feasible.

It's an unclear paragraph. I meant that if we are just looking for the
first match, we should try more specific rules before less specific rule.
That doesn't give us a complete ordering so we might do something
arbitrary for the rest, unless there is a better solution.

I think we should make sure that there are not multiple solutions, but we
want more specific rules to take priority. Order the solutions
lexicographically by how specific each rule in the derivation was and
complain if there isn't a least element in this set of solutions.  To
implement, if at each step there is a most specific rule in the set we
haven't tried, and making that choice at every step gives us a solution,
we know we have the most specific solution and don't need to keep
searching.

I don't want to be too strict about having a unique solution because
that can prevent modelling multiple inheritance

Brandon

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Another fold question

2003-11-06 Thread Paul Hudak
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

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Another fold question

2003-11-06 Thread Ralf Laemmel
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]
 



___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Another fold question

2003-11-06 Thread Dean Herington
At 4:27 AM + 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
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Another fold question

2003-11-06 Thread 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-)

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Another fold question

2003-11-06 Thread Keith Wansbrough
> 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 <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Another fold question

2003-11-06 Thread Tomasz Zielonka
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
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe