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: type puzzlement (prad)
   2.  cabal installs parsec-2.1 not parsec-3.1? Same   with
      QuickCheck-1.2 not 2.1? (Gerald Gutierrez)
   3. Re:  cabal installs parsec-2.1 not parsec-3.1?    Same with
      QuickCheck-1.2 not 2.1? (David McBride)
   4. Re:  cabal installs parsec-2.1 not parsec-3.1?    Same with
      QuickCheck-1.2 not 2.1? (Daniel Fischer)
   5. Re:  Re: type puzzlement (J?rgen Doser)
   6.  Re: [Haskell-cafe] music-related problem (Dean Herington)


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

Message: 1
Date: Wed, 21 Jul 2010 11:29:44 -0700
From: prad <p...@towardsfreedom.com>
Subject: [Haskell-beginners] Re: type puzzlement
To: beginners@haskell.org
Message-ID: <20100721112944.17c7e...@gom>
Content-Type: text/plain; charset=ISO-8859-1

On Wed, 21 Jul 2010 11:10:53 +0200
Jürgen Doser <jurgen.do...@gmail.com> wrote:

> There is: <interactive>:1:0-21 says the error is in line 1, columns
> 0-21 of the interactive input.
hmmm i'm worse at reading error messages than i thought. usually it
comes out something like Elem.lhs:186:13:, but i should have been able
to adapt and be more aware.

is there any sort of a guide for reading and interpreting error
messages? i couldn't find anything specific through google.

thank you for clarifying my difficulty jurgen (and ulrik, via email).
i'm not sufficiently capable of understanding type messages either.

i think it would be beneficial for me to collect these error messages
and type explanations as they come up to try to find patterns in them
to acquire more competence in interpretation. 

are there techniques or approaches others have used to get good at
understanding error messages as they learned haskell?

-- 
In friendship,
prad

                                      ... with you on your journey
Towards Freedom
http://www.towardsfreedom.com (website)
Information, Inspiration, Imagination - truly a site for soaring I's


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

Message: 2
Date: Wed, 21 Jul 2010 09:19:18 -0700
From: Gerald Gutierrez <gerald.gutier...@gmail.com>
Subject: [Haskell-beginners] cabal installs parsec-2.1 not parsec-3.1?
        Same    with QuickCheck-1.2 not 2.1?
To: beginners@haskell.org
Message-ID:
        <aanlktiks-kajaaa8sbjfgvnfvs-zkaao_vmvp71nm...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Why is it that when I run "cabal install parsec" or "cabal upgrade parsec",
it does not install the latest 3.1 version but instead sticks with the
current 2.1 version? The same goes for quickcheck, where it will stay at 1.2
and not upgrade to 2.1. To install the latest versions, I need to explicitly
specify the version.

I thought /upgrade/ is supposed to upgrade to the latest version. Is there
reasoning behind this?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100721/374b8c13/attachment-0001.html

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

Message: 3
Date: Wed, 21 Jul 2010 15:39:26 -0400
From: David McBride <dmcbr...@neondsl.com>
Subject: Re: [Haskell-beginners] cabal installs parsec-2.1 not
        parsec-3.1?     Same with QuickCheck-1.2 not 2.1?
To: Gerald Gutierrez <gerald.gutier...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <aanlktinr-qk88ezyjzinvykfnpwz11a6vazldfj_b...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Have you done a 'cabal update' to pull the latest list of software that is
available?

On Wed, Jul 21, 2010 at 12:19 PM, Gerald Gutierrez <
gerald.gutier...@gmail.com> wrote:

> Why is it that when I run "cabal install parsec" or "cabal upgrade parsec",
> it does not install the latest 3.1 version but instead sticks with the
> current 2.1 version? The same goes for quickcheck, where it will stay at 1.2
> and not upgrade to 2.1. To install the latest versions, I need to explicitly
> specify the version.
>
> I thought /upgrade/ is supposed to upgrade to the latest version. Is there
> reasoning behind this?
>
>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100721/b606fda6/attachment-0001.html

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

Message: 4
Date: Wed, 21 Jul 2010 21:47:27 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] cabal installs parsec-2.1 not
        parsec-3.1?     Same with QuickCheck-1.2 not 2.1?
To: beginners@haskell.org
Cc: Gerald Gutierrez <gerald.gutier...@gmail.com>
Message-ID: <201007212147.28219.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="utf-8"

On Wednesday 21 July 2010 18:19:18, Gerald Gutierrez wrote:
> Why is it that when I run "cabal install parsec" or "cabal upgrade
> parsec", it does not install the latest 3.1 version but instead sticks
> with the current 2.1 version? The same goes for quickcheck, where it
> will stay at 1.2 and not upgrade to 2.1. To install the latest versions,
> I need to explicitly specify the version.
>
> I thought /upgrade/ is supposed to upgrade to the latest version. Is
> there reasoning behind this?

