{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 708
{-# LANGUAGE Trustworthy #-}
#elif __GLASGOW_HASKELL >= 704
{-# LANGUAGE Unsafe #-}
#endif
{-# LANGUAGE ScopedTypeVariables #-}
module Data.Profunctor.Unsafe
(
Profunctor(..)
) where
import Control.Arrow
import Control.Category
import Control.Comonad (Cokleisli(..))
import Control.Monad (liftM)
import Data.Bifunctor.Biff (Biff(..))
import Data.Bifunctor.Clown (Clown(..))
import Data.Bifunctor.Joker (Joker(..))
import Data.Bifunctor.Product (Product(..))
import Data.Bifunctor.Tannen (Tannen(..))
#if __GLASGOW_HASKELL__ < 710
import Data.Functor
#endif
import Data.Functor.Contravariant (Contravariant(..))
import Data.Tagged
import Prelude hiding (id,(.),sequence)
#if __GLASGOW_HASKELL__ >= 708
import Data.Coerce
#else
import Unsafe.Coerce
#endif
{-# ANN module "Hlint: ignore Redundant lambda" #-}
{-# ANN module "Hlint: ignore Collapse lambdas" #-}
infixr 9 #.
infixl 8 .#
class Profunctor p where
dimap :: (a -> b) -> (c -> d) -> p b c -> p a d
dimap f g = lmap f . rmap g
{-# INLINE dimap #-}
lmap :: (a -> b) -> p b c -> p a c
lmap f = dimap f id
{-# INLINE lmap #-}
rmap :: (b -> c) -> p a b -> p a c
rmap = dimap id
{-# INLINE rmap #-}
#if __GLASGOW_HASKELL__ >= 708
( #. ) :: Coercible c b => (b -> c) -> p a b -> p a c
#else
( #. ) :: (b -> c) -> p a b -> p a c
#endif
( #. ) = \f -> \p -> p `seq` rmap f p
{-# INLINE ( #. ) #-}
#if __GLASGOW_HASKELL__ >= 708
( .# ) :: Coercible b a => p b c -> (a -> b) -> p a c
#else
( .# ) :: p b c -> (a -> b) -> p a c
#endif
( .# ) = \p -> p `seq` \f -> lmap f p
{-# INLINE ( .# ) #-}
#if __GLASGOW_HASKELL__ >= 708
{-# MINIMAL dimap | (lmap, rmap) #-}
#endif
instance Profunctor (->) where
dimap ab cd bc = cd . bc . ab
{-# INLINE dimap #-}
lmap = flip (.)
{-# INLINE lmap #-}
rmap = (.)
{-# INLINE rmap #-}
#if __GLASGOW_HASKELL__ >= 708
( #. ) _ = coerce (\x -> x :: b) :: forall a b. Coercible b a => a -> b
( .# ) pbc _ = coerce pbc
#else
( #. ) _ = unsafeCoerce
( .# ) pbc _ = unsafeCoerce pbc
#endif
{-# INLINE ( #. ) #-}
{-# INLINE ( .# ) #-}
instance Profunctor Tagged where
dimap _ f (Tagged s) = Tagged (f s)
{-# INLINE dimap #-}
lmap _ = retag
{-# INLINE lmap #-}
rmap = fmap
{-# INLINE rmap #-}
#if __GLASGOW_HASKELL__ >= 708
( #. ) _ = coerce (\x -> x :: b) :: forall a b. Coercible b a => a -> b
#else
( #. ) _ = unsafeCoerce
#endif
{-# INLINE ( #. ) #-}
Tagged s .# _ = Tagged s
{-# INLINE ( .# ) #-}
instance Monad m => Profunctor (Kleisli m) where
dimap f g (Kleisli h) = Kleisli (liftM g . h . f)
{-# INLINE dimap #-}
lmap k (Kleisli f) = Kleisli (f . k)
{-# INLINE lmap #-}
rmap k (Kleisli f) = Kleisli (liftM k . f)
{-# INLINE rmap #-}
#if __GLASGOW_HASKELL__ >= 708
( .# ) pbc _ = coerce pbc
#else
( .# ) pbc _ = unsafeCoerce pbc
#endif
{-# INLINE ( .# ) #-}
instance Functor w => Profunctor (Cokleisli w) where
dimap f g (Cokleisli h) = Cokleisli (g . h . fmap f)
{-# INLINE dimap #-}
lmap k (Cokleisli f) = Cokleisli (f . fmap k)
{-# INLINE lmap #-}
rmap k (Cokleisli f) = Cokleisli (k . f)
{-# INLINE rmap #-}
#if __GLASGOW_HASKELL__ >= 708
( #. ) _ = coerce (\x -> x :: b) :: forall a b. Coercible b a => a -> b
#else
( #. ) _ = unsafeCoerce
#endif
{-# INLINE ( #. ) #-}
instance Contravariant f => Profunctor (Clown f) where
lmap f (Clown fa) = Clown (contramap f fa)
{-# INLINE lmap #-}
rmap _ (Clown fa) = Clown fa
{-# INLINE rmap #-}
dimap f _ (Clown fa) = Clown (contramap f fa)
{-# INLINE dimap #-}
instance Functor f => Profunctor (Joker f) where
lmap _ (Joker fb) = Joker fb
{-# INLINE lmap #-}
rmap g (Joker fb) = Joker (fmap g fb)
{-# INLINE rmap #-}
dimap _ g (Joker fb) = Joker (fmap g fb)
{-# INLINE dimap #-}
instance (Profunctor p, Functor f, Functor g) => Profunctor (Biff p f g) where
lmap f (Biff p) = Biff (lmap (fmap f) p)
rmap g (Biff p) = Biff (rmap (fmap g) p)
dimap f g (Biff p) = Biff (dimap (fmap f) (fmap g) p)
instance (Profunctor p, Profunctor q) => Profunctor (Product p q) where
lmap f (Pair p q) = Pair (lmap f p) (lmap f q)
{-# INLINE lmap #-}
rmap g (Pair p q) = Pair (rmap g p) (rmap g q)
{-# INLINE rmap #-}
dimap f g (Pair p q) = Pair (dimap f g p) (dimap f g q)
{-# INLINE dimap #-}
( #. ) f (Pair p q) = Pair (f #. p) (f #. q)
{-# INLINE ( #. ) #-}
( .# ) (Pair p q) f = Pair (p .# f) (q .# f)
{-# INLINE ( .# ) #-}
instance (Functor f, Profunctor p) => Profunctor (Tannen f p) where
lmap f (Tannen h) = Tannen (lmap f <$> h)
{-# INLINE lmap #-}
rmap g (Tannen h) = Tannen (rmap g <$> h)
{-# INLINE rmap #-}
dimap f g (Tannen h) = Tannen (dimap f g <$> h)
{-# INLINE dimap #-}
( #. ) f (Tannen h) = Tannen ((f #.) <$> h)
{-# INLINE ( #. ) #-}
( .# ) (Tannen h) f = Tannen ((.# f) <$> h)
{-# INLINE ( .# ) #-}