
Is there a nifty way to write filter (\x -> x < 0.5 && x > -0.5) xs without explicitly using x? Maybe arrows? I have a vague understanding that arrows can "send" an argument to more than one computation. -Mike

On Mon, Oct 19, 2009 at 9:49 AM, Michael Mossey
Is there a nifty way to write
filter (\x -> x < 0.5 && x > -0.5) xs
without explicitly using x?
Maybe arrows? I have a vague understanding that arrows can "send" an argument to more than one computation.
Using &&& from Control.Arrow you can write something like file (uncurry (&&) . ((< 0.5) &&& (> -0.5))) xs /M -- Magnus Therning (OpenPGP: 0xAB4DFBA4) magnus@therning.org Jabber: magnus@therning.org http://therning.org/magnus identi.ca|twitter: magthe

On Mon, Oct 19, 2009 at 10:49, Michael Mossey
Is there a nifty way to write
filter (\x -> x < 0.5 && x > -0.5) xs
without explicitly using x?
Maybe arrows? I have a vague understanding that arrows can "send" an argument to more than one computation.
You can do that with arrows like this:
Prelude Control.Arrow> let rangeA x y = ((>x) &&& (

Had you considered list comprehension? [x | x <- xs, x < 0.5 && x > -0.5] Luca.
Date: Mon, 19 Oct 2009 01:49:17 -0700 From: mpm@alumni.caltech.edu To: beginners@haskell.org Subject: [Haskell-beginners] \x -> x < 0.5 && x > -0.5
Is there a nifty way to write
filter (\x -> x < 0.5 && x > -0.5) xs
without explicitly using x?
Maybe arrows? I have a vague understanding that arrows can "send" an argument to more than one computation.
-Mike _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_________________________________________________________________ Use Windows Live Messenger for free on selected mobiles http://clk.atdmt.com/UKM/go/174426567/direct/01/

Michael Mossey wrote:
Is there a nifty way to write
filter (\x -> x < 0.5 && x > -0.5) xs
without explicitly using x?
Maybe arrows? I have a vague understanding that arrows can "send" an argument to more than one computation.
That's a job for the reader monad. Lambda Fu, form 53 - silent reader of truth import Control.Monad import Control.Monad.Reader filter (liftM2 (&&) (< 0.5) (> -0.5)) xs Regards, apfelmus -- http://apfelmus.nfshost.com

Wouldn't it be better to make an instance of the Boolean class for functions, that way you could just write: filter ((< 0.5) && (> -0.5)) xs Not sure about the syntax, as the Haskell site is down. Also it will require that you install and import the Boolean class. One could ask if any of these methods are more readable than the original though. Paul Heinrich Apfelmus wrote:
Michael Mossey wrote:
Is there a nifty way to write
filter (\x -> x < 0.5 && x > -0.5) xs
without explicitly using x?
Maybe arrows? I have a vague understanding that arrows can "send" an argument to more than one computation.
That's a job for the reader monad.
Lambda Fu, form 53 - silent reader of truth
import Control.Monad import Control.Monad.Reader
filter (liftM2 (&&) (< 0.5) (> -0.5)) xs
Regards, apfelmus
-- http://apfelmus.nfshost.com
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Or simply write a function: between :: Ord a => a -> a -> a -> Bool between min max x = x > min && x < max filter (between (-0.5) 0.5) xs Keep it simple, stupid?

Heinrich Apfelmus wrote:
Michael Mossey wrote:
Is there a nifty way to write
filter (\x -> x < 0.5 && x > -0.5) xs
without explicitly using x?
Maybe arrows? I have a vague understanding that arrows can "send" an argument to more than one computation.
That's a job for the reader monad.
Lambda Fu, form 53 - silent reader of truth
import Control.Monad import Control.Monad.Reader
filter (liftM2 (&&) (< 0.5) (> -0.5)) xs
Cool. I realized there was a way to think about this. I haven't used the reader monad in my own projects, but I recall it's one way to pass the same value into several functions: headTail = do h <- head t <- tail return (h,t) headTail "foo" = ('f',"oo") Note also there's no need for runReader or evalReader (at least not that I'm aware of) because unlike other monads, the reader monad is itself a function that takes the state to be read. This could be generalized to headTail2 g = do h <- head t <- tail return $ g h t headTail2 (,) "foo" = ('f',"oo") But this form: do { x <- m1; y <- m2; return $ g x y} is exactly the definition of liftM2. Specifically, liftM2 g m1 m2.

On Mon, Oct 19, 2009 at 12:09:02PM -0700, Michael Mossey wrote:
Note also there's no need for runReader or evalReader (at least not that I'm aware of) because unlike other monads, the reader monad is itself a function that takes the state to be read.
Note that little-r 'reader' is just an informal name for the ((->) e) monad, which is what your code was using. Control.Monad.Reader also provides the big-R 'Reader' type, which is just a newtype wrapper around a little-r reader, and does indeed have a 'runReader' method (which just removes the newtype constructor). That is, newtype Reader r a = Reader { runReader :: r -> a } C.M.Reader also provides ReaderT, a monad transformer version of Reader. -Brent