Don't use cabal upgrade, it does not do what you expect, probably.

The reason that cabal install parsec gives you parsec-2 and not parsec-3 
(same for QuickCheck and a few others) is that there are 'preferred 
versions' for a few packages which are not the latest versions, because 
they've been widely used and then undergone major API changes, so serving 
the new version unquestioningly could break many packages, hence it was 
decided to play safe and default to the previous (packages depending on the 
new versions would pull that in explicitly).
The new versions have now been around for a while, so most packages should 
have fixed their dependencies and the 'preferred versions' can (will?) be 
removed soon.


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

Message: 5
Date: Thu, 22 Jul 2010 00:27:12 +0200
From: J?rgen Doser <jurgen.do...@gmail.com>
Subject: Re: [Haskell-beginners] Re: type puzzlement
To: prad <p...@towardsfreedom.com>
Cc: beginners@haskell.org
Message-ID: <1279751232.3466.35.ca...@imedia.irun.org>
Content-Type: text/plain; charset=utf-8

El mié, 21-07-2010 a las 11:29 -0700, prad escribió:
> [...]
> are there techniques or approaches others have used to get good at
> understanding error messages as they learned haskell?

Practice makes perfect. Simply trying hard to understand what ghc is
saying has worked for me so far. It helps of course, if you know what
the types mean, and have a rough understanding of how the type-inference
is supposed to work. Most tutorials on functional programming/Haskell
should have some nice exercises on manually inferring types.

        Jürgen



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

Message: 6
Date: Thu, 22 Jul 2010 00:32:03 -0400
From: Dean Herington <heringtonla...@mindspring.com>
Subject: [Haskell-beginners] Re: [Haskell-cafe] music-related problem
To: Michael Mossey <m...@alumni.caltech.edu>, beginners@haskell.org,
        haskell-cafe <haskell-c...@haskell.org>
Message-ID: <a06240800c86c3e029...@[192.168.1.103]>
Content-Type: text/plain; charset="us-ascii" ; format="flowed"

