As an aside, the Union constraint on epsilon/gepsilon is only needed for the :+: case, you can search products just fine with any old contravariant functor, as you'd expect given the existence of the Applicative.
-Edward
Here is a considerably longer worked example using the analogy to J, borrowing heavily from Wadler:As J, this doesn't really add any power, but perhaps when used with non-representable functors like Equivalence/Comparison you can do something more interesting.-- Used for Hilbert{-# LANGUAGE DefaultSignatures, TypeOperators #-}
-- Used for Representable{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleContexts, FlexibleInstances #-}module Search whereimport Control.Applicativeimport Data.Function (on)import Data.Functor.Contravariantimport GHC.Generics -- for Hilbertnewtype Search f a = Search { optimum :: f a -> a }instance Contravariant f => Functor (Search f) wherefmap f (Search g) = Search $ f . g . contramap f
instance Contravariant f => Applicative (Search f) wherepure a = Search $ \_ -> aSearch fs <*> Search as = Search $ \k ->let go f = f (as (contramap f k))in go (fs (contramap go k))instance Contravariant f => Monad (Search f) wherereturn a = Search $ \_ -> aSearch ma >>= f = Search $ \k ->optimum (f (ma (contramap (\a -> optimum (f a) k) k))) k
class Contravariant f => Union f whereunion :: Search f a -> Search f a -> Search f ainstance Union Predicate whereunion (Search ma) (Search mb) = Search $ \ p -> case ma p ofa | getPredicate p a -> a| otherwise -> mb p
instance Ord r => Union (Op r) whereunion (Search ma) (Search mb) = Search $ \ f -> leta = ma fb = mb fin if getOp f a >= getOp f b then a else bboth :: Union f => a -> a -> Search f aboth = on union pure
fromList :: Union f => [a] -> Search f afromList = foldr1 union . map return
class Contravariant f => Neg f whereneg :: f a -> f a
instance Neg Predicate whereneg (Predicate p) = Predicate (not . p)
instance Num r => Neg (Op r) whereneg (Op f) = Op (negate . f)
pessimum :: Neg f => Search f a -> f a -> apessimum m p = optimum m (neg p)
forsome :: Search Predicate a -> (a -> Bool) -> Boolforsome m p = p (optimum m (Predicate p))forevery :: Search Predicate a -> (a -> Bool) -> Boolforevery m p = p (pessimum m (Predicate p))member :: Eq a => a -> Search Predicate a -> Boolmember a x = forsome x (== a)each :: (Union f, Bounded a, Enum a) => Search f aeach = fromList [minBound..maxBound]bit :: Union f => Search f Boolbit = fromList [False,True]cantor :: Union f => Search f [Bool]cantor = sequence (repeat bit)least :: (Int -> Bool) -> Intleast p = head [ i | i <- [0..], p i ]infixl 4 -->(-->) :: Bool -> Bool -> Boolp --> q = not p || qfan :: Eq r => ([Bool] -> r) -> Intfan f = least $ \ n ->forevery cantor $ \x ->forevery cantor $ \y ->(take n x == take n y) --> (f x == f y)-- a length check that can handle infinite listscompareLength :: [a] -> Int -> OrderingcompareLength xs n = case drop (n - 1) xs of[] -> LT[_] -> EQ_ -> GT
-- Now, lets leave Haskell 98 behind-- Using the new GHC generics to derive versions of Hilbert's epsilonclass GHilbert t wheregepsilon :: Union f => Search f (t a)class Hilbert a whereepsilon :: Union f => Search f adefault epsilon :: (Union f, GHilbert (Rep a), Generic a) => Search f aepsilon = fmap to gepsiloninstance GHilbert U1 wheregepsilon = return U1instance (GHilbert f, GHilbert g) => GHilbert (f :*: g) wheregepsilon = liftA2 (:*:) gepsilon gepsiloninstance (GHilbert f, GHilbert g) => GHilbert (f :+: g) wheregepsilon = fmap L1 gepsilon `union` fmap R1 gepsiloninstance GHilbert a => GHilbert (M1 i c a) wheregepsilon = fmap M1 gepsiloninstance Hilbert a => GHilbert (K1 i a) wheregepsilon = fmap K1 epsiloninstance Hilbert ()instance (Hilbert a, Hilbert b) => Hilbert (a, b)instance (Hilbert a, Hilbert b, Hilbert c) => Hilbert (a, b, c)instance (Hilbert a, Hilbert b, Hilbert c, Hilbert d) =>Hilbert (a, b, c, d)instance (Hilbert a, Hilbert b, Hilbert c, Hilbert d, Hilbert e) =>Hilbert (a, b, c, d, e)instance Hilbert Boolinstance Hilbert Orderinginstance Hilbert a => Hilbert [a]instance Hilbert a => Hilbert (Maybe a)instance (Hilbert a, Hilbert b) => Hilbert (Either a b)instance Hilbert Char whereepsilon = eachinstance (Union f, Hilbert a) => Hilbert (Search f a) whereepsilon = fmap fromList epsilonsearch :: (Union f, Hilbert a) => f a -> asearch = optimum epsilonfind :: Hilbert a => (a -> Bool) -> afind = optimum epsilon . Predicateevery :: Hilbert a => (a -> Bool) -> Boolevery = forevery epsilonexists :: Hilbert a => (a -> Bool) -> Boolexists = forsome epsilon-- and MPTCs/Fundeps to define representable contravariant functors:
class Contravariant f => Representable f r | f -> r whererepresent :: f a -> a -> rtally :: (a -> r) -> f ainstance Representable (Op r) r whererepresent (Op f) = ftally = Opinstance Representable Predicate Bool whererepresent (Predicate p) = ptally = Predicatesupremum :: Representable f r => Search f a -> (a -> r) -> rsupremum m p = p (optimum m (tally p))infimum :: (Representable f r, Neg f) => Search f a -> (a -> r) -> rinfimum m p = p (pessimum m (tally p))A few toy examples:ghci> supremum (fromList [1..10] :: Search (Op Int) Int) id10ghci> find (=='a')'a'ghci> fan (!!4)5ghci> find (\xs -> compareLength xs 10 == EQ && (xs !! 4) == 'a')"\NUL\NUL\NUL\NULa\NUL\NUL\NUL\NUL\NUL"-Edward