Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  help with types and composition (Dan Douglas)
   2. Re:  help with types and composition (Edward Z. Yang)
   3. Re:  help with types and composition (Thomas Davie)
   4. Re:  Help with "20 intermediate haskell exercises"
      (Patrick LeBoutillier)
   5.  guitar tuner alike (Bernhard Lehnert)
   6. Re:  guitar tuner alike (Joe Fredette)
   7. Re:  Help with "20 intermediate haskell exercises" (Brent Yorgey)
   8. Re:  guitar tuner alike (Brent Yorgey)
   9.  Understanding State (Geoffrey Marchant)


----------------------------------------------------------------------

Message: 1
Date: Mon, 06 Jul 2009 08:30:46 CDT
From: Dan Douglas <doug0...@metnet.edu>
Subject: Re: [Haskell-beginners] help with types and composition
To: beginners@haskell.org
Message-ID: <200907061330.n66dukuc006...@tove.metnet.edu>
Content-Type: TEXT/plain; CHARSET=US-ASCII

Ah silly me I think I sorta get it. after looking up currying this somewhat
makes sense (it isn't really mentioned in YAHT and not till later in most
other books.)

So, basically any function's type will always be in curryfied form, and the
only time there's a tuple involved is if the function's argument is itself a
tuple? I'll have to ponder a bit how nesting functions are equivalent to a
function with multiple arguments.

Sorry about the messed up Unicode. That question doesn't really make sense
knowing this.

On 6 Jul 2009, Daniel Fischer wrote:
> Am Montag 06 Juli 2009 13:53:01 schrieb Dan Douglas:
> > Hello everyone! first post here. I'm working through YAHT and Real World
> > Haskell sort of in parallel. I have a somewhat related question.
> >
> > Assume we have a binary operator which is not a higher order function.
The
> > "greater than" relation for example:
> >
> > Prelude List> :t (>)
> > (>) :: forall a. (Ord a) => a -> a -> Bool
> >
> > Type classes and variables make sense - I assume since we have
quantifiers,
> > the type classes must be essentially predicates, and the type variables
are
> > bound to them as expected. Also I assume whenever we see (a -> b) this
> > means roughly f:(<domain> -> <codomain>)
> 
> Correct.
> 
> >
> > a -> a -> Bool could therefore mean either: "a function whose domain is
an
> > 'a' and whose codomain is a function from a to bool";
> 
> Yes, that's it.
> 
> > or "a function which
> > takes a function from type 'a' to 'a' and returns a bool.
> 
> That would be the type (a -> a) -> Bool.
> 
> >
> > According to YAHT:
> >
> > "NOTE The parentheses are not necessary; in function types, if you
> > have a -> b -> y it is assume that b -> y is grouped. If you want the
> > other way, with a -> b grouped, you need to put parentheses around
> > them."
> 
> In short: (->) is right associative,
> 
> a -> b -> c -> d === a -> (b -> (c -> d))
> 
> 
> >
> > I'm confused by this. A function which takes multiple arguments should be
> > equivalent to a predicate bound to some n-tuple. Or in this case of a
> > binary infix operator, equivalent to a prefix operator which takes a
tuple.
> 
> Correct.
> 
> > But, (a, a) is not equivalent to (a -> a),
> 
> Indeed it isn't, the two sets don't even have the same cardinality (except
a
> contains only 
> one element).
> But (a -> a) -> Bool is *not* equivalent to a -> (a -> Bool).
> 
> > and (a -> Bool) just doesn't make sense as a range.
> 
> But it does. (a -> Bool) is a perfectly reasonable set/Haskell type.
> Functions whose result is a function are very common in functional
> programming.
> 
> > It should be something like:
> >
> > (>) :: forall a. (Ord a) => (a, a) -> Bool
> 
> Note that, (ignoring _|_ and partial functions), the types ((a,b) -> c) and

