module Generics.Pointless.Bifctrable where
import Prelude hiding (Functor(..),fmap)
import Generics.Pointless.Bifunctors
import Generics.Pointless.Combinators
data Bifctr (f :: * -> * -> *) where
    BI :: Bifctr BId
    BK :: Bifctr (BConst c)
    BP :: Bifctr BPar
    (:*!|) :: (Bifunctor f,Bifunctor g) => Bifctr f -> Bifctr g -> Bifctr (f :*| g)
    (:+!|) :: (Bifunctor f,Bifunctor g) => Bifctr f -> Bifctr g -> Bifctr (f :+| g)
    (:@!|) :: (Bifunctor f,Bifunctor g) => Bifctr f -> Bifctr g -> Bifctr (f :@| g)
class (Bifunctor f) => Bifctrable (f :: * -> * -> *) where
    bctr :: Bifctr f
instance Bifctrable BId where
    bctr = BI
instance Bifctrable (BConst c) where
    bctr = BK
instance Bifctrable BPar where
    bctr = BP
instance (Bifunctor f,Bifctrable f,Bifunctor g,Bifctrable g) => Bifctrable (f :*| g) where
    bctr = (:*!|) bctr bctr
instance (Bifunctor f,Bifctrable f,Bifunctor g,Bifctrable g) => Bifctrable (f :+| g) where
    bctr = (:+!|) bctr bctr
fixB :: Bifctr f -> BFix f
fixB (_::Bifctr f) = (_L :: BFix f)
fctrB :: Bifctrable f => BFix f -> Bifctr f
fctrB (_::BFix f) = bctr :: Bifctr f