{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} module LinearAlgebra.TypedSpaces.Classes ( Isomorphism (..) , CZippable (..) , CIndexed (..) , IsList (..) , module CC ) where import GHC.Exts (IsList (..), Constraint) import Control.ConstraintClasses as CC ---------------------------------------------------------------------- class Isomorphism a b where fw :: a -> b bw :: b -> a ---------------------------------------------------------------------- class CFunctor f => CZippable f where czipWith :: (CFun f a, CFun f b, CFun f c) => (a -> b -> c) -> f a -> f b -> f c czipWith3 :: (CFun f a, CFun f b, CFun f c, CFun f d) => (a -> b -> c -> d) -> f a -> f b -> f c -> f d czipWith4 :: (CFun f a, CFun f b, CFun f c, CFun f d, CFun f e) => (a -> b -> c -> d -> e) -> f a -> f b -> f c -> f d -> f e ---------------------------------------------------------------------- class CFunctor f => CIndexed f i | f -> i where type CInd f a :: Constraint type CInd f a = () (!) :: (CFun f a, CInd f a) => f a -> i -> a ----------------------------------------------------------------------