> (a -> (b -> c)) are isomorphic. The isomorphism is given by
> 
> curry :: ((a,b) -> c) -> (a -> (b -> c))
> curry f = \x y -> f (x,y)
> 
> and
> 
> uncurry :: (a -> (b -> c)) -> ((a,b) -> c)
> uncurry g = \(x,y) -> g x y
> 
> >
> > Someone on freenode told me that if you had:
> >
> > foo :: a -> b
> > bar :: b -> c
> > baz :: c -> d
> >
> > and:
> >
> > bork = (baz . bar . foo)
> >
> > then:
> >
> > bork :: a -> d
> 
> 
> Yup.
> >
> > Which, if correct means Haskell should always chain types for first-order
> > functions. And since (>) is transitive, it should satisfy
> > &#8704;x&#8704;y&#8704;z(((x,y) &#8712; R & (y,z) &#8712; R) -> (x,z)
> > &#8712; R) and omit the case for (y,z).
> 
> 
> ???
> 
> >
> > How it is possible to express a function which takes multiple arguments
(or
> > any first-order function at all) with more than one arrow/map symbol? How
> > does this even make sense?
> >
> > It gets even worse with more complicated examples:
> >
> > Prelude List> :t foldl
> > foldl :: forall a b. (a -> b -> a) -> a -> [b] -> a
> >
> > Prelude List> :t (>>=)
> > (>>=)
> >
> >   :: forall (m :: * -> *) a b. (Monad m) => m a -> (a -> m b) -> m b
> >
> > How do the non-existent associativity rules make complex function types
> > seemingly without enough parentheses have unique meaning?
> 
> The associativity rules exist:
> 
> (->) associates to the right.
> 
> Hence, fully parenthesised:
> 
> foldl :: (a -> (b -> a)) -> (a -> ([b] -> a))
> 
> Due to the right associativity, you can omit three pairs of parentheses.
> 
> >
> > Nearly every example in every tutorial on types I can find has this
> > unexplained phenomenon, or I'm really not reading carefully.
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
> 




------------------------------

Message: 2
Date: Mon, 06 Jul 2009 10:30:05 -0400
From: "Edward Z. Yang" <ezy...@mit.edu>
Subject: Re: [Haskell-beginners] help with types and composition
To: beginners <beginners@haskell.org>
Message-ID: <1246890561-sup-3...@javelin>
Content-Type: text/plain; charset=UTF-8

Excerpts from Dan Douglas's message of Mon Jul 06 09:30:46 -0400 2009:
> So, basically any function's type will always be in curryfied form, and the
> only time there's a tuple involved is if the function's argument is itself a
> tuple? I'll have to ponder a bit how nesting functions are equivalent to a
> function with multiple arguments.

The easiest way to think about this is to add parentheses around the
type declaration.

Int -> Int -> Int

becomes:

Int -> (Int -> Int)

Cheers,
Edward


------------------------------

Message: 3
Date: Mon, 6 Jul 2009 16:41:08 +0200
From: Thomas Davie <tom.da...@gmail.com>
Subject: Re: [Haskell-beginners] help with types and composition
To: "Edward Z. Yang" <ezy...@mit.edu>
Cc: beginners <beginners@haskell.org>
Message-ID: <7d11ac99-ab45-46a9-8159-401e8733f...@gmail.com>
Content-Type: text/plain; charset=US-ASCII; format=flowed; delsp=yes


On 6 Jul 2009, at 16:30, Edward Z. Yang wrote:

> Excerpts from Dan Douglas's message of Mon Jul 06 09:30:46 -0400 2009:
>> So, basically any function's type will always be in curryfied form,  
>> and the
>> only time there's a tuple involved is if the function's argument is  
>> itself a
>> tuple? I'll have to ponder a bit how nesting functions are  
>> equivalent to a
>> function with multiple arguments.
>
> The easiest way to think about this is to add parentheses around the
> type declaration.
>
> Int -> Int -> Int
>
> becomes:
>
> Int -> (Int -> Int)

The other part of the story being the definition of functions.  First  
lets rewrite some syntactic sugar:

f x y = x + y
-- Rewrite to use lambda abstraction instead of the definition syntax
f = \x y -> x + y
-- Rewrite to remove multiple argument lambas
f = \x -> \y -> x + y
-- Add in the parentheses to show the currying going on
f = \x -> (\y -> x + y)

Bob


------------------------------

Message: 4
Date: Mon, 6 Jul 2009 15:55:34 -0400
From: Patrick LeBoutillier <patrick.leboutill...@gmail.com>
Subject: Re: [Haskell-beginners] Help with "20 intermediate haskell
        exercises"
To: beginners@haskell.org
Message-ID:
        <b217a64f0907061255x4d86e643m6366ddde65ea9...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi,

