#if __GLASGOW_HASKELL__ >= 702
#endif
#if __GLASGOW_HASKELL__ >= 706
#endif
#if __GLASGOW_HASKELL__ >= 710
#endif
module Control.Applicative.Backwards (
Backwards(..),
) where
import Data.Functor.Classes
#if MIN_VERSION_base(4,12,0)
import Data.Functor.Contravariant
#endif
import Prelude hiding (foldr, foldr1, foldl, foldl1, null, length)
import Control.Applicative
import Data.Foldable
import Data.Traversable
newtype Backwards f a = Backwards { forwards :: f a }
instance (Eq1 f) => Eq1 (Backwards f) where
liftEq eq (Backwards x) (Backwards y) = liftEq eq x y
instance (Ord1 f) => Ord1 (Backwards f) where
liftCompare comp (Backwards x) (Backwards y) = liftCompare comp x y
instance (Read1 f) => Read1 (Backwards f) where
liftReadsPrec rp rl = readsData $
readsUnaryWith (liftReadsPrec rp rl) "Backwards" Backwards
instance (Show1 f) => Show1 (Backwards f) where
liftShowsPrec sp sl d (Backwards x) =
showsUnaryWith (liftShowsPrec sp sl) "Backwards" d x
instance (Eq1 f, Eq a) => Eq (Backwards f a) where (==) = eq1
instance (Ord1 f, Ord a) => Ord (Backwards f a) where compare = compare1
instance (Read1 f, Read a) => Read (Backwards f a) where readsPrec = readsPrec1
instance (Show1 f, Show a) => Show (Backwards f a) where showsPrec = showsPrec1
instance (Functor f) => Functor (Backwards f) where
fmap f (Backwards a) = Backwards (fmap f a)
instance (Applicative f) => Applicative (Backwards f) where
pure a = Backwards (pure a)
Backwards f <*> Backwards a = Backwards (a <**> f)
instance (Alternative f) => Alternative (Backwards f) where
empty = Backwards empty
Backwards x <|> Backwards y = Backwards (x <|> y)
instance (Foldable f) => Foldable (Backwards f) where
foldMap f (Backwards t) = foldMap f t
foldr f z (Backwards t) = foldr f z t
foldl f z (Backwards t) = foldl f z t
foldr1 f (Backwards t) = foldr1 f t
foldl1 f (Backwards t) = foldl1 f t
#if MIN_VERSION_base(4,8,0)
null (Backwards t) = null t
length (Backwards t) = length t
#endif
instance (Traversable f) => Traversable (Backwards f) where
traverse f (Backwards t) = fmap Backwards (traverse f t)
sequenceA (Backwards t) = fmap Backwards (sequenceA t)
#if MIN_VERSION_base(4,12,0)
instance Contravariant f => Contravariant (Backwards f) where
contramap f = Backwards . contramap f . forwards
#endif