blob: 5ce53733967a72a577477021d0352eb403bccc28 (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
|
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
module Data.Array.Nested.Internal.Lemmas where
import Data.Proxy
import Data.Type.Equality
import GHC.TypeLits
import Data.Array.Mixed.Lemmas
import Data.Array.Mixed.Permutation
import Data.Array.Mixed.Shape
import Data.Array.Mixed.Types
import Data.Array.Nested.Internal.Shape
lemRankMapJust :: ShS sh -> Rank (MapJust sh) :~: Rank sh
lemRankMapJust ZSS = Refl
lemRankMapJust (_ :$$ sh') | Refl <- lemRankMapJust sh' = Refl
lemMapJustApp :: ShS sh1 -> Proxy sh2
-> MapJust (sh1 ++ sh2) :~: MapJust sh1 ++ MapJust sh2
lemMapJustApp ZSS _ = Refl
lemMapJustApp (_ :$$ sh) p | Refl <- lemMapJustApp sh p = Refl
lemMapJustTakeLen :: Perm is -> ShS sh -> TakeLen is (MapJust sh) :~: MapJust (TakeLen is sh)
lemMapJustTakeLen PNil _ = Refl
lemMapJustTakeLen (_ `PCons` is) (_ :$$ sh) | Refl <- lemMapJustTakeLen is sh = Refl
lemMapJustTakeLen (_ `PCons` _) ZSS = error "TakeLen of empty"
lemMapJustDropLen :: Perm is -> ShS sh -> DropLen is (MapJust sh) :~: MapJust (DropLen is sh)
lemMapJustDropLen PNil _ = Refl
lemMapJustDropLen (_ `PCons` is) (_ :$$ sh) | Refl <- lemMapJustDropLen is sh = Refl
lemMapJustDropLen (_ `PCons` _) ZSS = error "DropLen of empty"
lemMapJustIndex :: SNat i -> ShS sh -> Index i (MapJust sh) :~: Just (Index i sh)
lemMapJustIndex SZ (_ :$$ _) = Refl
lemMapJustIndex (SS (i :: SNat i')) ((_ :: SNat n) :$$ (sh :: ShS sh'))
| Refl <- lemMapJustIndex i sh
, Refl <- lemIndexSucc (Proxy @i') (Proxy @(Just n)) (Proxy @(MapJust sh'))
, Refl <- lemIndexSucc (Proxy @i') (Proxy @n) (Proxy @sh')
= Refl
lemMapJustIndex _ ZSS = error "Index of empty"
lemMapJustPermute :: Perm is -> ShS sh -> Permute is (MapJust sh) :~: MapJust (Permute is sh)
lemMapJustPermute PNil _ = Refl
lemMapJustPermute (i `PCons` is) sh
| Refl <- lemMapJustPermute is sh
, Refl <- lemMapJustIndex i sh
= Refl
lemKnownMapJust :: forall sh. KnownShS sh => Proxy sh -> Dict KnownShX (MapJust sh)
lemKnownMapJust _ = lemKnownShX (go (knownShS @sh))
where
go :: ShS sh' -> StaticShX (MapJust sh')
go ZSS = ZKX
go (n :$$ sh) = SKnown n :!% go sh
|