On Sun, Jul 5, 2009 at 3:44 PM, Daniel Fischer<daniel.is.fisc...@web.de> wrote:
> Am Sonntag 05 Juli 2009 21:05:20 schrieb Patrick LeBoutillier:
>> Hi,
>>
>> Thanks for the help. I figured it out after that. I'm having a hard
>> time with the other exercises though, I'm currently stuck at 14:
>>
>>
>> class Misty m where
>>   banana :: (a -> m b) -> m a -> m b
>>   unicorn :: a -> m a
>>
>> -- Exercise 14
>> -- Relative Difficulty: 6
>> moppy :: (Misty m) => [a] -> (a -> m b) -> m [b]
>> moppy = error "todo"
>
> moppy [] mop = ?
> moppy (a:as) mop = (mop a) ?? (moppy as mop)
>
> use (among other things) banana and unicorn to replace the question marks

I came up with this:moppy [] mop = unicorn []
moppy (a:as) mop = banana (\b -> banana (\bs -> unicorn (b:bs)) (moppy
as mop)) (mop a)


moppy [] mop = unicorn []
moppy (a:as) mop = banana (\b -> banana (\bs -> unicorn (b:bs)) (moppy
as mop)) (mop a)

How do I make the second one nicer/shorter?


Patrick


>
>>
>>
>> Does anyone know if the solutions are posted anywhere?
>
> They're (under different names) in the standard libraries :)

I found it: forM

>
>>
>>
>> Patrick
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



-- 
=====================
Patrick LeBoutillier
Rosemère, Québec, Canada


------------------------------

Message: 5
Date: Mon, 06 Jul 2009 22:32:07 +0200
From: Bernhard Lehnert <b.lehn...@gmx.de>
Subject: [Haskell-beginners] guitar tuner alike
To: beginners@haskell.org
Message-ID: <1246912327.3625.7.ca...@sol>
Content-Type: text/plain

Hi,

would there, by any chance, be something like a simple and well
documented way to read sound from a microphone on the soundcard and
perform a fft or sth. to find the pitch of a sound?

There is a whole lot of so called "guitar tuner" progs doing that, but
any simple to use library for haskell? (Preferebly available on Windows,
too.)
Looking through hackage it seems to me that there is a wealth of libs
for sound and music synthesis but not so much for sound analysis. Good
online reading advice on the topic (be it haskell or not) would also be
greatly appreciated (maybe some handbook for the dsp package?).

Thanks,
Bernhard



------------------------------

Message: 6
Date: Mon, 06 Jul 2009 17:00:25 -0400
From: Joe Fredette <jfred...@gmail.com>
Subject: Re: [Haskell-beginners] guitar tuner alike
To: Bernhard Lehnert <b.lehn...@gmx.de>
Cc: beginners@haskell.org
Message-ID: <4a5265e9.1060...@gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

I don't know of any such libs on hackage, but I think your best bet 
would be to find a C library which does what you want, then write an FFI 
binding to it. Not only will you get the functionality you want, but you 
could contribute a binding-library to hackage which would be _way 
awesome_. You can find resources about FFI in Real World Haskell (google 
it, the book is available free online), and of course Hoogle will be 
helpful.

/Joe

Bernhard Lehnert wrote:
> Hi,
>
> would there, by any chance, be something like a simple and well
> documented way to read sound from a microphone on the soundcard and
> perform a fft or sth. to find the pitch of a sound?
>
> There is a whole lot of so called "guitar tuner" progs doing that, but
> any simple to use library for haskell? (Preferebly available on Windows,
> too.)
> Looking through hackage it seems to me that there is a wealth of libs
> for sound and music synthesis but not so much for sound analysis. Good
> online reading advice on the topic (be it haskell or not) would also be
> greatly appreciated (maybe some handbook for the dsp package?).
>
> Thanks,
> Bernhard
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>   
-------------- next part --------------
A non-text attachment was scrubbed...
Name: jfredett.vcf
Type: text/x-vcard
Size: 296 bytes
Desc: not available
Url : 
http://www.haskell.org/pipermail/beginners/attachments/20090706/55a53122/jfredett-0001.vcf

------------------------------

Message: 7
Date: Mon, 6 Jul 2009 17:10:22 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Help with "20 intermediate haskell
        exercises"
To: beginners@haskell.org
Message-ID: <20090706211022.ga8...@seas.upenn.edu>
Content-Type: text/plain; charset=iso-8859-1