Brent Yorgey wrote:
Note that little-r 'reader' is just an informal name for the ((->) e) monad, which is what your code was using. Control.Monad.Reader also provides the big-R 'Reader' type, which is just a newtype wrapper around a little-r reader, and does indeed have a 'runReader' method (which just removes the newtype constructor). That is,
newtype Reader r a = Reader { runReader :: r -> a }
C.M.Reader also provides ReaderT, a monad transformer version of Reader.
I thought Control.Monad.Reader also provides the needed instance Monad ((->) r) but this is actually provided by Control.Monad.Instances . Regards, apfelmus -- http://apfelmus.nfshost.com

Michael Mossey schrieb:
Is there a nifty way to write
filter (\x -> x < 0.5 && x > -0.5) xs
without explicitly using x?
Hoogle did not find a function of type: (b -> b -> b) -> (a -> b) -> (a -> b) -> a -> b or (b -> c -> d) -> (a -> b) -> (a -> c) -> a -> d But maybe such a function is worth being added to Data.Function. Cheers Christian

On Mon, Oct 19, 2009 at 12:07:19PM +0200, Christian Maeder wrote:
Michael Mossey schrieb:
Is there a nifty way to write
filter (\x -> x < 0.5 && x > -0.5) xs
without explicitly using x?
Hoogle did not find a function of type:
(b -> b -> b) -> (a -> b) -> (a -> b) -> a -> b
or (b -> c -> d) -> (a -> b) -> (a -> c) -> a -> d
Apparently Hoogle does not know to try unifying m b with a -> b. As others have pointed out, a function of this type (actually, a more general type) does exist, namely, liftM2. -Brent

Michael Mossey wrote:
Is there a nifty way to write
filter (\x -> x < 0.5 && x > -0.5) xs
without explicitly using x?
I'm pretty new to Haskell... are you looking for a *better* way to write this, or is this an exercise in exploring alternatives for the sake of understanding? I'm not seeing any of the proposed alternatives as being as clear as the lambda function, and I'd be surprised (in my ignorance) if any of them were more efficient. -- Carl D Cravens (raven@phoenyx.net) Bad Command! Bad, Bad Command! Sit! Staaaaay...

Carl Cravens wrote:
Michael Mossey wrote:
Is there a nifty way to write
filter (\x -> x < 0.5 && x > -0.5) xs
without explicitly using x?
I'm pretty new to Haskell... are you looking for a *better* way to write this, or is this an exercise in exploring alternatives for the sake of understanding?
Hi Carl, Either one. Let me chime in with some observations from a few months of studying Haskell. (Brent and Apfelmus can probably elaborate on this.) Eliminating variables and working with function combinations has benefits. The one suggestion I've seen here that seems to be right on the money is liftM2 (&&) (< 0.5) (> -0.5) Although that might seem less clear to a beginner, it is actually _more_ clear than the lambda function in some ways. It's easier to work with proof at a more abstract level like this, and strange as it may seem, what I seem to observe in expert users of Haskell is that their brains will pick up what this is doing faster than the lambda function. Or maybe this example is too small to be meaningful, but this kind of abstraction is the direction I want to move in, for there are benefits waiting for me when I arrive. The Parsec library is an example of how concise and elegant code can get when you choose your abstractions carefully. -Mike

Michael Mossey wrote:
Eliminating variables and working with function combinations has benefits. The one suggestion I've seen here that seems to be right on the money is
liftM2 (&&) (< 0.5) (> -0.5)
yep, I might not write it myself, but it's definitely the only one straightforward enough to perhaps justify itself. now for a completely different suggestion; you write
filter (\x -> x < 0.5 && x > -0.5) xs
but as a reader I would find it clearer to switch the order to numerical: filter (\x -> x > -0.5 && x < 0.5) xs (in this particular instance, we can observe numerical properties and even change to (\x -> abs x < 0.5) if we so desire. Which can be written point-free as ((< 0.5) . abs), if you want to.) -Isaac

Am Dienstag 20 Oktober 2009 04:48:50 schrieb Michael Mossey:
Carl Cravens wrote:
Michael Mossey wrote:
Is there a nifty way to write
filter (\x -> x < 0.5 && x > -0.5) xs
without explicitly using x?
I'm pretty new to Haskell... are you looking for a *better* way to write this, or is this an exercise in exploring alternatives for the sake of understanding?
Hi Carl,
Either one.
Let me chime in with some observations from a few months of studying Haskell. (Brent and Apfelmus can probably elaborate on this.)
Eliminating variables and working with function combinations has benefits.
But it's not unconditionally a good thing. If you exaggerate it, it's pure obfuscation. Nevertheless, playing around with eliminating variables and using combinators even beyond the border of obfuscation is a good exercise. You gain understanding and a feeling of when it's better to stop by that.
The one suggestion I've seen here that seems to be right on the money is
liftM2 (&&) (< 0.5) (> -0.5)
May I offer (&&) <$> (< 0.5) <*> (> -0.5) ? It works on Applicative Functors (doesn't need the full force of Monads).
Although that might seem less clear to a beginner, it is actually _more_ clear than the lambda function in some ways. It's easier to work with proof at a more abstract level like this, and strange as it may seem, what I seem to observe in expert users of Haskell is that their brains will pick up what this is doing faster than the lambda function.
In this small example, both are immediately clear, you need more complicated lambda expressions to get a measurable difference :)

Daniel Fischer wrote:
Am Dienstag 20 Oktober 2009 04:48:50 schrieb Michael Mossey:
Eliminating variables and working with function combinations has benefits.
But it's not unconditionally a good thing. If you exaggerate it, it's pure obfuscation. Nevertheless, playing around with eliminating variables and using combinators even beyond the border of obfuscation is a good exercise. You gain understanding and a feeling of when it's better to stop by that.
I think I understand. Another way to put my point is that learning Haskell has trained my eye to notice when a particular variable is flopping around in six different places. I programmed for twenty years or more in imperative languages (in a business setting, not academia) and no one ever said, "Hey we've got too many repetitions of x! Let's see what the underlying abstraction REALLY is."
The one suggestion I've seen here that seems to be right on the money is
liftM2 (&&) (< 0.5) (> -0.5)
May I offer
(&&) <$> (< 0.5) <*> (> -0.5)
? It works on Applicative Functors (doesn't need the full force of Monads).
Although that might seem less clear to a beginner, it is actually _more_ clear than the lambda function in some ways. It's easier to work with proof at a more abstract level like this, and strange as it may seem, what I seem to observe in expert users of Haskell is that their brains will pick up what this is doing faster than the lambda function.
In this small example, both are immediately clear, you need more complicated lambda expressions to get a measurable difference :)
Yeah, pretty small example, but based on what I've read in "Real World Haskell" and "Craft of Functional Programming," the authors find a lot of "strange-looking" (to the imperative programmer's eye) function combinators to be the most natural way of expressing the solution, and from time to time I find my thoughts aligning with them, and I realize how much less thought it takes. This raises the question: is "step by step" thinking the "most natural" way to think about a mathematical problem? My hunch is "no." There are multiple modes of thought, and no reason to eliminate cognitive models that involve imagery, imaginary things moving and sliding through space... or analogies to the more common physical world... or the list is endless. I like the way Haskell resonates with a larger set of thinking styles. Mike

