module Language.Symantic.Transforming.Trans where

-- |
-- * 'trans_lift' is generally not /surjective/
-- * 'trans_apply' is not /injective/
-- * 'trans_apply' . 'trans_lift' == 'id'
-- * 'trans_lift' . 'trans_apply' /= 'id'
--
-- NOTE: @DefaultSignatures@ can be used
-- when declaring a symantic type class
-- to provide default definition of the methods:
-- implementing their identity transformation
-- in order to avoid boilerplate code
-- when writting 'Trans' instances which
-- do not need to alterate those methods.
class Trans t term where
	-- | Lift a term to the transformer's.
	trans_lift  :: term a -> t term a
	-- | Unlift a term from the transformer's.
	trans_apply :: t term a -> term a
	
	-- | Convenient method to define the identity transformation for a unary symantic method.
	trans_map1 :: (term a -> term b) -> (t term a -> t term b)
	trans_map1 f = trans_lift . f . trans_apply
	
	-- | Convenient method to define the identity transformation for a binary symantic method.
	trans_map2
	 :: (term a -> term b -> term c)
	 -> (t term a -> t term b -> t term c)
	trans_map2 f e1 e2 = trans_lift (trans_apply e1 `f` trans_apply e2)
	
	-- | Convenient method to define the identity transformation for a ternary symantic method.
	trans_map3
	 :: (term a -> term b -> term c -> term d)
	 -> (t term a -> t term b -> t term c -> t term d)
	trans_map3 f e1 e2 e3 = trans_lift $ f (trans_apply e1) (trans_apply e2) (trans_apply e3)

-- | Closed type family extracting the term
-- upon which a transformer is applied.
--
-- This is useful to write default associated types in symantics.
type family Term_of_Trans (term :: * -> *) :: (* -> *) where
	Term_of_Trans (t term) = term