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:  for those who wondered where I was... (Yitzchak Gale)
   2. Re:  for those who wondered where I was... (Marc Weber)
   3.  bad state monad instances (Keith Sheppard)
   4. Re:  bad state monad instances (Alexander Dunlap)
   5. Re:  bad state monad instances (Daniel Fischer)
   6. Re:  bad state monad instances (Keith Sheppard)
   7.  a problem (Michael Mossey)
   8. Re:  a problem (Stephen Tetley)
   9.  Re: howto reason infinite lists (Heinrich Apfelmus)


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

Message: 1
Date: Tue, 22 Jun 2010 23:49:48 +0300
From: Yitzchak Gale <g...@sefer.org>
Subject: Re: [Haskell-beginners] for those who wondered where I was...
To: Michael Mossey <m...@alumni.caltech.edu>
Cc: haskellbeginners <beginners@haskell.org>
Message-ID:
        <aanlktinzt3iwlzz5czeux8slkf6-apvynnlu-z_pi...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Michael Mossey wrote:
> ...I went back to Python...
> Then I thought, what the heck am I doing? This is a good task for Haskell!
> ...Working with Haskell tonight, in about four hours I replicated several 
> weeks
> of Python work. Yup, this is the right approach.

Welcome back!

Regards,
Yitz


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

Message: 2
Date: Tue, 22 Jun 2010 23:49:07 +0200
From: Marc Weber <marco-owe...@gmx.de>
Subject: Re: [Haskell-beginners] for those who wondered where I was...
To: beginners <beginners@haskell.org>
Message-ID: <1277243253-sup-3...@nixos>
Content-Type: text/plain; charset=UTF-8

> It took me a few weeks to get a basic input system working. I.e. 
> MusicXML documents translated into my own representation, and reasonable 
> error checking.

Check out lilypond.
http://lilypond.org/about/faq

It can process MusicXML to .ly and .ly to .midi
However I think that there are some shortcomings using this chain

Still lilypond may be of interest to you.

Marc Weber


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

Message: 3
Date: Tue, 22 Jun 2010 21:53:14 -0400
From: Keith Sheppard <keiths...@gmail.com>
Subject: [Haskell-beginners] bad state monad instances
To: beginners@haskell.org
Message-ID:
        <aanlktimvfjdl6nmnzo68ptanp0qrobg3v8tjxysys...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi,

