{-# LANGUAGE AllowAmbiguousTypes #-} module Pandora.Paradigm.Structure.Ability.Rotatable where import Pandora.Pattern.Category ((.)) import Pandora.Paradigm.Primary.Functor.Tagged (Tagged (Tag)) class Rotatable f t where type Rotational (f :: k) (t :: * -> *) a rotation :: Tagged f (t a) -> Rotational f t a rotate :: forall f t a . Rotatable f t => t a -> Rotational f t a rotate :: t a -> Rotational f t a rotate = Tagged f (t a) -> Rotational f t a forall k (f :: k) (t :: * -> *) a. Rotatable f t => Tagged f (t a) -> Rotational f t a rotation (Tagged f (t a) -> Rotational f t a) -> (t a -> Tagged f (t a)) -> t a -> Rotational f t a forall (m :: * -> * -> *) b c a. Category m => m b c -> m a b -> m a c . forall a. a -> Tagged f a forall k (tag :: k) a. a -> Tagged tag a Tag @f