linearmap-category-0.6.0.1: Native, complete-ish, matrix-free linear algebra.
Copyright(c) Justus Sagemüller 2022
LicenseGPL v3
Maintainer(@) jsag $ hvl.no
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Math.VectorSpace.DimensionAware.Theorems.MaybeNat

Description

 

Documentation

type family ZipWith (f :: k -> l -> m) (a :: Maybe k) (b :: Maybe l) :: Maybe m where ... Source #

Equations

ZipWith f 'Nothing y = 'Nothing 
ZipWith f x 'Nothing = 'Nothing 
ZipWith f ('Just x) ('Just y) = 'Just (f x y) 

type family ZipWithPlus (a :: Maybe Nat) (b :: Maybe Nat) :: Maybe Nat where ... Source #

Equations

ZipWithPlus 'Nothing y = 'Nothing 
ZipWithPlus x 'Nothing = 'Nothing 
ZipWithPlus ('Just x) ('Just y) = 'Just (x + y) 

type family ZipWithTimes (a :: Maybe Nat) (b :: Maybe Nat) :: Maybe Nat where ... Source #

Equations

ZipWithTimes 'Nothing y = 'Nothing 
ZipWithTimes x 'Nothing = 'Nothing 
ZipWithTimes ('Just x) ('Just y) = 'Just (x * y) 

type family MaybePred (a :: Nat) :: Maybe Nat where ... Source #

Equations

MaybePred 0 = 'Nothing 
MaybePred n = 'Just (n - 1) 

type family BindMaybePred (a :: Maybe Nat) :: Maybe Nat where ... Source #

type TriangularNum (a :: Nat) = (a * (a + 1)) `Div` 2 Source #

justNatSing :: forall (n :: Nat). Sing n -> Sing ('Just n) Source #

succMaybePredSing :: forall n. SNat n -> Sing (MaybePred (n + 1)) Source #

maybePredSing :: forall a. Sing a -> Sing (MaybePred a) Source #

zipWithPlusSing :: forall a b r. Sing a -> Sing b -> Sing (ZipWithPlus a b) Source #

zipWithTimesSing :: forall a b r. Sing a -> Sing b -> Sing (ZipWithTimes a b) Source #

zipWithTimesAssoc :: forall a b c r. Sing a -> Sing b -> Sing c -> (ZipWithTimes a (ZipWithTimes b c) ~ ZipWithTimes (ZipWithTimes a b) c => r) -> r Source #

zipWithTimesCommu :: forall a b r. Sing a -> Sing b -> (ZipWithTimes a b ~ ZipWithTimes b a => r) -> r Source #