On Tue, Oct 20, 2009 at 5:28 AM, Daniel Fischer
May I offer
(&&) <$> (< 0.5) <*> (> -0.5)
or: import Control.Applicative.Infix between l h = (> l) <^ (&&) ^> (< h) Bas You can find Control.Applicative.Infix in InfixApplicative: http://hackage.haskell.org/package/InfixApplicative

filter ((<=0.5) . abs) xs
On Mon, Oct 19, 2009 at 10:49 AM, Michael Mossey
Is there a nifty way to write
filter (\x -> x < 0.5 && x > -0.5) xs
without explicitly using x?
Maybe arrows? I have a vague understanding that arrows can "send" an argument to more than one computation.
-Mike _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Am Freitag 23 Oktober 2009 16:25:57 schrieb pl:
filter ((<=0.5) . abs) xs
Would be filter ((< 0.5) . abs). Yes, it's fine. However, if the range is not symmetrical about 0, this is not so nice anymore: cap lo hi = filter (\x -> lo < x && x < hi) cap lo hi = filter (liftM2 (&&) (lo <) (< hi)) cap lo hi = filter ((&&) <$> (lo <) <*> (< hi)) cap lo hi = filter ((< halflength) . abs . subtract mid) where mid = (lo+hi)/2 halflength = (hi-lo)/2
On Mon, Oct 19, 2009 at 10:49 AM, Michael Mossey
wrote: Is there a nifty way to write
filter (\x -> x < 0.5 && x > -0.5) xs
without explicitly using x?
Maybe arrows? I have a vague understanding that arrows can "send" an argument to more than one computation.
-Mike

On Fri, Oct 23, 2009 at 10:25 AM, pl
filter ((<=0.5) . abs) xs
pure (&&) <*> (< 0.5) <*> (> -0.5) liftM2 (&&) (< 0.5) (> -0.5) Someone suggested that this was an example of the reader monad but I don't get that.
:i (->) data (->) a b -- Defined in GHC.Prim instance Monad ((->) r) -- Defined in Control.Monad.Instances instance Functor ((->) r) -- Defined in Control.Monad.Instances instance Applicative ((->) a) -- Defined in Control.Applicative
That's what I see working here. -- Darrin

Am Freitag 23 Oktober 2009 17:25:57 schrieb Darrin Thompson:
On Fri, Oct 23, 2009 at 10:25 AM, pl
wrote: filter ((<=0.5) . abs) xs
pure (&&) <*> (< 0.5) <*> (> -0.5)
liftM2 (&&) (< 0.5) (> -0.5)
Someone suggested that this was an example of the reader monad but I don't get that.
It's because ((->) r) *is* the reader monad. Control.Monad.Reader's Reader r a is just that wrapped in a newtype: newtype Reader r a = Reader { runReader :: r -> a }
:i (->)
data (->) a b -- Defined in GHC.Prim instance Monad ((->) r) -- Defined in Control.Monad.Instances instance Functor ((->) r) -- Defined in Control.Monad.Instances instance Applicative ((->) a) -- Defined in Control.Applicative
That's what I see working here.
-- Darrin

On Fri, Oct 23, 2009 at 11:32 AM, Daniel Fischer
It's because ((->) r) *is* the reader monad. Control.Monad.Reader's Reader r a is just that wrapped in a newtype:
newtype Reader r a = Reader { runReader :: r -> a }
So I was thinking: :t runReader $ liftM2 (&&) (Reader (< 0.5)) (Reader (> -0.5)) Thanks. -- Darrin
participants (15)
-
Bas van Dijk
-
Brent Yorgey
-
Carl Cravens
-
Christian Maeder
-
Daniel Fischer
-
Darrin Thompson
-
Heinrich Apfelmus
-
Isaac Dupree
-
Krzysztof Skrzętnicki
-
Luca Ciciriello
-
Magnus Therning
-
Michael Mossey
-
Paul Visschers
-
pl
-
Roel van Dijk