{-# LANGUAGE TypeFamilies #-} module Numeric.LAPACK.Shape where import qualified Data.Array.Comfort.Shape as Shape import Data.Tagged (Tagged) import Data.Ix (Ix) import Control.DeepSeq (NFData, rnf) {- | Class of shapes where indices still make sense if we permute elements. We use this for all matrix factorisations involving permutations or more generally orthogonal transformations, e.g. eigenvalue and singular value, LU and QR decompositions. E.g. say, we have a square matrix with dimension 'Shape.Enumeration Ordering'. Its vector of eigenvalues has the same dimension, but it does not make sense to access the eigenvalues with indices like 'LT' or 'EQ'. Thus 'Shape.Enumeration' is no instance of 'Permutable' (and you should not add an orphan instance). If you want to factor a matrix with a non-permutable shape, you should convert it temporarily to a permutable one, like 'Shape.ZeroBased' (i.e. 'Matrix.ShapeInt') or 'IntIndexed'. The 'Permutable' class has no method, so you could add any shape to it. However, you should use good taste when adding an instance. There is no strict criterion which shape type to add. We tried to use 'ShapeInt' for eigenvalue vectors and 'LiberalSquare's as transformation matrices of eigenvalue decompositions. However, this way, the type checker cannot infer that the product of the factorisation is a strict square. We also tried to use 'Shape.IntIndexed' for eigenvalue vectors with according 'LiberalSquare's transformations. This has also the problem of inferring squares. Additionally, more such transformations lead to nested 'Shape.IntIndexed' wrappers and for 'Matrix.ShapeInt' even the first wrapper is unnecessary. -} class (Shape.C shape) => Permutable shape where instance Permutable Shape.Zero where instance Permutable () where instance (Ix n) => Permutable (Shape.Range n) where instance (Integral n) => Permutable (Shape.Shifted n) where instance (Integral n) => Permutable (Shape.ZeroBased n) where instance (Integral n) => Permutable (Shape.OneBased n) where instance (Integral n) => Permutable (Shape.Cyclic n) where instance (Permutable sh) => Permutable (Shape.Deferred sh) where instance (Permutable sh) => Permutable (Tagged s sh) where {- | This shape type wraps any other array shape type. However, its 'Shape.Indexed' instance just uses zero-based 'Int' indices. Thus it can turn any shape type into a 'Shape.Indexed' one. The main usage is to make an arbitrary shape 'Permutable'. -} newtype IntIndexed sh = IntIndexed {deconsIntIndexed :: sh} deriving (Eq, Show) instance (NFData sh) => NFData (IntIndexed sh) where rnf (IntIndexed sh) = rnf sh instance (Shape.C sh) => Shape.C (IntIndexed sh) where size (IntIndexed sh) = Shape.size sh shapeInt :: (Shape.C sh) => sh -> Shape.ZeroBased Int shapeInt = Shape.ZeroBased . Shape.size instance (Shape.C sh) => Shape.Indexed (IntIndexed sh) where type Index (IntIndexed sh) = Int indices (IntIndexed sh) = take (Shape.size sh) [0 ..] unifiedOffset (IntIndexed sh) = Shape.unifiedOffset (shapeInt sh) unifiedSizeOffset (IntIndexed sh) = Shape.unifiedSizeOffset (shapeInt sh) inBounds (IntIndexed sh) k = Shape.inBounds (Shape.ZeroBased $ Shape.size sh) k instance (Shape.C sh) => Shape.InvIndexed (IntIndexed sh) where unifiedIndexFromOffset (IntIndexed sh) = Shape.unifiedIndexFromOffset (shapeInt sh) instance (Shape.C sh) => Permutable (IntIndexed sh) where