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: WWAAA... I hate monads (Ertugrul Soeylemez) 2. Re: parser comparison question (Daniel Fischer) 3. music layout problem (Michael Mossey) 4. Sequence for functors that are not applicative? (Heinrich Apfelmus) 5. Re: generating the set of all finite-valued [...] (Erik Quaeghebeur) 6. Re: problem cabal install'ing hmatrix (Erik Quaeghebeur) 7. Working With TVars (aditya siram) 8. Re: generating the set of all finite-valued ... (Chadda? Fouch?) ---------------------------------------------------------------------- Message: 1 Date: Sat, 25 Apr 2009 09:35:09 +0200 From: Ertugrul Soeylemez <e...@ertes.de> Subject: [Haskell-beginners] Re: WWAAA... I hate monads To: beginners@haskell.org Message-ID: <20090425093509.7d6fd...@tritium.xx> Content-Type: text/plain; charset=UTF-8 Daniel Carrera <daniel.carr...@theingots.org> wrote: > > Actually Schrödinger's cat is neither dead nor alive. Its state S > > is a unit vector living in a Hilbert space. > > I spoke imprecisely, but I do know about superposition. I took a > couple of quantum courses when I got my physics degree (but generally > I focused on astrophysics which is far more interesting than quantum > mechanics). I just wanted to justify why the cat is neither dead nor alive, not both at the same time, as seems to be the common sense about quantum mechanics. But of course, this is totally off topic here. =) Greets, Ertugrul. -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://blog.ertes.de/ ------------------------------ Message: 2 Date: Sat, 25 Apr 2009 10:34:29 +0200 From: Daniel Fischer <daniel.is.fisc...@web.de> Subject: Re: [Haskell-beginners] parser comparison question To: beginners@haskell.org Message-ID: <200904251034.30159.daniel.is.fisc...@web.de> Content-Type: text/plain; charset="iso-8859-1" Am Samstag 25 April 2009 04:31:29 schrieb Walck, Scott: > I've been comparing Graham Hutton's simple parser with Parsec. Here is > some example code. > > -- Comparison of Hutton's simple parser with Parsec > > -- Hutton's simple parser is available at > -- http://www.cs.nott.ac.uk/~gmh/Parsing.lhs > > -- Hutton simple parser called H > -- Parsec called P > > import qualified Parsing as H > import qualified Text.ParserCombinators.Parsec as P > > exH = H.parse (H.string "hi") "hiho" > exP = P.parse (P.string "hi") "" "hiho" > > charH = H.parse (H.char 'a' H.+++ H.char 'b') "bbb" > charP = P.parse (P.char 'a' P.<|> P.char 'b') "" "bbb" > > choiceH = H.parse (H.string "hoo" H.+++ H.string "ho") "hono" > choiceP1 = P.parse (P.string "bb" P.<|> P.string "ba") "" "bbb" > choiceP2 = P.parse (P.string "ba" P.<|> P.string "bb") "" "bbb" > > choiceP22 = P.parse (P.try (P.string "ba") P.<|> P.string "bb") "" "bbc" > > I am interested if anyone could comment on the design of the Parsec 'try' > function. For example, choiceP2 fails and returns Left error, while > choiceP22 succeeds. > > Hutton's simple parser doesn't need try. It seems so simple and elegant. > I'm wondering why Parsec requires me to use 'try' for a string parse that > might fail. In short: efficiency The simple parser is a fully backtracking parser, therefore it has to keep the whole input available in case a parse fails and an alternative has to be tried. Parsec's alternative (<|>) tries the second parser only if the first parser failed *without consuming any input*, so the input consumed so far can be immediately discarded, which is more efficient. To get backtracking behaviour you must wrap the first parser in a 'try', which makes it either succeed or fail without consuming any input. Using try means keeping more of the input available, which has a performance cost, so use try sparingly, try to write your parsers so that they either succeed or fail (almost) immediately (P.try (P.string "ba") requires only a short part of the input kept available, so it doesn't hurt performance measurably, but imagine you have a parser that can fail after having consumed 500MB of input. Keeping that around to try the second alternative on as the simple parser must do will hurt.) > > Thanks, > > Scott > > > Scott N. Walck > Associate Professor of Physics > Lebanon Valley College > ------------------------------ Message: 3 Date: Sat, 25 Apr 2009 16:39:44 -0700 From: Michael Mossey <m...@alumni.caltech.edu> Subject: [Haskell-beginners] music layout problem To: beginners@haskell.org Message-ID: <49f39f40.7010...@alumni.caltech.edu> Content-Type: text/plain; charset=ISO-8859-1; format=flowed I'm continuing to work on this music layout problem, and I'm trying another angle. A page of music is made of many individual symbols and graphical items like lines and arcs. I decided to call a drawable symbol/item a Grapheme. so type MusicPage = [Grapheme] The program also maintains the more fundamental description of music in conceptual form---that is, notes, chords, time signatures, tempo indications, etc. I decided to call bits of information about music Datemes. type MusicScore = [Dateme] A function to lay out a musical page would have this signature: layoutPage :: [Dateme] -> [Grapheme] Now let's think about the structure of a page of music for a moment. It's made of *systems*, which are groups of notes read from left to right. A page consists of a number of systems stacked vertically (like a page of text has lines of text stacked vertically). The layout algorithm will fit as many systems as it can into a page. When it runs out of space, it will stop (even if there are Dateme left). A layout algorithm in imperative pseudocode would look something like: - initialize the list remainingDateme to the input list of Dateme - loop - looking at the list of remainingDateme, make a system - try to fit the system to the page - if the system doesn't fit, break out of the loop - add the system to the page - drop the used Dateme from remainingDateme - if remainingDateme is empty, break out of the loop - go to top of loop I tried to write this in Haskell, and it seem awkward. It would be something like: -- layout page, produce list of Grapheme and also list of -- unused Dateme layoutPage :: PageDimensions -> [Dateme] -> ( [Grapheme], [Dateme] ) layoutPage dim dateme = layoutPage' dim [] dateme layoutPage' :: PageDimensions -> [Grapheme] -> [Dateme] -> ( [Grapheme], [Dateme] ) layoutPage' dim graphemeSoFar [] = ( graphemeSoFar, [] ) layoutPage' dim graphemeSoFar remainingDateme = let ( newGrapheme, remainingDateme', dim' ) = layoutSystem dim remainingDateme in if null newGrapheme then ( graphemeSoFar, remainingDateme ) else layoutPage' dim' (graphemeSoFar ++ newGrapheme) remainingDateme' We assume this is defined elsewhere: -- layoutSystem takes as input the current page dimensions (think of -- the "current page dimensions" as the room *remaining* on the page), -- and a list of Dateme, and returns the triple: -- ( [Grapheme] for the new system, or null list if no additional system -- can fit on the page, -- remaining [Dateme] that are not consumed, -- new page dimensions ) layoutSystem :: PageDimensions -> [Dateme] -> ( [Grapheme], [Dateme], PageDimensions ) ------------------------------ Message: 4 Date: Mon, 27 Apr 2009 19:34:33 +0200 From: Heinrich Apfelmus <apfel...@quantentunnel.de> Subject: [Haskell-beginners] Sequence for functors that are not applicative? To: beginners@haskell.org Cc: haskell-c...@haskell.org Message-ID: <gt4qb2$p0...@ger.gmane.org> Content-Type: text/plain; charset=ISO-8859-1 Hello, I would like to write a function convert :: [(Name, [(Time, Chord)])] -> [(Time, [(Name, Chord)])] which transposes a finite map [(Name,b)] of event lists [(Time,a)] into an event list of finite maps. Sterling remarked that this looks very much like a job for sequence , but since event lists are not even applicative functors, I wonder whether an abstraction with less requirements can be found. Below is a first try. Heinrich Apfelmus wrote: > Sterling Clover wrote: >> Maybe just bikeshedding here (and on -beginners, no less), but this >> seems like a job for Data.Traversable.sequence? >> >> sequence :: Monad m => t (m a) -> m (t a) >> > > Great idea! > > My type signature is wrong, it should actually read > > convert :: [Named [Timed Chord]] -> [Timed [Named Chord]] > > I'm not sure whether sequence applies directly, > > type EventList a = [Timed a] > > is not a monad. It's not quite an applicative functor either, because in > > (<*>) :: EventList (a -> b) -> EventList a -> EventList b > > it's not clear what should happen to events from the left and right list > that are not simultaneous. This needs further thought. It appears that type EventList a = [(Time, a)] -- ascending times is not an applicative functor, but only a "monoid preserving functor" instance Monoid a => Monoid (EventList a) where mempty = [] mappend xs ys = map mconcat . groupBy ((==) `on` fst) . sortBy (comparing fst) (xs ++ ys) The same is true for type Group a = [(Name, a)] instance Monoid a => Monoid (Group a) where ... Put differently, we have two functions unionWith :: (a -> a -> a) -> EventList a -> EventList a -> EventList a unionWith :: (a -> a -> a) -> Group a -> Group a -> Group a Additionally, we need concat :: (a -> a -> a) -> Group a -> a and a strange function cobind' :: Functor f => Group (f a) -> Group (f (Group a)) cobind' xs = [(name, fmap (\y -> (name,y)) x) | (name,x) <- xs] that is reminiscent of a comonad. With this machinery, we can write convert :: Group (EventList a) -> EventList (Group a) convert = concat (unionWith (unionWith snd)) . cobind' No idea whether all this is overkill. After all, convert is but a glorified transpose. Regards, apfelmus -- http://apfelmus.nfshost.com ------------------------------ Message: 5 Date: Mon, 27 Apr 2009 20:39:26 +0200 (CEST) From: Erik Quaeghebeur <equae...@nospammail.net> Subject: Re: [Haskell-beginners] generating the set of all finite-valued [...] To: Haroldo Stenger <harold.sten...@gmail.com> Cc: Beginners@haskell.org Message-ID: <alpine.lnx.2.00.0904272030190.23...@ybpnyubfg> Content-Type: TEXT/PLAIN; charset=US-ASCII; format=flowed > 2009/4/23 Erik Quaeghebeur <equae...@nospammail.net> > >> I'd like to lazily generate the set of all {-1,0,1}-valued functions on >> {'a','b','c'}? How should I best approach this. I was thinking about >> generalizing the power set definition >> >> powerset :: [a] -> [[a]] >> powerset = filterM (const [True, False]) >> >> but clearly don't know enough about filterM and the like to do it this way. >> >> Erik On Mon, 27 Apr 2009, Haroldo Stenger wrote: > > i got curious about this one. Can you elaborate ? Well, elaborate about my ultimate goal, or about the powerset definition? The latter I can tell little about, I found it on-line and recognized it as a starting point. The former: generalizing http://users.ugent.be/~equaeghe/constraints.php to previsions from probabilities; C++ is a little too heavy, so I thought I'd try out Haskell. Erik ------------------------------ Message: 6 Date: Tue, 28 Apr 2009 00:05:38 +0200 (CEST) From: Erik Quaeghebeur <equae...@nospammail.net> Subject: Re: [Haskell-beginners] problem cabal install'ing hmatrix To: Alberto Ruiz <ar...@um.es> Cc: beginners@haskell.org Message-ID: <alpine.lnx.2.00.0904280002460.21...@ybpnyubfg> Content-Type: TEXT/PLAIN; charset=US-ASCII; format=flowed On Fri, 24 Apr 2009, Alberto Ruiz wrote: > > Erik, if you get > >> # ld -lgsl -llapack -lgslcblas >> ld: warning: cannot find entry symbol _start; not setting start address > > perhaps you only need to uncomment line 141 in hmatrix.cabal and try "cabal > install" in that folder. > > This is not the default because we prefer to link with a possibly optimized > cblas. Clearly hmatrix requires a previous configure step. I've managed to get things working using the gentoo haskell overlay! I had an optimized blas installed (atlas), but perhaps it wasn't automatically detected? Anyhow, it works now; there is no need to get deeper into the distribution-specific behavior. I can focus on coding. Erik ------------------------------ Message: 7 Date: Tue, 28 Apr 2009 00:43:36 -0500 From: aditya siram <aditya.si...@gmail.com> Subject: [Haskell-beginners] Working With TVars To: beginners@haskell.org Message-ID: <594f78210904272243q69118d73w1d02b869f3468...@mail.gmail.com> Content-Type: text/plain; charset="iso-8859-1" Hi all, I have a tuple inside a TVar : > type MySTM = TVar (Int,Int) Whenever I want to edit/read 'a' or 'b' I find myself writing : > editFunction mySTM = do (a',b') <- readTVar mySTM dostuff a' ... This is boilerplate stuff, so I decided to write some accessors. So far I have : > getA , getB :: MySTM -> STM Int > getA mySTM = do > (a',b') <- readTVar mySTM > return a' > > getB mySTM = do > (a',b') <- readTVar mySTM > return b' I want to be able to use these accessors like so: > doSomethingWithA mySTM = do > case (getA mySTM) of > 1 -> doStuff > 0 -> doSomethingElse But getA returns an STM Int, so I still have to do a : > doSomethingWithA = do > a' <- (getA mySTM) > case a' of > 1 -> doStuff > 0 -> doSomethingElse This doesn't really save me a lot of boilerplate. What is the best way of writing a function that just returns my values do I can work with them in the STM monad without unpacking them all the time? Thanks , Deech -------------- next part -------------- An HTML attachment was scrubbed... URL: http://www.haskell.org/pipermail/beginners/attachments/20090428/4d57a761/attachment-0001.htm ------------------------------ Message: 8 Date: Tue, 28 Apr 2009 09:26:18 +0200 From: Chadda? Fouch? <chaddai.fou...@gmail.com> Subject: Re: [Haskell-beginners] generating the set of all finite-valued ... To: Erik Quaeghebeur <equae...@nospammail.net> Cc: beginners@haskell.org Message-ID: <e9350eaf0904280026g3e187b5h5e8bf9f4792b6...@mail.gmail.com> Content-Type: text/plain; charset=UTF-8 On Fri, Apr 24, 2009 at 6:20 PM, Erik Quaeghebeur <equae...@nospammail.net> wrote: > Yes, now I see it, thanks to both Jan and Brent. > I can nicely generalize this to > >     n = ... >     values = [...] >     sequence (replicate n values) > (sequence (replicate n xs)) is part of Control.Monad under the name replicateM so : > replicateM n values -- Jedaï ------------------------------ _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners End of Beginners Digest, Vol 10, Issue 29 *****************************************