
I recently was writing code long these lines. f x = p1 x || p2 x || ... || pn x I would have liked to write that in pointfree form but couldn't find a library function to do it. I created this. disj :: [a -> Bool] -> a -> Bool disj ps = (\x -> or $ map ($x) ps) disj2 p1 p2 = disj [p1, p2] disj3 p1 p2 p3 = disj [p1, p2] disj4 p1 p2 p3 p4 = disj [p1, p2] ... With that I can write my function as follows. f = disj pi p2 p3 ... pn Is there a standard way to do this? * -- Russ*

On Thu, Dec 9, 2010 at 6:02 PM, Russ Abbott
I recently was writing code long these lines.
f x = p1 x || p2 x || ... || pn x
I would have liked to write that in pointfree form but couldn't find a library function to do it.
I created this.
disj :: [a -> Bool] -> a -> Bool disj ps = (\x -> or $ map ($x) ps)
disj2 p1 p2 = disj [p1, p2] disj3 p1 p2 p3 = disj [p1, p2] disj4 p1 p2 p3 p4 = disj [p1, p2] ...
With that I can write my function as follows.
f = disj pi p2 p3 ... pn
Is there a standard way to do this?
Assuming you have in instance of Applicative for ((->) r) in scope: (<||>) :: (r -> Bool) -> (r -> Bool) -> (r -> Bool) (<||>) = liftA2 (||) then you could say: f = p1 <||> p2 <||> p3 ... Antoine

On Thu, Dec 9, 2010 at 6:13 PM, Antoine Latter
On Thu, Dec 9, 2010 at 6:02 PM, Russ Abbott
wrote: I recently was writing code long these lines.
f x = p1 x || p2 x || ... || pn x
I would have liked to write that in pointfree form but couldn't find a library function to do it.
I created this.
disj :: [a -> Bool] -> a -> Bool disj ps = (\x -> or $ map ($x) ps)
disj2 p1 p2 = disj [p1, p2] disj3 p1 p2 p3 = disj [p1, p2] disj4 p1 p2 p3 p4 = disj [p1, p2] ...
With that I can write my function as follows.
f = disj pi p2 p3 ... pn
Is there a standard way to do this?
Assuming you have in instance of Applicative for ((->) r) in scope:
(<||>) :: (r -> Bool) -> (r -> Bool) -> (r -> Bool) (<||>) = liftA2 (||)
then you could say:
f = p1 <||> p2 <||> p3 ...
And if you're not interested in playing tricks with liftA2 there's always: p1 <||> p2 = \x -> p1 x || p2 x Antoine

We can use a standard trick for poly-variadic functions. {-# LANGUAGE FlexibleInstances #-} class PolyDisj t where disj :: Bool -> t instance PolyDisj Bool where disj x = x instance PolyDisj t => PolyDisj (Bool -> t) where disj x y = disj (x || y) And a test: *Main> disj False False False :: Bool False *Main> disj False False False True :: Bool True You need to somehow give the expression a type otherwise it won't know which instance to use. Edward

On 10/12/10 10:02, Russ Abbott wrote:
I recently was writing code long these lines.
f x = p1 x || p2 x || ... || pn x
I would have liked to write that in pointfree form but couldn't find a library function to do it.
I created this.
disj :: [a -> Bool] -> a -> Bool disj ps = (\x -> or $ map ($x) ps)
disj2 p1 p2 = disj [p1, p2] disj3 p1 p2 p3 = disj [p1, p2] disj4 p1 p2 p3 p4 = disj [p1, p2] ...
With that I can write my function as follows.
f = disj pi p2 p3 ... pn
Is there a standard way to do this? / -- Russ/
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
disj = fmap or . sequence -- Tony Morris http://tmorris.net/
participants (4)
-
Antoine Latter
-
Edward Z. Yang
-
Russ Abbott
-
Tony Morris