At 11:53 AM -0700 7/4/10, Michael Mossey wrote:
>Wondering if I could get some suggestions for coding this problem.
>
>A musical document (or "score") consists primarily of a list of 
>measures. A measure consists primarily of lists of "items". We'll 
>consider only one kind of item: a note. Items have a location within 
>the measure. A note's
>location indicates both where it goes on the page (i.e. a visual 
>representation of the score) and what moment in time it begins 
>sounding (i.e. rendering the score in sound). My concern here is 
>sound.
>
>data Doc = [Measure]
>
>data Loc = ... (represents a location within the musical
>                 document including measure number)
>
>
>data Measure = Measure [(Loc,Item)]
>   -- In the Meausre, we can assume (Loc,Item) are in
>   --  ascending order
>
>
>Notes also have an end, when indicates when in time they stop
>sounding. See the 'end' field below. Also note the 'soundedEnd'
>  'tieStart' and 'tieStop' fields which I will explain.
>
>data Item = Note
>             { pitch :: Pitch
>             , end :: Loc
>             , soundedEnd :: Maybe Loc
>             , tieNext :: Bool
>             , tiePrior :: Bool
>             }
>
>There is a concept of "tied notes". When two notes are tied
>together, their durations are summed and they are sounded
>continuously as if one note. Ties have several uses, but one
>important one is to make a sound that begins in one measure and
>ends in a later measure, by tying notes across measures.
>
>The 'tieNext' field indicates if a note is tied to the following
>note (that is, the next note of the same pitch). 'tiePrior'
>indicates if tied to immediately prior note of same pitch.
>
>A chain of notes can be tied. Notes in the middle with have
>both tieNext and tiePrior set.
>
>In the event a note is within a chain of ties, its 'soundedEnd'
>field needs to be computed as Just e where e is the end of the
>last note in the chain. This information is useful when rendering
>the document as sound.
>
>My problem is:
>
>   - given a Doc in which all fields have been set EXCEPT soundedEnd
>     (all soundedEnd's are given a default value of Nothing)
>   - update those notes in the Doc which need to have soundedEnd set.
>     This involves chasing down the chain of ties.
>
>I can solve a simpler problem which is
>
>-- Given a note with tieNext set, and a list of notes, find
>-- the end Loc of the last note in the chain. Only notes
>-- with the same pitch as 'firstNote' are considered when looking
>-- for the chain of notes.
>computeSoundedEnd :: Item -> [Item] -> Loc
>computeSoundedEnd firstNote notes = compSndEnd (pitch firstNote) notes
>
>compSndEnd :: Pitch -> [Item] -> Loc
>compSndEnd _ [] = error "tie chain doesn't come to completion"
>compSndEnd p (n:ns) = if pitch n == p
>                         then if tieNext n
>                           then if tiePrior n
>                             then compSndEnd p ns
>                             else error "illegal tie chain"
>                           else if tiePrior n
>                             then end n
>                             else error "illegal tie chain"
>                         else compSndEnd p ns
>
>The thing that is hard for me to understand is how, in a functional
>paradigm, to update the entire Doc by chasing down every tie and making
>all necessary updates.
>
>Thanks,
>Mike


[Sorry to be coming so late to this thread.  I'm catching up on old 
Haskell e-mail.]

I agree with some of the earlier posters that your representation is 
probably more complicated than needed.  (BTW, a graph especially 
seems like overkill.)

Nevertheless, given your representation, `soundedEnd` can be computed 
idiomatically and efficiently in Haskell.  As you showed, computing 
`soundedEnd` for one item depends only on the item and those that 
follow it.  In an imperative language, we would compute the 
`soundedEnd` values from the end to the beginning, storing the 
results as we go.  In Haskell, we can simply use a "foldr" pattern 
and let lazy evaluation take care of the rest.  (Unfortunately, in 
this case the "foldr" is not quite so simple, due to the two levels 
of lists--measures and items.)

I simplify the computation of `soundedEnd` by letting it be defined 
always:  For a note whose `tieNext` is `False`, the `soundedEnd` 
value equals the `end` value.  With this approach, `soundedEnd` has 
type `Loc`.  (In fact, its value could be computed (i.e., the thunk 
to evaluate it could be installed) when the item is originally 
created, thanks again to lazy evaluation.)  Also, I eliminate 
`tiePrior` because it's not needed for this demonstration.

Dean


import Ratio

type Duration = Rational  -- Whole note has duration 1.

type Loc = (Int, Duration)

type Pitch = Char  -- for simplicity

data Item = Note
         { pitch :: Pitch
         , end :: Loc
         , soundedEnd :: Loc
         , tieNext :: Bool
         }
   deriving (Show, Read)

data Measure = Measure [(Loc, Item)]
   deriving (Show, Read)

type Doc = [Measure]


computeSoundedEnd :: Doc -> Doc
computeSoundedEnd measures = foldr eachMeasure [] measures
   where eachMeasure (Measure litems) remainingMeasures = Measure 
(foldr eachLItem [] litems) : remainingMeasures
           where eachLItem (loc, item) remainingLItems = (loc, item') 
: remainingLItems
                   where item' = item{ soundedEnd = soundedEndFor 
item' remainingLItems remainingMeasures }

soundedEndFor :: Item -> [(Loc, Item)] -> [Measure] -> Loc
soundedEndFor item litems measures
     | tieNext item = case filter ((pitch item ==) . pitch . snd) 
(litems ++ concatMap unMeasure measures) of
                        [] -> error "illegal tie chain"
                        (_, item') : _ -> soundedEnd item'
     | otherwise = end item

unMeasure :: Measure -> [(Loc, Item)]
unMeasure (Measure litems) = litems



measureLength = 4%4  -- for simplicity

plus :: Loc -> Duration -> Loc
(m, o) `plus` d = let o' = (o + d) / measureLength
                       md = floor o'
                       od = o' - fromIntegral md
                   in (m + md, od)

li tied start pitch dur = (start, Note pitch (start `plus` dur) 
(error "undefined soundedEnd") tied)
ni start pitch dur = li False start pitch dur
ti start pitch dur = li True  start pitch dur

[a,b,c,d,e,f,g] = ['a'..'g']

-- In the following graphical representation:
--  * Each character position represents an eighth note.
--  * A capitalized note is tied to its successor.
--  * Note that the "B" line is musically dubious.
-- |        |        |      g.|
-- |        |        |   Ff.  |
-- |      E.|E.......|E.e     |
-- |  D.d.  |        |        |
-- |c.  c.  |        |        |
-- |      B.|        |b.......|
-- |        |A.A.A.a.|        |
doc1 = [Measure [ni (0,0%4) c (1%4), ti (0,1%4) d (1%4), ni (0,2%4) c 
(1%4), ni (0,2%4) d (1%4), ti (0,3%4) b (1%4), ti (0,3%4) e (1%4)],
         Measure [ti (1,0%4) a (1%4), ti (1,0%4) e (1%1), ti (1,1%4) a 
(1%4), ti (1,2%4) a (1%4), ni (1,3%4) a (1%4)],
         Measure [ti (2,0%4) e (1%4), ni (2,0%4) b (1%1), ni (2,1%4) e 
(1%8), ti (2,3%8) f (1%8), ni (2,2%4) f (1%4), ni (2,3%4) g (1%4)]]

main = print (computeSoundedEnd doc1)


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

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


End of Beginners Digest, Vol 25, Issue 47
*****************************************

Reply via email to