{-# LANGUAGE TypeFamilies #-} module Numeric.LAPACK.Matrix.Banded.Naive where import qualified Numeric.LAPACK.Matrix.Array as ArrMatrix import qualified Numeric.LAPACK.Matrix.Layout as Layout import qualified Numeric.LAPACK.Matrix.Extent as Extent import qualified Numeric.LAPACK.Matrix as Matrix import Numeric.LAPACK.Matrix.Layout (Order) import qualified Numeric.Netlib.Class as Class import qualified Type.Data.Num.Unary as Unary import qualified Data.Array.Comfort.Storable as Array import qualified Data.Array.Comfort.Shape as Shape import Data.Array.Comfort.Storable ((!)) toFull :: (Unary.Natural sub, Unary.Natural super, Extent.Measure meas, Extent.C vert, Extent.C horiz, Shape.Indexed height, Shape.Indexed width, Class.Floating a) => Matrix.Banded sub super meas vert horiz height width a -> Matrix.Full meas vert horiz height width a toFull = ArrMatrix.lift1 $ \a -> case Array.shape a of shape@(Layout.Banded _offDiag order extent) -> Array.sample (Layout.Full order extent) $ \ix -> let bix = uncurry Layout.InsideBox ix in if Shape.inBounds shape bix then a!bix else 0 forceOrder :: (Unary.Natural sub, Unary.Natural super, Extent.Measure meas, Extent.C vert, Extent.C horiz, Shape.Indexed height, Shape.Indexed width, Class.Floating a) => Order -> Matrix.Banded sub super meas vert horiz height width a -> Matrix.Banded sub super meas vert horiz height width a forceOrder newOrder = ArrMatrix.lift1 $ \a -> case Array.shape a of shape -> Array.sample (shape{Layout.bandedOrder = newOrder}) $ \ix -> case ix of Layout.InsideBox _ _ -> a!ix _ -> if newOrder == Layout.bandedOrder shape then a!ix else 0