I'm working on understanding the state monad, and I got stumped pretty
much right away. When I run the following script (with instances
copied verbatim from
http://www.haskell.org/all_about_monads/html/statemonad.html )

#!/usr/bin/env runhaskell
\begin{code}
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
import Control.Monad.State(Monad, MonadState(..))

newtype State s a = State { runState :: (s -> (a,s)) }

instance Monad (State s) where
    return a        = State $ \s -> (a,s)
    (State x) >>= f = State $ \s -> let (v,s') = x s in runState (f v) s'

instance MonadState (State s) s where
    get   = State $ \s -> (s,s)
    put s = State $ \_ -> ((),s)

main :: IO ()
main = putStrLn "hello"

\end{code}


It fails with:
statemonadtest.lhs:11:20:
    `State s' is not applied to enough type arguments
    Expected kind `*', but `State s' has kind `* -> *'
    In the instance declaration for `MonadState (State s) s'

Can you see what I'm doing wrong? I must be making a really basic
mistake but I'm not sure what it is.

Thanks, Keith
-- 
keithsheppard.name


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

Message: 4
Date: Tue, 22 Jun 2010 19:13:30 -0700
From: Alexander Dunlap <alexander.dun...@gmail.com>
Subject: Re: [Haskell-beginners] bad state monad instances
To: Keith Sheppard <keiths...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <aanlktima9lvdiwsuewrc4bij6k6dsu6xnd-bgh3w4...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

Change the instance head to

instance MonadState s (State s) where

It looks like the tutorial has the two parameters for MonadState in
the opposite order as does the mtl package.

Alex

On Tue, Jun 22, 2010 at 6:53 PM, Keith Sheppard <keiths...@gmail.com> wrote:
> Hi,
>
> I'm working on understanding the state monad, and I got stumped pretty
> much right away. When I run the following script (with instances
> copied verbatim from
> http://www.haskell.org/all_about_monads/html/statemonad.html )
>
> #!/usr/bin/env runhaskell
> \begin{code}
> {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
> import Control.Monad.State(Monad, MonadState(..))
>
> newtype State s a = State { runState :: (s -> (a,s)) }
>
> instance Monad (State s) where
>    return a        = State $ \s -> (a,s)
>    (State x) >>= f = State $ \s -> let (v,s') = x s in runState (f v) s'
>
> instance MonadState (State s) s where
>    get   = State $ \s -> (s,s)
>    put s = State $ \_ -> ((),s)
>
> main :: IO ()
> main = putStrLn "hello"
>
> \end{code}
>
>
> It fails with:
> statemonadtest.lhs:11:20:
>    `State s' is not applied to enough type arguments
>    Expected kind `*', but `State s' has kind `* -> *'
>    In the instance declaration for `MonadState (State s) s'
>
> Can you see what I'm doing wrong? I must be making a really basic
> mistake but I'm not sure what it is.
>
> Thanks, Keith
> --
> keithsheppard.name
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>


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

Message: 5
Date: Wed, 23 Jun 2010 04:17:51 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] bad state monad instances
To: beginners@haskell.org
Message-ID: <201006230417.52068.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

On Wednesday 23 June 2010 03:53:14, Keith Sheppard wrote:
> Hi,
>
> I'm working on understanding the state monad, and I got stumped pretty
> much right away. When I run the following script (with instances
> copied verbatim from
> http://www.haskell.org/all_about_monads/html/statemonad.html )
>
> #!/usr/bin/env runhaskell
> \begin{code}
> {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
> import Control.Monad.State(Monad, MonadState(..))
>
> newtype State s a = State { runState :: (s -> (a,s)) }
>
> instance Monad (State s) where
>     return a        = State $ \s -> (a,s)
>     (State x) >>= f = State $ \s -> let (v,s') = x s in runState (f v)
> s'
>
> instance MonadState (State s) s where
>     get   = State $ \s -> (s,s)
>     put s = State $ \_ -> ((),s)
>
> main :: IO ()
> main = putStrLn "hello"
>
> \end{code}
>
>
> It fails with:
> statemonadtest.lhs:11:20:
>     `State s' is not applied to enough type arguments
>     Expected kind `*', but `State s' has kind `* -> *'
>     In the instance declaration for `MonadState (State s) s'
>
> Can you see what I'm doing wrong? I must be making a really basic
> mistake but I'm not sure what it is.

Wrong argument order in the MonadState instance,

class (Monad m) => MonadState s m | m -> s where
  get :: m s
  put :: s -> m ()

The state type comes first, then the Monad.

Make it

instance MonadState s (State s) where ...

I don't know if that's been changed at some point or if it was a typo in 
the tutorial from the beginning.

>
> Thanks, Keith



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

Message: 6
Date: Tue, 22 Jun 2010 22:23:33 -0400
From: Keith Sheppard <keiths...@gmail.com>
Subject: Re: [Haskell-beginners] bad state monad instances
To: Daniel Fischer <daniel.is.fisc...@web.de>,
        alexander.dun...@gmail.com
Cc: beginners@haskell.org
Message-ID:
        <aanlktinlnzyn3twkzcfnoacnd0r1olmctvz3wkiy9...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Thanks! This change plus adding FlexibleInstances makes it valid.

On Tue, Jun 22, 2010 at 10:17 PM, Daniel Fischer
<daniel.is.fisc...@web.de> wrote:
> On Wednesday 23 June 2010 03:53:14, Keith Sheppard wrote:
>> Hi,
>>
>> I'm working on understanding the state monad, and I got stumped pretty
>> much right away. When I run the following script (with instances
>> copied verbatim from
>> http://www.haskell.org/all_about_monads/html/statemonad.html )
>>
>> #!/usr/bin/env runhaskell
>> \begin{code}
>> {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
>> import Control.Monad.State(Monad, MonadState(..))
>>
>> newtype State s a = State { runState :: (s -> (a,s)) }
>>
>> instance Monad (State s) where
>>     return a        = State $ \s -> (a,s)
>>     (State x) >>= f = State $ \s -> let (v,s') = x s in runState (f v)
>> s'
>>
>> instance MonadState (State s) s where
>>     get   = State $ \s -> (s,s)
>>     put s = State $ \_ -> ((),s)
>>
>> main :: IO ()
>> main = putStrLn "hello"
>>
>> \end{code}
>>
>>
>> It fails with:
>> statemonadtest.lhs:11:20:
>>     `State s' is not applied to enough type arguments
>>     Expected kind `*', but `State s' has kind `* -> *'
>>     In the instance declaration for `MonadState (State s) s'
>>
>> Can you see what I'm doing wrong? I must be making a really basic
>> mistake but I'm not sure what it is.
>
> Wrong argument order in the MonadState instance,
>
> class (Monad m) => MonadState s m | m -> s where
>  get :: m s
>  put :: s -> m ()
>
> The state type comes first, then the Monad.
>
> Make it
>
> instance MonadState s (State s) where ...
>
> I don't know if that's been changed at some point or if it was a typo in
> the tutorial from the beginning.
>
>>
>> Thanks, Keith
>
>



-- 
keithsheppard.name


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

Message: 7
Date: Wed, 23 Jun 2010 01:07:33 -0700
From: Michael Mossey <m...@alumni.caltech.edu>
Subject: [Haskell-beginners] a problem
To: beginners@haskell.org
Message-ID: <4c21c0c5.5050...@alumni.caltech.edu>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Can I get a suggestion for a concise way to write 'sortOutMusicData' as 
described here? This is MusicXML-related.

data Music_Data_ = Music_Data_1 Note
                  | Music_Data_4 Direction
                  | Music_Data_9 Sound
                   ...

sortOutMusicData :: [Music_Data_] -> ([Note],[Direction],[Sound])



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

Message: 8
Date: Wed, 23 Jun 2010 10:19:05 +0100
From: Stephen Tetley <stephen.tet...@gmail.com>
Subject: Re: [Haskell-beginners] a problem
To: Michael Mossey <m...@alumni.caltech.edu>
Cc: beginners@haskell.org
Message-ID:
        <aanlktilhtwg2kegm6n8f3ly-gardovwuyrkmvtyqb...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

A right-fold with a three-part accumulator is arguably simple and clear:

sortOutMusicData :: [Music_Data_] -> ([Note],[Direction],[Sound])
sortOutMusicData = foldr step ([],[],[])
  where
    step (Music_Data_1 n) (ns,ds,ss) = (n:ns, ds,   ss  )
    step (Music_Data_4 d) (ns,ds,ss) = (ns,   d:ds, ss  )
    step (Music_Data_9 s) (ns,ds,ss) = (ns,   ds,   s:ss)

Each step is simply a cons (:) to one of the tree lists which is
efficient. As the right fold takes you "backwards" through the list,
the orders of [Note], [Direction] etc. will be congruent with the
order of original input.


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

Message: 9
Date: Wed, 23 Jun 2010 13:02:38 +0200
From: Heinrich Apfelmus <apfel...@quantentunnel.de>
Subject: [Haskell-beginners] Re: howto reason infinite lists
To: beginners@haskell.org
Message-ID: <hvspkf$tc...@dough.gmane.org>
Content-Type: text/plain; charset=UTF-8; format=flowed

prad wrote:
> i'm trying to figure out how to think out the circular definition for
> an infinite list and would appreciate suggestions.
> 
> consider
> ones = 1 : ones
> this essentially says 1 : (1 : (1 : (1 : ones))) with ones being given
> by the original def.
> 
> however, i had trouble with this one
> fib = 1 : 1 : [ a+b | (a,b) <- zip fib (tail fib) ]

The Haskell wikibook has some material on this:

   http://en.wikibooks.org/wiki/Haskell/Denotational_semantics


Basically, the key question is: "What is a recursive definition, 
anyway?". The answer to that is that any recursively defined value is 
obtained from a sequence of approximations. We start with the worst 
approximation called ⊥ ("bottom") which basically means "it's undefined, 
we don't know what it is".

   fib_0 = ⊥

To get a better approximation, we apply the definition of  fib  to that.

   fib_1 = 1 : 1 : [ a+b | (a,b) <- zip fib_0 (tail fib_0) ]
         = 1 : 1 : [ a+b | (a,b) <- zip ⊥ (tail ⊥) ]
         = 1 : 1 : [ a+b | (a,b) <- zip ⊥ ⊥ ]
         = 1 : 1 : [ a+b | (a,b) <- ⊥ ]
         = 1 : 1 : ⊥

To get an even better approximation, we once again apply the equation 
for  fib  to this approximation:

   fib_2 = 1 : 1 : [ a+b | (a,b) <- zip fib_1 (tail fib_1) ]
         = 1 : 1 : [ a+b | (a,b) <- zip (1:1:⊥) (tail (1:1:⊥)) ]
         = 1 : 1 : [ a+b | (a,b) <- zip (1:1:⊥) (1:⊥) ]
         = 1 : 1 : [ a+b | (a,b) <- (1,1):⊥ ]
         = 1 : 1 : 2 : ⊥

and so on and so on. The limit of these approximations

   fib_0 = ⊥
   fib_1 = 1 : 1 : ⊥
   fib_2 = 1 : 1 : 2 : ⊥
   fib_3 = 1 : 1 : 2 : 3 : ⊥
   ...

is the infinite list

   fib = 1 : 1 : 2 : 3 : 5 : ...


This is the thinking that you have described, with a minor, but crucial 
change. Namely, it's not clear that your list elements  a,b,c,d,  etc. 
exist a priori, i.e. that the list is already created in this form. For 
instance, it wouldn't be right to say that the example

   foo = 1 : 1 : loop
       where loop = loop

can be written as

   foo = [1,1,a,b,c, ..]

because the recursion simply won't progress past

   foo = 1 : 1 : ⊥

The formulation with ⊥ can handle such cases. In other words, your 
thinking is right but somewhat restricted to a few particular examples 
while the method using ⊥ as shown here will *always* apply.

The key message to take away is that you also need some way (⊥) to 
express recursive definitions that might loop forever.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com



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

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


End of Beginners Digest, Vol 24, Issue 28
*****************************************

Reply via email to