[Haskell] Do the libraries define S' ?

Iavor S. Diatchki diatchki at cse.ogi.edu
Wed Jul 7 14:49:22 EDT 2004


hi,
you can use the reader (environment monad) for this.
combineTest c t1 t2   = liftM2 c t1 t2
lately i have been using 2 combinators to do things like that (thanks to 
Thomas Hallgren for showing me this):

-- a nicer name for fmap (or liftM if one prefers)
(#) :: Functor f => (a -> b) -> f a -> f b

-- a nicer name for "ap" from Monad.hs
(<#) :: Monad m => m (a -> b) -> m a -> m b

then you can write the above as:
cobineTest c t1 t2   = c # t1 <# t2

i like those two as then you don't need all the liftM? functions.
-iavor




Graham Klyne wrote:

> There's a pattern of higher-order function usage I find myself 
> repeatedly wanting to use, exemplified by the following:
>
> [[
> -- combineTest :: (Bool->Bool->Bool) -> (a->Bool) -> (a->Bool) -> 
> (a->Bool)
> combineTest :: (b->c->d) -> (a->b) -> (a->c) -> a -> d
> combineTest c t1 t2 = \a -> c (t1 a) (t2 a)
>
> (.&.) :: (a->Bool) -> (a->Bool) -> (a->Bool)
> (.&.) = combineTest (&&)
>
> (.|.) :: (a->Bool) -> (a->Bool) -> (a->Bool)
> (.|.) = combineTest (||)
>
> t1 = (>0) .&. (<=4) $ 2         -- True
> t2 = (>0) .&. (<=4) $ 5         -- False
> t3 = (>0) .&. (<=4) $ 0         -- False
> t4 = (>0) .|. (<=4) $ 5         -- True
> t5 = (>0) .|. (<=4) $ 0         -- True
>
> tall = and [t1,not t2,not t3,t4,t5]
> ]]
>
> Looking at the fully-generalized type of 'combineTest', and digging 
> around in SPJ's book on implementation of FP languages, I notice that 
> my combineTest function has the same reduction pattern as the S' 
> combinator used as an optimization of SK combinator compilation.
>
> All this (the recurring requirement, and the fact that S' is a very 
> well-known combinator) leads me to think that maybe there is a version 
> of S' somewhere in the standard Haskell libraries.
>
> If there is, where is it please?
>
> If not, should it be in there somewhere?
>
> #g
>
>
> ------------
> Graham Klyne
> For email:
> http://www.ninebynine.org/#Contact
>
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell




More information about the Haskell mailing list