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: deducing type of multi-parameter type class (Felipe Lessa) 2. Re: deducing type of multi-parameter type class (Michael Snoyman) 3. Re: Re: why is something different within a function when it comes out? (Chadda? Fouch?) 4. Re: Re: why is something different within a function when it comes out? (Chadda? Fouch?) 5. Re: Thompson Exercise 9.13 (dan portin) 6. Re: Thompson Exercise 9.13 (Patrick LeBoutillier) ---------------------------------------------------------------------- Message: 1 Date: Thu, 15 Jul 2010 04:09:16 -0300 From: Felipe Lessa <felipe.le...@gmail.com> Subject: Re: [Haskell-beginners] deducing type of multi-parameter type class To: Michael Snoyman <mich...@snoyman.com> Cc: beginners@haskell.org Message-ID: <aanlktil90glzcfcb1gb2iu54rgzuyoe0snezrw2fv...@mail.gmail.com> Content-Type: text/plain; charset=UTF-8 On Thu, Jul 15, 2010 at 3:13 AM, Michael Snoyman <mich...@snoyman.com> wrote: > You could also use type families for this, but I believe you cannot express > the "Show" superclass: > class MyClass a where >    type MyResult a >    fn :: a -> MyResult a I guess this works: class Show (MyResult a) => MyClass a where type MyResult a fn :: a -> MyResult a HTH, -- Felipe. ------------------------------ Message: 2 Date: Thu, 15 Jul 2010 10:35:14 +0300 From: Michael Snoyman <mich...@snoyman.com> Subject: Re: [Haskell-beginners] deducing type of multi-parameter type class To: Felipe Lessa <felipe.le...@gmail.com> Cc: beginners@haskell.org Message-ID: <aanlktinqsfwbxyhmf1pnl__bcb_kxmraz-t_gwtj6...@mail.gmail.com> Content-Type: text/plain; charset="utf-8" On Thu, Jul 15, 2010 at 10:09 AM, Felipe Lessa <felipe.le...@gmail.com>wrote: > On Thu, Jul 15, 2010 at 3:13 AM, Michael Snoyman <mich...@snoyman.com> > wrote: > > You could also use type families for this, but I believe you cannot > express > > the "Show" superclass: > > class MyClass a where > > type MyResult a > > fn :: a -> MyResult a > > I guess this works: > > class Show (MyResult a) => MyClass a where > type MyResult a > fn :: a -> MyResult a > Thanks, I forgot about that. Funny, because I use it in Yesod ;). Michael -------------- next part -------------- An HTML attachment was scrubbed... URL: http://www.haskell.org/pipermail/beginners/attachments/20100715/7ba73e2e/attachment-0001.html ------------------------------ Message: 3 Date: Thu, 15 Jul 2010 09:39:39 +0200 From: Chadda? Fouch? <chaddai.fou...@gmail.com> Subject: Re: [Haskell-beginners] Re: why is something different within a function when it comes out? To: prad <p...@towardsfreedom.com> Cc: beginners@haskell.org Message-ID: <aanlktinnmxdkgatdz-qkf0s_jdllr91aocvwxxloo...@mail.gmail.com> Content-Type: text/plain; charset=UTF-8 On Thu, Jul 15, 2010 at 3:19 AM, prad <p...@towardsfreedom.com> wrote: > which works fine for single lines, but produces nothing for multiple > lines - same with some of the other ways i tried it with single lines > good, nothing for multiple. python requires setting the re.S flag which > i always found strange since \n i thought is a char as well. The problem is classic in regex world : by default "." match any character except \n, I would suggest "<title>\n([^<]*)\n</title>" which is probably a bit more robust anyway. Though you must be aware that parsing html (or any markup language) properly with regexp is just impossible in general and you can only get crude and fragile approximations. There are proper html parsing libraries on hackage if your needs become too complex for simple regexp to handle. -- Jedaï ------------------------------ Message: 4 Date: Thu, 15 Jul 2010 09:44:18 +0200 From: Chadda? Fouch? <chaddai.fou...@gmail.com> Subject: Re: [Haskell-beginners] Re: why is something different within a function when it comes out? To: prad <p...@towardsfreedom.com> Cc: beginners@haskell.org Message-ID: <aanlktiltztnsb78kilywkfdwz8c5ze3nwz1htzjpj...@mail.gmail.com> Content-Type: text/plain; charset=UTF-8 On Thu, Jul 15, 2010 at 3:19 AM, prad <p...@towardsfreedom.com> wrote: > python requires setting the re.S flag Note that Haskell also allows you to do things like that though you must compile the regexp with the proper flags, you can't use a simple string as a regexp anymore (mkRegexpWithOpts False False "regexp" compile with "single-line" semantics (ie. "." will match \n)). -- Jedaï ------------------------------ Message: 5 Date: Thu, 15 Jul 2010 06:46:15 -0700 From: dan portin <danpor...@gmail.com> Subject: Re: [Haskell-beginners] Thompson Exercise 9.13 To: Daniel Fischer <daniel.is.fisc...@web.de>, beginners@haskell.org Message-ID: <aanlktikrnktbbocv8ngphgayz4ewpkmtu6hvf6iwp...@mail.gmail.com> Content-Type: text/plain; charset="iso-8859-1" > [...] it needs to traverse the entire list before it can start assembling > the result. > To avoid that, so the result can be assembled from the start of the list, > you need to make the pattern match on the second argument lazy, > > f (x,y) ~(xs,ys) = (x:xs,y:ys) > > or > > f (x,y) p = (x : fst p, y : snd p) > > Now > > f (x,y) (f (x1,y1) ([],[])) > ~> let (xs,ys) = f (x1,y1) ([],[]) in (x:xs, y:ys) > This makes sense. I didn't realize Haskell was doing this. Of course, that could be a downside to evaluating by hand on paper, where you often 'think lazily.' I assumed Haskell evaluated the expression in a similar way to your 'let ...' clause. > > > > *last* :: [a] -> a > > last xs = head $ foldr f [] xs > > where f :: a -> [a] -> [a] > > f x [] = [x] > > f x ys = ys ++ [x] > > last xs = head (reverse xs), yes, it's correct, but not very pretty. > And not very efficient since it builds a left-associated nest of (++) > applications and needs to pattern match to decide which branch to take. > > last (1:2:3:4:[]) > ~> head $ foldr f [] (1:2:3:4:[]) > ~> head $ f 1 (f 2 (f 3 (f 4 []))) > ~> head $ f 1 (f 2 (f 3 [4])) > ~> head $ f 1 (f 2 ([4] ++ [3])) > ~> head $ f 1 (([4] ++ [3]) ++ [2]) > ~> head $ ((([4] ++ [3]) ++ [2]) ++ [1] > > a) in the second branch of f, you don't actually need to concatenate, > > f x [] = [x] > f _ ys = ys > > works too, but is faster. > > b) you can get much faster by delaying the pattern match, > > f x ys = (case ys of { [] -> x; y:_ -> y }) : [] > Yes, nesting each element inside (++) operators was an oversight on my part. Your solution (a) is much cleaner, since head $ foldr f [] (1:2:3:[]) ~> head $ f 1 (f 2 (f 3 [])) ~> head $ f 1 (f 2 (3:[])) ~> head $ f 1 (3:[]) ~> head $ (3:[]) I'm confused about (b), however. I was under the impression<http://www.haskell.org/tutorial/patterns.html>that the pattern match f P1 ... P1N = E1 f P2 ... P2N = E2 is *semantically* equivalent to f x1 ... xn = case (x1, ..., xn) of { P1 ... P1n -> E1; P2 ... P2n -> E2}. Of course, "semantically equivalent" doesn't mean "as efficient." I don't understand whether the move from matching against '_ ys' to y:_ is supposed to make the definition of f more efficient to compute, or whether the use of case expressions is supposed to. > > > *init* :: [a] -> [a] > > init xs = tail $ foldr f [] xs > > where f :: a -> [a] -> [a] > > f x [] = [x] > > f x (y:xs) = y : x : xs > > Correct too, but again not very efficient since it has to find the last > element and bubble it to the front. > > Much faster: > : > import Data.Maybe (fromMaybe) > > init' :: [a] -> [a] > init' = fromMaybe (error "init': empty list") . foldr f Nothing > where > f x mb = Just $ case mb of > Just xs -> x:xs > Nothing -> [] > > By delaying the pattern match on the Maybe until after the constructor is > applied, we can start building the output with minimal delay (we only need > to look whether there's a next list element to decide whether to cons it to > the front or not). > I'm not sure what you mean by "applying the constructor [Just]," or which function you are forcing to evaluate (after 'applying the constructor'). Obviously, I need to learn more about Haskell's monads and type constructors. > > (2) Is there a way to eliminate the > > post-processing of the lists (i.e., *head* in *last* and *tail* in > > *init*)? > > Not in a clean way. > > Let us consider last first. > > Suppose we had > > last xs = foldr f z xs > > without post-processing. > Since foldr f z [] = z and last [] = error "Prelude.last: empty list", > we must have z = error "...". > Now last (... x:[]) = x and > foldr f z (... x:[]) = ... (f x z) > > So f x y = y if y is not error "..." and f x (error "...") = x, that means > f would have to find out whether its second argument is a specific error > and return its first argument in that case, otherwise its second argument. > It's possible to do that, but very unclean. > That's helpful. I was trying to *name* a list at a particular stage of construction, and it failed for just this reason. -------------- next part -------------- An HTML attachment was scrubbed... URL: http://www.haskell.org/pipermail/beginners/attachments/20100715/1255c1cf/attachment-0001.html ------------------------------ Message: 6 Date: Thu, 15 Jul 2010 10:06:01 -0400 From: Patrick LeBoutillier <patrick.leboutill...@gmail.com> Subject: Re: [Haskell-beginners] Thompson Exercise 9.13 To: Daniel Fischer <daniel.is.fisc...@web.de> Cc: beginners@haskell.org Message-ID: <aanlktinksblcpyoffansulhwlii5l3jt5gnnjayi3...@mail.gmail.com> Content-Type: text/plain; charset=ISO-8859-1 Hi, >> >> *last* :: [a] -> a >> last xs = head $ foldr f [] xs >> where f :: a -> [a] -> [a] >> f x [] = [x] >> f x ys = ys ++ [x] > a) in the second branch of f, you don't actually need to concatenate, > > f x [] = [x] > f _ ys = ys > > works too, but is faster. Why is it faster? I thought that the laziness would cause the concatenation not to be evaluated at all since we are taking the head of the list. Is that not the case? Thanks, Patrick > > b) you can get much faster by delaying the pattern match, > > f x ys = (case ys of { [] -> x; y:_ -> y }) : [] > >> >> *init* :: [a] -> [a] >> init xs = tail $ foldr f [] xs >> where f :: a -> [a] -> [a] >> f x [] = [x] >> f x (y:xs) = y : x : xs > > Correct too, but again not very efficient since it has to find the last > element and bubble it to the front. > > Much faster: > > import Data.Maybe (fromMaybe) > > init' :: [a] -> [a] > init' = fromMaybe (error "init': empty list") . foldr f Nothing > where > f x mb = Just $ case mb of > Just xs -> x:xs > Nothing -> [] > > By delaying the pattern match on the Maybe until after the constructor is > applied, we can start building the output with minimal delay (we only need > to look whether there's a next list element to decide whether to cons it to > the front or not). > >> >> Now, these seemed to be hard questions. So, I have three questions: (1) >> are these correct? They work on test cases, and I *did* do some quick >> proofs. They seem okay. > > They are correct for finite lists, unzip and init above won't return on > infinite lists (last shouldn't, so that's correct for infinite lists too). > They are not, strictly speaking, correct for infinite lists. But that is > way beyond beginner territory :) > >> (2) Is there a way to eliminate the >> post-processing of the lists (i.e., *head* in *last* and *tail* in >> *init*)? > > Not in a clean way. > > Let us consider last first. > > Suppose we had > > last xs = foldr f z xs > > without post-processing. > Since foldr f z [] = z and last [] = error "Prelude.last: empty list", > we must have z = error "...". > Now last (... x:[]) = x and > foldr f z (... x:[]) = ... (f x z) > > So f x y = y if y is not error "..." and f x (error "...") = x, that means > f would have to find out whether its second argument is a specific error > and return its first argument in that case, otherwise its second argument. > It's possible to do that, but very unclean. > > For init, the situation is similar, the value for the empty list case > supplied to foldr must be an error and the combining function needs to know > whether its second argument is an error and do things accordingly. > >> (3) Why the complex answers in the list archives? Am I missing >> something? > > Don't know. In part, because beginners didn't find the easiest ways, I > suppose, in part because it's not too easy to give efficient > implementations with foldr. > > _______________________________________________ > Beginners mailing list > Beginners@haskell.org > http://www.haskell.org/mailman/listinfo/beginners > -- ===================== Patrick LeBoutillier Rosemère, Québec, Canada ------------------------------ _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners End of Beginners Digest, Vol 25, Issue 35 *****************************************