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. music-related problem (Michael Mossey) 2. Re: [Haskell-cafe] music-related problem (Serguey Zefirov) 3. Re: 'cabal install hdirect' can't find hdirect (Larry Evans) 4. Re: curry in a hurry (prad) 5. Re: curry in a hurry (prad) 6. Re: 'cabal install hdirect' can't find hdirect (Stephen Tetley) 7. Re: 'cabal install hdirect' can't find hdirect (Larry Evans) 8. threadDelay does not delay thread execution? (Benjamin Edwards) ---------------------------------------------------------------------- Message: 1 Date: Sun, 04 Jul 2010 11:53:39 -0700 From: Michael Mossey <m...@alumni.caltech.edu> Subject: [Haskell-beginners] music-related problem To: beginners@haskell.org, haskell-cafe <haskell-c...@haskell.org> Message-ID: <4c30d8b3.9060...@alumni.caltech.edu> Content-Type: text/plain; charset=ISO-8859-1; format=flowed 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 ------------------------------ Message: 2 Date: Sun, 4 Jul 2010 22:13:19 +0300 From: Serguey Zefirov <sergu...@gmail.com> Subject: [Haskell-beginners] Re: [Haskell-cafe] music-related problem To: Michael Mossey <m...@alumni.caltech.edu> Cc: beginners@haskell.org, haskell-cafe <haskell-c...@haskell.org> Message-ID: <aanlktikwst8yva-1q3zgisusvymtdjnpbcibsoaky...@mail.gmail.com> Content-Type: text/plain; charset=ISO-8859-1 > 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. This looks like one of graph algorithms. Notes are nodes, ties are arcs. Measures, etc are parts of node label. soundedEnd property can be computed over this. Actually, it would be wise to parametrize Item with computed attributes so that you can clearly distinguish between documents where soundedEnd is set from documents where it is not. ------------------------------ Message: 3 Date: Sun, 04 Jul 2010 16:45:29 -0500 From: Larry Evans <cppljev...@suddenlink.net> Subject: Re: [Haskell-beginners] 'cabal install hdirect' can't find hdirect To: beginners@haskell.org Message-ID: <4c3100f9.8000...@suddenlink.net> Content-Type: text/plain; charset=ISO-8859-1; format=flowed On 07/04/10 11:19, Stephen Tetley wrote: > Hi Larry > > > Hugs comes with a library - FiniteMap. Maybe FiniteMaps is a spelling > mistake or maybe it it a module the Wolfram Kahl didn't distribute. > > Thanks Stephen, I changed the name; however, then 2 other names needed changing: lookupDftFM -> lookupWithDefaultFM zeroFM -> emptyFM However, even after those changes, I got several errors: ~/prog_dev/haskell/modular-interpreter $ ghc -fallow-overlapping-instances -fallow-undecidable-instances -fglasgow-exts -o Int Interpreter.hs Interpreter.hs:155:39: Couldn't match expected type `FiniteMap Name (InterpM Value)' against inferred type `Name' In the first argument of `addToFM', namely `n' In the first argument of `Env', namely `(addToFM n v e)' In the expression: Env (addToFM n v e) Interpreter.hs:203:14: Overlapping instances for StateMonad s (StateT Store (EnvT Env (ContT Answer (StateT [String] (ErrorT []))))) arising from a use of `liftSTFun' at Interpreter.hs:203:14-38 Matching instances: instance [overlap ok] (StateMonad s m, MonadT t m) => StateMonad s (t m) -- Defined at Interpreter.hs:(391,0)-(392,23) instance [overlap ok] (Monad m) => StateMonad s (StateT s m) -- Defined at Interpreter.hs:(301,0)-(302,43) (The choice depends on the instantiation of `s' To pick the first instance above, use -fallow-incoherent-instances when compiling the other instance declarations) In the expression: liftSTFun (updateStore p) In the definition of `updateLoc': updateLoc p = liftSTFun (updateStore p) Interpreter.hs:211:56: Couldn't match expected type `InterpM Value' against inferred type `FiniteMap Integer (InterpM Value)' In the third argument of `addToFM', namely `fm' In the second argument of `Store', namely `(addToFM i v fm)' In the expression: Store n (addToFM i v fm) Interpreter.hs:427:9: The scoped type variables `env' and `r' are bound to the same type (variable) Distinct scoped type variables must be distinct In the pattern: r :: env In the definition of `inEnv': inEnv (r :: env) (ContT c) = ContT (\ k -> do o <- rdEnv inEnv r (c (inEnv (o :: env) . k))) In the definition for method `inEnv' ~/prog_dev/haskell/modular-interpreter $ Any suggestions for workarounds would be appreciated. -regards, Larry ------------------------------ Message: 4 Date: Sun, 4 Jul 2010 19:02:10 -0700 From: prad <p...@towardsfreedom.com> Subject: [Haskell-beginners] Re: curry in a hurry To: beginners@haskell.org Message-ID: <20100704190210.526ba...@gom> Content-Type: text/plain; charset=US-ASCII On Sat, 03 Jul 2010 19:37:48 -0400 Brandon S Allbery KF8NH <allb...@ece.cmu.edu> wrote: > look up Church numerals. > i've been trying to understand the process here through this document: http://users.info.unicaen.fr/~karczma/Essays/church.html and i'm getting parts of it. what is really good is that it seems to be haskell specific and so i'll give it a try after getting a better idea about it all through the above, the recommended paper "Church Numerals, Twice" (hinze), and some other papers i found on lambda calculus. these ideas all seem very different to any math i've ever done (boolean algebra is about the extent of it as related to computer languages), i'm hoping that a grounding in some of this will help my haskell. >This too looks odd; but consider Gaussian integers > i'll look into that too afterwards. thanks for the way to interpret the type declaration, brandon. -- 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: 5 Date: Sun, 4 Jul 2010 19:14:28 -0700 From: prad <p...@towardsfreedom.com> Subject: [Haskell-beginners] Re: curry in a hurry To: beginners@haskell.org Message-ID: <20100704191428.7b245...@gom> Content-Type: text/plain; charset=US-ASCII On Sun, 4 Jul 2010 01:17:45 +0200 Daniel Fischer <daniel.is.fisc...@web.de> wrote: > Which is somewhat incorrect. Every function takes exactly one > argument, curried or not. > ya i'm beginning to see that i took the statement too much to heart. your explanations have helped sort out several things including thinking about what is being said instead of just accepting it. > No, your initial thought is correct, f takes a single argument, which > is a pair. (Well, since tuples are composed of several components, it > is also a common way of speech to say that functions taking a tuple > argument take several arguments. In that sense, f takes two > arguments. But in Haskell- speak, it's more common to say a function > fun :: a -> b -> c > takes two arguments > right, but what i think i was doing was making an issue with one vs multiple arguments when what i should probably have been doing is examining exactly what (un)currying processes actually do. > - of course, if c is a function type, we can also > say that f takes three [or more] arguments.) > ok so this is interesting too! f :: a -> b -> c c :: x -> y -> z would mean f effectively takes 5 arguments and i should be paying attention to and understanding structures that develop from the typedefs. -- 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: 6 Date: Mon, 5 Jul 2010 08:08:41 +0100 From: Stephen Tetley <stephen.tet...@gmail.com> Subject: Re: [Haskell-beginners] 'cabal install hdirect' can't find hdirect To: Larry Evans <cppljev...@suddenlink.net> Cc: beginners@haskell.org Message-ID: <aanlktikfbi1uvx4gztqihy9mpew1zswwdnzefvikl...@mail.gmail.com> Content-Type: text/plain; charset=ISO-8859-1 Hi Larry I'll take a look at getting the code to work later today. Which system - GHCi or Hugs - would you prefer to use? If you prefer GHCi, I'll replace the whole FiniteMap module with Data.Map as FiniteMap has been made obsolete by Data.Map. Best wishes Stephen ------------------------------ Message: 7 Date: Mon, 05 Jul 2010 04:53:06 -0500 From: Larry Evans <cppljev...@suddenlink.net> Subject: Re: [Haskell-beginners] 'cabal install hdirect' can't find hdirect To: beginners@haskell.org Message-ID: <4c31ab82.6030...@suddenlink.net> Content-Type: text/plain; charset=ISO-8859-1; format=flowed On 07/05/10 02:08, Stephen Tetley wrote: > Hi Larry > > I'll take a look at getting the code to work later today. > Thanks very much. > Which system - GHCi or Hugs - would you prefer to use? > GHCi, because I tried: cabal install --hugs after download & unzip & untar: http://hackage.haskell.org/packages/archive/hdirect/0.21.0/hdirect-0.21.0.tar.gz but, apparently, the hugs compiler I've got cannot correctly parse some of the .lhs files downloaded :( > If you prefer GHCi, I'll replace the whole FiniteMap module with > Data.Map as FiniteMap has been made obsolete by Data.Map. > That sounds best. > Best wishes > > Stephen > > Thank you Stephen. -regards, Larry ------------------------------ Message: 8 Date: Mon, 5 Jul 2010 11:51:58 +0200 From: Benjamin Edwards <edwards.b...@gmail.com> Subject: [Haskell-beginners] threadDelay does not delay thread execution? To: haskellbeginners <beginners@haskell.org> Message-ID: <aanlktileuejlndcmu0js_wz6w9hyc6-s4bup-0nt0...@mail.gmail.com> Content-Type: text/plain; charset="iso-8859-1" Hi All, I am looking to make a simple program that polls an interface once a second or so. I thought I could use threadDelay for this, so knocked up the following toy program to test my idea. module TD where import Control.Concurrent import Control.Concurrent.MVar main :: IO () main = do mv <- newEmptyMVar forkIO $ loop mv 0 "Hai" takeMVar mv return () where loop mv n msg = do putStrLn msg threadDelay 10000 if n < 10 then loop mv (n+1) msg else putMVar mv () It doesn't work, in as much as I see all the messages printed seemingly as fast as Std out will print them. What am I doing wrong? All help is much appreciated, Ben -------------- next part -------------- An HTML attachment was scrubbed... URL: http://www.haskell.org/pipermail/beginners/attachments/20100705/123bfbb4/attachment.html ------------------------------ _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners End of Beginners Digest, Vol 25, Issue 14 *****************************************