module Numeric.LAPACK.Matrix.Private where import qualified Numeric.LAPACK.Matrix.Layout.Private as Layout import qualified Numeric.LAPACK.Matrix.Extent.Private as Extent import qualified Data.Array.Comfort.Storable.Unchecked as Array import qualified Data.Array.Comfort.Shape as Shape import Data.Array.Comfort.Storable.Unchecked (Array(Array)) import Foreign.ForeignPtr (ForeignPtr) type Full meas vert horiz height width = Array (Layout.Full meas vert horiz height width) type General height width = Array (Layout.General height width) type Tall height width = Array (Layout.Tall height width) type Wide height width = Array (Layout.Wide height width) type LiberalSquare height width = Array (Layout.LiberalSquare height width) type Square sh = Array (Layout.Square sh) type SquareMeas meas height width = Array (Layout.SquareMeas meas height width) argGeneral :: (Layout.Order -> height -> width -> ForeignPtr a -> b) -> (General height width a -> b) argGeneral f (Array (Layout.Full order extent) a) = f order (Extent.height extent) (Extent.width extent) a argSquare :: (Layout.Order -> sh -> ForeignPtr a -> b) -> (Square sh a -> b) argSquare f (Array (Layout.Full order extent) a) = f order (Extent.squareSize extent) a type ShapeInt = Shape.ZeroBased Int shapeInt :: Int -> ShapeInt shapeInt = Shape.ZeroBased mapExtent :: (Extent.Measure measA, Extent.C vertA, Extent.C horizA) => (Extent.Measure measB, Extent.C vertB, Extent.C horizB) => Extent.Map measA vertA horizA measB vertB horizB height width -> Full measA vertA horizA height width a -> Full measB vertB horizB height width a mapExtent f = Array.mapShape $ Layout.fullMapExtent f fromFull :: (Extent.Measure meas, Extent.C vert, Extent.C horiz) => Full meas vert horiz height width a -> General height width a fromFull = mapExtent Extent.toGeneral generalizeTall :: (Extent.Measure meas, Extent.C vert, Extent.C horiz) => Full meas vert Extent.Small height width a -> Full Extent.Size vert horiz height width a generalizeTall = mapExtent Extent.generalizeTall generalizeWide :: (Extent.Measure meas, Extent.C vert, Extent.C horiz) => Full meas Extent.Small horiz height width a -> Full Extent.Size vert horiz height width a generalizeWide = mapExtent Extent.generalizeWide weakenTall :: (Extent.Measure meas, Extent.C vert, Extent.C horiz) => Full meas vert Extent.Small height width a -> Full meas vert horiz height width a weakenTall = mapExtent Extent.weakenTall weakenWide :: (Extent.Measure meas, Extent.C vert, Extent.C horiz) => Full meas Extent.Small horiz height width a -> Full meas vert horiz height width a weakenWide = mapExtent Extent.weakenWide height :: (Extent.Measure meas, Extent.C vert, Extent.C horiz) => Full meas vert horiz height width a -> height height = Layout.fullHeight . Array.shape width :: (Extent.Measure meas, Extent.C vert, Extent.C horiz) => Full meas vert horiz height width a -> width width = Layout.fullWidth . Array.shape revealOrder :: (Extent.Measure meas, Extent.C vert, Extent.C horiz) => Full meas vert horiz height width a -> Either (Array (height,width) a) (Array (width,height) a) revealOrder (Array (Layout.Full order extent) a) = let (h,w) = Extent.dimensions extent in case order of Layout.RowMajor -> Left $ Array (h,w) a Layout.ColumnMajor -> Right $ Array (w,h) a