{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE GADTs #-}
module Numeric.LAPACK.Matrix.Indexed where

import qualified Numeric.LAPACK.Matrix.Array.Indexed as ArrIndexed
import qualified Numeric.LAPACK.Matrix.Extent.Private as Extent
import qualified Numeric.LAPACK.Matrix.Array.Private as ArrMatrix
import qualified Numeric.LAPACK.Matrix.Type.Private as Matrix
import qualified Numeric.LAPACK.Permutation as Perm
import Numeric.LAPACK.Matrix.Type.Private (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 Array
import qualified Data.Array.Comfort.Shape as Shape
import Data.Array.Comfort.Storable ((!))


infixl 9 #!

class (Matrix.Box typ) => Indexed typ where
   (#!) ::
      (Extent.Measure meas, Extent.C vert, Extent.C horiz,
       Shape.Indexed height, Shape.Indexed width, Class.Floating a) =>
      Matrix typ xl xu lower upper meas vert horiz height width a ->
      (Shape.Index height, Shape.Index width) -> a

instance Indexed (ArrMatrix.Array pack property) where
   (#!) a@(ArrMatrix.Array _) = (ArrIndexed.#!) a

instance Indexed Matrix.Scale where
   Matrix.Scale sh a #! (i,j) =
      if Shape.offset sh i == Shape.offset sh j then a else zero

instance Indexed Matrix.Permutation where
   Matrix.Permutation (Permutation perm) #! (i,j) =
      let psh@(Perm.Shape sh) = Array.shape perm
          reindex = Shape.indexFromOffset psh . Shape.offset sh
      in if perm ! reindex i == reindex j then one else zero