From borgauf at gmail.com Sun Apr 4 04:26:09 2021 From: borgauf at gmail.com (Galaxy Being) Date: Sat, 3 Apr 2021 23:26:09 -0500 Subject: [Haskell-beginners] Type class instance with Num Message-ID: I'm following LYHFGG and I have this class YesNo a where yesno :: a -> Bool instance YesNo Int where yesno 0 = False yesno _ = True but then I have to specify Int here > yesno (5 :: Int) True Just with 5 gives this error Ambiguous type variable ‘a0’ arising from the literal ‘5’ prevents the constraint ‘(Num a0)’ from being solved. Probable fix: use a type annotation to specify what ‘a0’ should be. I tried this instance YesNo (Num a) where yesno 0 = False yesno _ = True but got cryptic errors. What can I do to make yesno take any of Num's numbers? LB -------------- next part -------------- An HTML attachment was scrubbed... URL: From bob at redivi.com Sun Apr 4 04:39:23 2021 From: bob at redivi.com (Bob Ippolito) Date: Sat, 3 Apr 2021 21:39:23 -0700 Subject: [Haskell-beginners] Type class instance with Num In-Reply-To: References: Message-ID: You need something like this: {-# LANGUAGE FlexibleInstances, UndecidableInstances #-} class YesNo a where yesno :: a -> Bool instance (Num a, Eq a) => YesNo a where yesno = (/= 0) The reason this doesn't work without turning on some "scary" flags is that you can easily write code that is ambiguous since typeclasses are open. Open means that some other file can define a data type that has an instance of Num and an instance for YesNo and then there's no obvious choice which instance should be used. If you want a bit more detail, here's a relevant StackOverflow question: https://stackoverflow.com/questions/8877541/how-to-write-an-instance-for-all-types-in-another-type-class On Sat, Apr 3, 2021 at 9:26 PM Galaxy Being wrote: > I'm following LYHFGG and I have this > > class YesNo a where > yesno :: a -> Bool > > instance YesNo Int where > yesno 0 = False > yesno _ = True > > but then I have to specify Int here > > > yesno (5 :: Int) > True > > Just with 5 gives this error > > Ambiguous type variable ‘a0’ arising from the literal ‘5’ > prevents the constraint ‘(Num a0)’ from being solved. > Probable fix: use a type annotation to specify what ‘a0’ should be. > > I tried this > > instance YesNo (Num a) where > yesno 0 = False > yesno _ = True > > but got cryptic errors. What can I do to make yesno take any of Num's > numbers? > > LB > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -------------- next part -------------- An HTML attachment was scrubbed... URL: From borgauf at gmail.com Wed Apr 7 16:47:03 2021 From: borgauf at gmail.com (Galaxy Being) Date: Wed, 7 Apr 2021 11:47:03 -0500 Subject: [Haskell-beginners] Is map (map f) just map f? Message-ID: I'm in Bird's *Thinking Functionally with Haskell* and the topic is natural transformations. He says filter p . map f = map f . filter (p . f) and he has a proof, but one step of the proof he goes from filter p . map f = concat . map (map f) . map (test (p . f)) to filter p . map f = map f . concat . map (test (p . f)) which means concat . map (map f) => map f . concat which means map (map f) = map f ... or I'm getting this step wrong somehow. To begin with, I'm having a hard time comprehending map(map f), Any ideas on how this is possible? LB -------------- next part -------------- An HTML attachment was scrubbed... URL: From tanuki at gmail.com Wed Apr 7 17:06:47 2021 From: tanuki at gmail.com (Akhra Gannon) Date: Wed, 7 Apr 2021 10:06:47 -0700 Subject: [Haskell-beginners] Is map (map f) just map f? In-Reply-To: References: Message-ID: Check the types! map :: (a -> b) -> [a] -> [b] Therefore: map f :: [a] -> [b] map . map :: (a -> b) -> [[a]] -> [[b]] map (map f) :: [[a]] -> [[b]] And, concat :: [[a]] -> [a] Put it all together and you should see how that rewrite works! On Wed, Apr 7, 2021, 9:47 AM Galaxy Being wrote: > I'm in Bird's *Thinking Functionally with Haskell* and the topic is > natural transformations. He says > > filter p . map f = map f . filter (p . f) > > and he has a proof, but one step of the proof he goes from > > filter p . map f = concat . map (map f) . map (test (p . f)) > > to > > filter p . map f = map f . concat . map (test (p . f)) > > which means > > concat . map (map f) => map f . concat > > which means > > map (map f) = map f > > ... or I'm getting this step wrong somehow. To begin with, I'm having a > hard time comprehending map(map f), Any ideas on how this is possible? > > LB > > > > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -------------- next part -------------- An HTML attachment was scrubbed... URL: From borgauf at gmail.com Thu Apr 8 05:03:32 2021 From: borgauf at gmail.com (Galaxy Being) Date: Thu, 8 Apr 2021 00:03:32 -0500 Subject: [Haskell-beginners] Is map (map f) just map f? In-Reply-To: References: Message-ID: So basically I can see that the type definitions would seem to deliver the same thing. I test it > (concat . (map (map (*5)))) [[1],[2],[3]] [5,10,15] > (map (*5) . concat) [[1],[2],[3]] [5,10,15] and can also conclude they give the same answer. So is this an example of referential transparency, i.e., the ability to substitute code and be assured both forms/expressions deliver the same answer? On Wed, Apr 7, 2021 at 12:07 PM Akhra Gannon wrote: > Check the types! > > map :: (a -> b) -> [a] -> [b] > > Therefore: > > map f :: [a] -> [b] > > map . map :: (a -> b) -> [[a]] -> [[b]] > > map (map f) :: [[a]] -> [[b]] > > And, > > concat :: [[a]] -> [a] > > Put it all together and you should see how that rewrite works! > > > On Wed, Apr 7, 2021, 9:47 AM Galaxy Being wrote: > >> I'm in Bird's *Thinking Functionally with Haskell* and the topic is >> natural transformations. He says >> >> filter p . map f = map f . filter (p . f) >> >> and he has a proof, but one step of the proof he goes from >> >> filter p . map f = concat . map (map f) . map (test (p . f)) >> >> to >> >> filter p . map f = map f . concat . map (test (p . f)) >> >> which means >> >> concat . map (map f) => map f . concat >> >> which means >> >> map (map f) = map f >> >> ... or I'm getting this step wrong somehow. To begin with, I'm having a >> hard time comprehending map(map f), Any ideas on how this is possible? >> >> LB >> >> >> >> >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >> > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -------------- next part -------------- An HTML attachment was scrubbed... URL: From utprimum at gmail.com Thu Apr 8 05:55:29 2021 From: utprimum at gmail.com (Ut Primum) Date: Thu, 8 Apr 2021 07:55:29 +0200 Subject: [Haskell-beginners] Is map (map f) just map f? In-Reply-To: References: Message-ID: Yes, thanks to referential transparency you can substitute concat . map (map f) with map f . concat in an expression and be sure you'll always get the same result Il gio 8 apr 2021, 07:04 Galaxy Being ha scritto: > So basically I can see that the type definitions would seem to deliver the > same thing. I test it > > > (concat . (map (map (*5)))) [[1],[2],[3]] > [5,10,15] > > (map (*5) . concat) [[1],[2],[3]] > [5,10,15] > > and can also conclude they give the same answer. So is this an example of > referential transparency, i.e., the ability to substitute code and be > assured both forms/expressions deliver the same answer? > > > On Wed, Apr 7, 2021 at 12:07 PM Akhra Gannon wrote: > >> Check the types! >> >> map :: (a -> b) -> [a] -> [b] >> >> Therefore: >> >> map f :: [a] -> [b] >> >> map . map :: (a -> b) -> [[a]] -> [[b]] >> >> map (map f) :: [[a]] -> [[b]] >> >> And, >> >> concat :: [[a]] -> [a] >> >> Put it all together and you should see how that rewrite works! >> >> >> On Wed, Apr 7, 2021, 9:47 AM Galaxy Being wrote: >> >>> I'm in Bird's *Thinking Functionally with Haskell* and the topic is >>> natural transformations. He says >>> >>> filter p . map f = map f . filter (p . f) >>> >>> and he has a proof, but one step of the proof he goes from >>> >>> filter p . map f = concat . map (map f) . map (test (p . f)) >>> >>> to >>> >>> filter p . map f = map f . concat . map (test (p . f)) >>> >>> which means >>> >>> concat . map (map f) => map f . concat >>> >>> which means >>> >>> map (map f) = map f >>> >>> ... or I'm getting this step wrong somehow. To begin with, I'm having a >>> hard time comprehending map(map f), Any ideas on how this is possible? >>> >>> LB >>> >>> >>> >>> >>> _______________________________________________ >>> Beginners mailing list >>> Beginners at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>> >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >> > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -------------- next part -------------- An HTML attachment was scrubbed... URL: From borgauf at gmail.com Sat Apr 10 03:59:07 2021 From: borgauf at gmail.com (Galaxy Being) Date: Fri, 9 Apr 2021 22:59:07 -0500 Subject: [Haskell-beginners] Strange use of undefined (et al.) in list comprehension Message-ID: I'm looking at Bird's *Thinking Functionally with Haskell *and he gives two list comprehensions, asking under what conditions they deliver the same results [e | x <- xs, p x, y <- ys] [e | x <- xs, y <- ys, p x] First, I'm confused about what is the input and what is the predicate. The y <- ys in the first LC seems to be in a predicate position, and in the second it's a second input after x <- xs with p x in the predicate position . . . confusing me. The answer examples Bird gives are beyond me: They deliver the same result only if ys is a finite list: > [1 | x <- [1,3], even x, y <- undefined] [] > [1 | x <- [1,3], y <- undefined, even x] Exception: Prelude.undefined > [1 | x <- [1,3], y <- [1..], even x] {Interruped} I'm not sure what's being said here, or what points are being made. -------------- next part -------------- An HTML attachment was scrubbed... URL: From mlow at ualberta.ca Sat Apr 10 05:17:20 2021 From: mlow at ualberta.ca (Matthew Low) Date: Fri, 9 Apr 2021 23:17:20 -0600 Subject: [Haskell-beginners] Strange use of undefined (et al.) in list comprehension In-Reply-To: References: Message-ID: > > First, I'm confused about what is the input and what is the predicate The haskell 2010 report ( https://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-420003.11) says that after the | we can have any type of qualifier, which can be 1. a generator (I think you called this the input) 2. a local binding (we don't care about these in your example, there are none) or 3. boolean guards, which are any expression that evaluate to Bool (your predicates). So there isn't really a `predicate postion`, predicates can occur anywhere after the `|`. As for the behaviour, its easiest to see what happens with a regular list of inputs: λ> [(x,y) | x <- [1,2], y <- ['A', 'B']] [(1,'A'),(1,'B'),(2,'A'),(2,'B')] so `y` acts as an inner loop and `x` the outer. > [1 | x <- [1,3], even x, y <- undefined] > Here we start the outer loop over x, and only if x is even, then we loop over y. But x is never even, so we never loop over y, so we never evaluate `undefined` (Haskell is lazy). So essentially filter out all elements of x and are left with [] > [1 | x <- [1,3], y <- undefined, even x] > Now we've moved the guard into the inner loop, after we try to evaluate y. So we blow up trying to do that and GHCi catches the exception [1 | x <- [1,3], y <- [1..], even x] > Similar to the above, the (even x) isn't guarding the evaluation of y, so we're stuck generating all the infinite pairings of x = 1, y = 1... On Fri, Apr 9, 2021 at 9:59 PM Galaxy Being wrote: > I'm looking at Bird's *Thinking Functionally with Haskell *and he gives > two list comprehensions, asking under what conditions they deliver the same > results > > [e | x <- xs, p x, y <- ys] > [e | x <- xs, y <- ys, p x] > > First, I'm confused about what is the input and what is the predicate. The y > <- ys in the first LC seems to be in a predicate position, and in the > second it's a second input after x <- xs with p x in the predicate > position . . . confusing me. > > The answer examples Bird gives are beyond me: > > They deliver the same result only if ys is a finite list: > > > [1 | x <- [1,3], even x, y <- undefined] > [] > > [1 | x <- [1,3], y <- undefined, even x] > Exception: Prelude.undefined > > [1 | x <- [1,3], y <- [1..], even x] > {Interruped} > > I'm not sure what's being said here, or what points are being made. > > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -------------- next part -------------- An HTML attachment was scrubbed... URL: From borgauf at gmail.com Sat Apr 10 15:49:07 2021 From: borgauf at gmail.com (Galaxy Being) Date: Sat, 10 Apr 2021 10:49:07 -0500 Subject: [Haskell-beginners] Strange use of undefined (et al.) in list comprehension In-Reply-To: References: Message-ID: So the Bool predicates and the generators are not purposefully grouped separately -- it just appears that way from the simplistic beginner book examples. But the evaluation is, indeed, left-to-right in that the first example above has even x evaluated directly after x <- [1,3], whereas in the second example the y <- undefined is evaluated directly after x <- [1,3], then the even x, correct? Again, the beginner book examples give the impression that any and all predicates are A) always pushed to the far right, closest to the right bracket, and B) follow no order of application such as being bound to the form closest to the left. So yes, it's visually obvious that there is an outer-inner looping happening when you see the output of two generators doing combinations, but, again, the beginner treatments I've seen make no explicit mention of order in an LC. This is all news to me, but thanks! That's what these forums are for! On Sat, Apr 10, 2021 at 12:18 AM Matthew Low wrote: > First, I'm confused about what is the input and what is the predicate > > The haskell 2010 report ( > https://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-420003.11) > says that after the | we can have any type of qualifier, which can be 1. a > generator (I think you called this the input) 2. a local binding (we don't > care about these in your example, there are none) or 3. boolean guards, > which are any expression that evaluate to Bool (your predicates). So there > isn't really a `predicate postion`, predicates can occur anywhere after the > `|`. > > As for the behaviour, its easiest to see what happens with a regular list > of inputs: > > λ> [(x,y) | x <- [1,2], y <- ['A', 'B']] > [(1,'A'),(1,'B'),(2,'A'),(2,'B')] > > so `y` acts as an inner loop and `x` the outer. > > > [1 | x <- [1,3], even x, y <- undefined] >> > Here we start the outer loop over x, and only if x is even, then we loop > over y. But x is never even, so we never loop over y, so we never evaluate > `undefined` (Haskell is lazy). So essentially filter out all elements of x > and are left with [] > > > [1 | x <- [1,3], y <- undefined, even x] >> > Now we've moved the guard into the inner loop, after we try to evaluate y. > So we blow up trying to do that and GHCi catches the exception > > [1 | x <- [1,3], y <- [1..], even x] >> > Similar to the above, the (even x) isn't guarding the evaluation of y, so > we're stuck generating all the infinite pairings of x = 1, y = 1... > > On Fri, Apr 9, 2021 at 9:59 PM Galaxy Being wrote: > >> I'm looking at Bird's *Thinking Functionally with Haskell *and he gives >> two list comprehensions, asking under what conditions they deliver the same >> results >> >> [e | x <- xs, p x, y <- ys] >> [e | x <- xs, y <- ys, p x] >> >> First, I'm confused about what is the input and what is the predicate. >> The y <- ys in the first LC seems to be in a predicate position, and in >> the second it's a second input after x <- xs with p x in the predicate >> position . . . confusing me. >> >> The answer examples Bird gives are beyond me: >> >> They deliver the same result only if ys is a finite list: >> >> > [1 | x <- [1,3], even x, y <- undefined] >> [] >> > [1 | x <- [1,3], y <- undefined, even x] >> Exception: Prelude.undefined >> > [1 | x <- [1,3], y <- [1..], even x] >> {Interruped} >> >> I'm not sure what's being said here, or what points are being made. >> >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >> > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mlow at ualberta.ca Sat Apr 10 19:19:20 2021 From: mlow at ualberta.ca (Matthew Low) Date: Sat, 10 Apr 2021 13:19:20 -0600 Subject: [Haskell-beginners] Strange use of undefined (et al.) in list comprehension In-Reply-To: References: Message-ID: Glad it helped! You might also be interested in the forums at https://discourse.haskell.org/ - there is a dedicated learning topic, which has a question at a bunch of different levels including very beginning. On Sat, Apr 10, 2021 at 9:49 AM Galaxy Being wrote: > So the Bool predicates and the generators are not purposefully grouped > separately -- it just appears that way from the simplistic beginner book > examples. But the evaluation is, indeed, left-to-right in that the first > example above has even x evaluated directly after x <- [1,3], whereas in > the second example the y <- undefined is evaluated directly after x <- > [1,3], then the even x, correct? Again, the beginner book examples give > the impression that any and all predicates are A) always pushed to the far > right, closest to the right bracket, and B) follow no order of application > such as being bound to the form closest to the left. So yes, it's visually > obvious that there is an outer-inner looping happening when you see the > output of two generators doing combinations, but, again, the beginner > treatments I've seen make no explicit mention of order in an LC. This is > all news to me, but thanks! That's what these forums are for! > > > > On Sat, Apr 10, 2021 at 12:18 AM Matthew Low wrote: > >> First, I'm confused about what is the input and what is the predicate >> >> The haskell 2010 report ( >> https://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-420003.11) >> says that after the | we can have any type of qualifier, which can be 1. a >> generator (I think you called this the input) 2. a local binding (we don't >> care about these in your example, there are none) or 3. boolean guards, >> which are any expression that evaluate to Bool (your predicates). So there >> isn't really a `predicate postion`, predicates can occur anywhere after the >> `|`. >> >> As for the behaviour, its easiest to see what happens with a regular list >> of inputs: >> >> λ> [(x,y) | x <- [1,2], y <- ['A', 'B']] >> [(1,'A'),(1,'B'),(2,'A'),(2,'B')] >> >> so `y` acts as an inner loop and `x` the outer. >> >> > [1 | x <- [1,3], even x, y <- undefined] >>> >> Here we start the outer loop over x, and only if x is even, then we loop >> over y. But x is never even, so we never loop over y, so we never evaluate >> `undefined` (Haskell is lazy). So essentially filter out all elements of x >> and are left with [] >> >> > [1 | x <- [1,3], y <- undefined, even x] >>> >> Now we've moved the guard into the inner loop, after we try to evaluate >> y. So we blow up trying to do that and GHCi catches the exception >> >> [1 | x <- [1,3], y <- [1..], even x] >>> >> Similar to the above, the (even x) isn't guarding the evaluation of y, so >> we're stuck generating all the infinite pairings of x = 1, y = 1... >> >> On Fri, Apr 9, 2021 at 9:59 PM Galaxy Being wrote: >> >>> I'm looking at Bird's *Thinking Functionally with Haskell *and he gives >>> two list comprehensions, asking under what conditions they deliver the same >>> results >>> >>> [e | x <- xs, p x, y <- ys] >>> [e | x <- xs, y <- ys, p x] >>> >>> First, I'm confused about what is the input and what is the predicate. >>> The y <- ys in the first LC seems to be in a predicate position, and in >>> the second it's a second input after x <- xs with p x in the predicate >>> position . . . confusing me. >>> >>> The answer examples Bird gives are beyond me: >>> >>> They deliver the same result only if ys is a finite list: >>> >>> > [1 | x <- [1,3], even x, y <- undefined] >>> [] >>> > [1 | x <- [1,3], y <- undefined, even x] >>> Exception: Prelude.undefined >>> > [1 | x <- [1,3], y <- [1..], even x] >>> {Interruped} >>> >>> I'm not sure what's being said here, or what points are being made. >>> >>> _______________________________________________ >>> Beginners mailing list >>> Beginners at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>> >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >> > _______________________________________________ > Beginners mailing list > Beginners at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mlow at ualberta.ca Sat Apr 10 19:26:08 2021 From: mlow at ualberta.ca (Matthew Low) Date: Sat, 10 Apr 2021 13:26:08 -0600 Subject: [Haskell-beginners] Strange use of undefined (et al.) in list comprehension In-Reply-To: References: Message-ID: I missed this question: > But the evaluation is, indeed, left-to-right ... correct? Correct (though note that in the second example, evaluating y <- undefined will throw and exception so (even x) will not be evaluated) On Sat, Apr 10, 2021 at 1:19 PM Matthew Low wrote: > Glad it helped! You might also be interested in the forums at > https://discourse.haskell.org/ - there is a dedicated learning topic, > which has a question at a bunch of different levels including very > beginning. > > On Sat, Apr 10, 2021 at 9:49 AM Galaxy Being wrote: > >> So the Bool predicates and the generators are not purposefully grouped >> separately -- it just appears that way from the simplistic beginner book >> examples. But the evaluation is, indeed, left-to-right in that the first >> example above has even x evaluated directly after x <- [1,3], whereas in >> the second example the y <- undefined is evaluated directly after x <- >> [1,3], then the even x, correct? Again, the beginner book examples give >> the impression that any and all predicates are A) always pushed to the far >> right, closest to the right bracket, and B) follow no order of application >> such as being bound to the form closest to the left. So yes, it's visually >> obvious that there is an outer-inner looping happening when you see the >> output of two generators doing combinations, but, again, the beginner >> treatments I've seen make no explicit mention of order in an LC. This is >> all news to me, but thanks! That's what these forums are for! >> >> >> >> On Sat, Apr 10, 2021 at 12:18 AM Matthew Low wrote: >> >>> First, I'm confused about what is the input and what is the predicate >>> >>> The haskell 2010 report ( >>> https://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-420003.11) >>> says that after the | we can have any type of qualifier, which can be 1. a >>> generator (I think you called this the input) 2. a local binding (we don't >>> care about these in your example, there are none) or 3. boolean guards, >>> which are any expression that evaluate to Bool (your predicates). So there >>> isn't really a `predicate postion`, predicates can occur anywhere after the >>> `|`. >>> >>> As for the behaviour, its easiest to see what happens with a regular >>> list of inputs: >>> >>> λ> [(x,y) | x <- [1,2], y <- ['A', 'B']] >>> [(1,'A'),(1,'B'),(2,'A'),(2,'B')] >>> >>> so `y` acts as an inner loop and `x` the outer. >>> >>> > [1 | x <- [1,3], even x, y <- undefined] >>>> >>> Here we start the outer loop over x, and only if x is even, then we loop >>> over y. But x is never even, so we never loop over y, so we never evaluate >>> `undefined` (Haskell is lazy). So essentially filter out all elements of x >>> and are left with [] >>> >>> > [1 | x <- [1,3], y <- undefined, even x] >>>> >>> Now we've moved the guard into the inner loop, after we try to evaluate >>> y. So we blow up trying to do that and GHCi catches the exception >>> >>> [1 | x <- [1,3], y <- [1..], even x] >>>> >>> Similar to the above, the (even x) isn't guarding the evaluation of y, >>> so we're stuck generating all the infinite pairings of x = 1, y = 1... >>> >>> On Fri, Apr 9, 2021 at 9:59 PM Galaxy Being wrote: >>> >>>> I'm looking at Bird's *Thinking Functionally with Haskell *and he >>>> gives two list comprehensions, asking under what conditions they deliver >>>> the same results >>>> >>>> [e | x <- xs, p x, y <- ys] >>>> [e | x <- xs, y <- ys, p x] >>>> >>>> First, I'm confused about what is the input and what is the predicate. >>>> The y <- ys in the first LC seems to be in a predicate position, and >>>> in the second it's a second input after x <- xs with p x in the >>>> predicate position . . . confusing me. >>>> >>>> The answer examples Bird gives are beyond me: >>>> >>>> They deliver the same result only if ys is a finite list: >>>> >>>> > [1 | x <- [1,3], even x, y <- undefined] >>>> [] >>>> > [1 | x <- [1,3], y <- undefined, even x] >>>> Exception: Prelude.undefined >>>> > [1 | x <- [1,3], y <- [1..], even x] >>>> {Interruped} >>>> >>>> I'm not sure what's being said here, or what points are being made. >>>> >>>> _______________________________________________ >>>> Beginners mailing list >>>> Beginners at haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>>> >>> _______________________________________________ >>> Beginners mailing list >>> Beginners at haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >>> >> _______________________________________________ >> Beginners mailing list >> Beginners at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: