{-# 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 #! :: forall meas vert horiz height width a xl xu lower upper. (Measure meas, C vert, C horiz, Indexed height, Indexed width, Floating a) => Matrix (Array pack property) xl xu lower upper meas vert horiz height width a -> (Index height, Index width) -> a (#!) a :: Matrix (Array pack property) xl xu lower upper meas vert horiz height width a a@(ArrMatrix.Array OmniArray pack property lower upper meas vert horiz height width a _) = ArrayMatrix pack property lower upper meas vert horiz height width a -> (Index height, Index width) -> a forall meas vert horiz height width a pack property lower upper. (Measure meas, C vert, C horiz, Indexed height, Indexed width, Floating a) => ArrayMatrix pack property lower upper meas vert horiz height width a -> (Index height, Index width) -> a (ArrIndexed.#!) Matrix (Array pack property) xl xu lower upper meas vert horiz height width a ArrayMatrix pack property lower upper meas vert horiz height width a a instance Indexed Matrix.Scale where Matrix.Scale height sh a a #! :: forall meas vert horiz height width a xl xu lower upper. (Measure meas, C vert, C horiz, Indexed height, Indexed width, Floating a) => Matrix Scale xl xu lower upper meas vert horiz height width a -> (Index height, Index width) -> a #! (Index height i,Index width j) = if height -> Index height -> Int forall sh. Indexed sh => sh -> Index sh -> Int Shape.offset height sh Index height i Int -> Int -> Bool forall a. Eq a => a -> a -> Bool == height -> Index height -> Int forall sh. Indexed sh => sh -> Index sh -> Int Shape.offset height sh Index height Index width j then a a else a forall a. Floating a => a zero instance Indexed Matrix.Permutation where Matrix.Permutation (Permutation Vector (Shape height) (Element height) perm) #! :: forall meas vert horiz height width a xl xu lower upper. (Measure meas, C vert, C horiz, Indexed height, Indexed width, Floating a) => Matrix Permutation xl xu lower upper meas vert horiz height width a -> (Index height, Index width) -> a #! (Index height i,Index width j) = let psh :: Shape height psh@(Perm.Shape height sh) = Vector (Shape height) (Element height) -> Shape height forall sh a. Array sh a -> sh Array.shape Vector (Shape height) (Element height) perm reindex :: Index height -> Element height reindex = Shape height -> Int -> Index (Shape height) forall sh. InvIndexed sh => sh -> Int -> Index sh Shape.indexFromOffset Shape height psh (Int -> Element height) -> (Index height -> Int) -> Index height -> Element height forall b c a. (b -> c) -> (a -> b) -> a -> c . height -> Index height -> Int forall sh. Indexed sh => sh -> Index sh -> Int Shape.offset height sh in if Vector (Shape height) (Element height) perm Vector (Shape height) (Element height) -> Index (Shape height) -> Element height forall sh a. (Indexed sh, Storable a) => Array sh a -> Index sh -> a ! Index height -> Element height reindex Index height i Element height -> Element height -> Bool forall a. Eq a => a -> a -> Bool == Index height -> Element height reindex Index height Index width j then a forall a. Floating a => a one else a forall a. Floating a => a zero