[Haskell] Do the libraries define S' ?
Remi Turk
rturk at science.uva.nl
Thu Jul 8 07:52:42 EDT 2004
On Thu, Jul 08, 2004 at 03:47:08PM +1000, Bernard James POPE wrote:
> I use almost exactly the same thing in my code. And I nearly came
> up with the same names as you! (I have .&&. and .||.)
>
> I find them very useful in guards:
>
> foo x y
> | (this .&&. that) x = ...
>
> I don't believe this kind of abstraction is defined anywhere in the standard
> libraries.
>
> Others have noted that you can rewrite it in terms of the Reader monad.
> Perhaps the Boolean specialistation is useful enough to warrant its own
> definition in a standard library, perhaps Data.Bool?
*digs up his own yet-another-variant*
Though I can't claim to have come up with the same names, I did
invent basically the same thing. I also made a class of it to
make it work with multiple arguments:
*Main> ((==) ||| (>)) 4 3
True
Then I got carried away and made (->) an instance of Num:
*Main> (negate * abs) 5
-25
*Main> ((*) + (^)) 2 3
14
Other "uses" for dup are dup (.) and dup (>>)
--dup :: (b -> b -> b) -> (a -> b) -> (a -> b) -> (a -> b)
dup :: (b1 -> b2 -> c) -> (a -> b1) -> (a -> b2) -> (a -> c)
dup op f g = \x -> f x `op` g x
class Boolish a where
(&&&), (|||):: a -> a -> a
nott :: a -> a
true, false :: a
instance Boolish Bool where
(&&&) = (&&)
(|||) = (||)
nott = not
true = True
false = False
andd, orr :: (Boolish a) => [a] -> a
andd xs = foldr (&&&) true xs
orr xs = foldr (|||) false xs
instance Boolish b => Boolish (a -> b) where
(&&&) = dup (&&&)
(|||) = dup (|||)
nott f = nott . f
true = const true
false = const false
{- I haven't found a use for them yet:
alll (>=) [0..5] 0
seems to be always replacable by
alll (>=0) [0..5] -}
alll, anyy :: (Boolish b) => (a -> b) -> [a] -> b
alll f = andd . map f
anyy f = orr . map f
----- Num (->) ----
-- urgh
instance Num b => Show (a -> b) where
show = error "Unimplementable"
-- urgh again
{- I failed to come up with a class for something like
(===) :: (Boolish b, Eqq c) => (a -> c) -> (a -> c) -> (a -> b)
(all (even /== odd) [0..] looks funny, if (/==) would work
with arbitrary numbers of arguments)
-}
instance Num b => Eq (a -> b) where
(==) = error "Unimplementable"
instance Num b => Num (a -> b) where
(+) = dup (+)
(-) = dup (-)
(*) = dup (*)
signum f = signum . f
abs f = abs . f
fromInteger = const . fromInteger
Groeten,
Remi
--
Nobody can be exactly like me. Even I have trouble doing it.
More information about the Haskell
mailing list