grids-0.4.0.0

Safe HaskellNone
LanguageHaskell2010

Data.Grid.Internal.Transpose

Synopsis

Documentation

type family Permuted (key :: [Nat]) (from :: [Nat]) :: [Nat] where ... Source #

Equations

Permuted '[] _ = '[] 
Permuted (x ': xs) from = (from !! x) ': Permuted xs from 

type ValidPermutation key from = (Sort key == EnumFromTo 0 (Length from - 1)) ?! (((((Text "Malformed permutation hint: " :<>: ShowType key) :$$: (Text "When permuting matrix of size: " :<>: ShowType from)) :$$: (Text "Key must be a permutation of " :<>: ShowType (EnumFromTo 0 (Length from - 1)))) :$$: Text "e.g. the identity permutation for 2x2 is @[0, 1]") :$$: Text "e.g. matrix transpose for 2x2 is @[1, 0]") Source #

permute :: forall (key :: [Nat]) from a invertedKey. (SingI invertedKey, invertedKey ~ InvertKey (EnumFromTo 0 (Length from - 1)) key, ValidPermutation key from, Dimensions from, Dimensions (Permuted key from)) => Grid from a -> Grid (Permuted key from) a Source #

Permute dimensions of a Grid. This is similar to MatLab's permute function

permute requires a type application containing a permutation pattern; The pattern is a re-ordering of the list [0..n] which represents the new dimension order. For example the permutation pattern [1, 2, 0] when applied to the dimensions [4, 5, 6] results in the dimensions [5, 6, 4].

For 2 dimensional matrixes, a permutation using [1, 0] is simply a matrix transpose

λ> small
fromNestedLists
  [[0,1,2]
  ,[3,4,5]
  ,[6,7,8]]

λ> permute @[1, 0] small
fromNestedLists
  [[0,3,6]
  ,[1,4,7]
  ,[2,5,8]]

permuteCoord :: forall (key :: [Nat]) to from. SingI key => Coord from -> Coord to Source #

Permute the dimensions of a coordinate according to a permutation pattern. see permute regarding permutation patterns

transpose :: (KnownNat x, KnownNat y) => Grid '[x, y] a -> Grid '[y, x] a Source #

Transpose a 2 dimensional matrix. Equivalent to:

permute @[1, 0]

type family InvertKey ref key :: [Nat] where ... Source #

Get the inverse of a permutation pattern, used internally

Equations

InvertKey '[] xs = '[] 
InvertKey (n ': ns) xs = FromJust (ElemIndex n xs) ': InvertKey ns xs