module Control.Applicative.Backwards where
import Prelude hiding (foldr, foldr1, foldl, foldl1)
import Control.Applicative
import Data.Foldable
import Data.Traversable
newtype Backwards f a = Backwards { forwards :: f a }
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) = foldl1 f t
foldl1 f (Backwards t) = foldr1 f t
instance (Traversable f) => Traversable (Backwards f) where
traverse f (Backwards t) = fmap Backwards (traverse f t)
sequenceA (Backwards t) = fmap Backwards (sequenceA t)