module Control.Monad.Hyper 
	( ContraFunctor(..)
	, Hyper
	, Hyp
	, PHyper(..)
	) where
import Control.Category.Hask
import Control.Functor
import Control.Functor.Fix
import Control.Functor.Contra
import Control.Monad.Instances
import Control.Monad.Parameterized
newtype PHyper h a b = PHyper { runPHyper :: h b -> a } 
instance PFunctor (PHyper h) Hask Hask where
	first f h = PHyper (f . runPHyper h)
instance ContraFunctor h => QFunctor (PHyper h) Hask Hask where
	second g h = PHyper (runPHyper h . contramap g)
instance ContraFunctor h => Bifunctor (PHyper h) Hask Hask Hask where
	bimap f g h = PHyper (f . runPHyper h . contramap g)
instance ContraFunctor h => PPointed (PHyper h) where
	preturn = PHyper . const
instance ContraFunctor h => PApplicative (PHyper h) where
	pap = papPMonad
instance ContraFunctor h => PMonad (PHyper h) where
	pbind k (PHyper h) = PHyper (k . h >>= runPHyper)
type Hyper h a = Fix (PHyper h)
type Hyp e a = Hyper (ContraF e) a