{-# LANGUAGE TypeFamilies #-} module Numeric.LAPACK.Matrix.Indexed where import qualified Numeric.LAPACK.Matrix.Plain.Indexed as ArrIndexed import qualified Numeric.LAPACK.Matrix.Array as ArrMatrix import qualified Numeric.LAPACK.Matrix.Type as Type import qualified Numeric.LAPACK.Permutation as Perm import Numeric.LAPACK.Matrix.Type (Matrix) import Numeric.LAPACK.Scalar (one, zero) import Numeric.LAPACK.Permutation.Private (Permutation(Permutation)) import qualified Numeric.Netlib.Class as Class import qualified Data.Array.Comfort.Storable.Unchecked as UArray import qualified Data.Array.Comfort.Shape as Shape import Data.Array.Comfort.Storable ((!)) infixl 9 #! class (Type.Box typ) => Indexed typ where (#!) :: (Class.Floating a) => Matrix typ a -> (Shape.Index (Type.HeightOf typ), Shape.Index (Type.WidthOf typ)) -> a instance (ArrIndexed.Indexed sh) => Indexed (ArrMatrix.Array sh) where ArrMatrix.Array arr #! ij = arr ArrIndexed.#! ij instance (Shape.Indexed size) => Indexed (Type.Scale size) where Type.Scale sh a #! (i,j) = if Shape.offset sh i == Shape.offset sh j then a else zero instance (Shape.Indexed size) => Indexed (Permutation size) where Type.Permutation (Permutation perm) #! (i,j) = let psh@(Perm.Shape sh) = UArray.shape perm reindex = Shape.indexFromOffset psh . Shape.offset sh in if perm ! reindex i == reindex j then one else zero