{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeOperators #-}

module Data.Invertible.Profunctor where

import Prelude hiding ((.), id, fst, snd, curry)
import qualified Prelude as P
import Data.Invertible.Bijection
import Data.Invertible.Function

-- | Class 'IsoProfunctor' represents a profunctor from @Iso@ -> @Hask@ (?)
--
-- @'dimap' 'id' 'id' ≡ 'id'@
--
-- @
--  'lmap' 'id' ≡ 'id'
--  'rmap' 'id' ≡ 'id'
-- @
--
-- @'dimap' f g ≡ 'lmap' f '.' 'rmap' g@
--
--
-- @
-- 'dimap' (f '.' g) (h '.' i) ≡ 'dimap' g h '.' 'dimap' f i
-- 'lmap' (f '.' g) ≡ 'lmap' g '.' 'lmap' f
-- 'rmap' (f '.' g) ≡ 'rmap' f '.' 'rmap' g
-- @
class IsoProfunctor p where
  dimap :: (a <-> b) -> (c <-> d) -> p b c -> p a d
  dimap f g = (P..) (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 #-}

instance IsoProfunctor (Bijection (->)) where
  dimap f g h = g . h . f