On Mon, Jul 06, 2009 at 03:55:34PM -0400, Patrick LeBoutillier wrote:
> Hi,
> 
> On Sun, Jul 5, 2009 at 3:44 PM, Daniel Fischer<daniel.is.fisc...@web.de> 
> wrote:
> > Am Sonntag 05 Juli 2009 21:05:20 schrieb Patrick LeBoutillier:
> >> Hi,
> >>
> >> Thanks for the help. I figured it out after that. I'm having a hard
> >> time with the other exercises though, I'm currently stuck at 14:
> >>
> >>
> >> class Misty m where
> >>   banana :: (a -> m b) -> m a -> m b
> >>   unicorn :: a -> m a
> >>
> >> -- Exercise 14
> >> -- Relative Difficulty: 6
> >> moppy :: (Misty m) => [a] -> (a -> m b) -> m [b]
> >> moppy = error "todo"
> >
> > moppy [] mop = ?
> > moppy (a:as) mop = (mop a) ?? (moppy as mop)
> >
> > use (among other things) banana and unicorn to replace the question marks
> 
> I came up with this:moppy [] mop = unicorn []
> moppy (a:as) mop = banana (\b -> banana (\bs -> unicorn (b:bs)) (moppy
> as mop)) (mop a)
> 
> 
> moppy [] mop = unicorn []
> moppy (a:as) mop = banana (\b -> banana (\bs -> unicorn (b:bs)) (moppy
> as mop)) (mop a)
> 
> How do I make the second one nicer/shorter?

Great!  You can't make it much shorter just using banana and unicorn.
But you could make it a little nicer like so:

  ananab = flip banana

  moppy (a:as) mop = mop a `ananab` (\b -> moppy as mop `ananab` (\bs -> 
unicorn (b:bs))

That makes it a bit more obvious where the 'b' and 'bs' are coming from.

You can also do something like this:

  liftBanana2 f mx my = mx `ananab` (\x -> my `ananab` (\y -> unicorn (f x y)))

  moppy (a:as) mop = liftBanana2 (:) (mop a) (moppy as mop)

I'll let you figure out what 'ananab' and 'liftBanana2' are called in the 
standard libraries. =)

-Brent


------------------------------

Message: 8
Date: Mon, 6 Jul 2009 17:11:46 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] guitar tuner alike
To: beginners@haskell.org
Message-ID: <20090706211145.gb8...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

I'd suggest forwarding your question to the haskell-art mailing list [1].

-Brent

[1] http://lists.lurk.org/mailman/listinfo/haskell-art

On Mon, Jul 06, 2009 at 10:32:07PM +0200, Bernhard Lehnert wrote:
> Hi,
> 
> would there, by any chance, be something like a simple and well
> documented way to read sound from a microphone on the soundcard and
> perform a fft or sth. to find the pitch of a sound?
> 
> There is a whole lot of so called "guitar tuner" progs doing that, but
> any simple to use library for haskell? (Preferebly available on Windows,
> too.)
> Looking through hackage it seems to me that there is a wealth of libs
> for sound and music synthesis but not so much for sound analysis. Good
> online reading advice on the topic (be it haskell or not) would also be
> greatly appreciated (maybe some handbook for the dsp package?).
> 
> Thanks,
> Bernhard
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners


------------------------------

Message: 9
Date: Thu, 9 Jul 2009 22:34:29 -0600
From: Geoffrey Marchant <geoffrey.march...@gmail.com>
Subject: [Haskell-beginners] Understanding State
To: beginners@haskell.org
Message-ID:
        <79e6290e0907092134g5b0b350fp9d6f2cecb5f9c...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

I'm trying to understand how to use State in a function. I've avoided the
topic for several years because State just never seemed very useful, but I
figure it's time for me to figure it out:
I have the following function

> update :: (a -> (r,a)) -> Int -> [a] -> (r, [a])
> update s 0 (a:as) = let (r,a') = s a in (r,a':as)
> update s i (a:as) = let (r,as') = update s (i-1) as in (r, a:as')

which updates a particular element of a list. Looking at it, I see two parts
of the type signature that look like State types, which leads me to think of
this:

> update' :: State a r -> Int -> State [a] r

Which leads to me writing this:

> update' s 0 = do
>    (a:as) <- get
>    let (r, a') = runState s a
>    put (a':as)
>    return r
> update' s i = do
>    (a:as) <- get
>    put as
>    r <- update' s (i-1)
>    as' <- get
>    put (a:as')
>    return r

Now, this just looks awful. The first half, the base condition, is actually
"running" a State calculation. And the second half sets the state within the
monad twice!

I like the idea of using State because it simplifies the type. When I see (a
-> (b,a)) I say "Wait a second, that's a State calculation, isn't it?" and
then, hopefully, generalize. But I can't write that calculation nearly as
concisely. How do I do this properly?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090710/b855502e/attachment.html

------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 13, Issue 5
****************************************

Reply via email to