From 4bacc3a43b91e9f2ec3d197bb7428f008e76bb72 Mon Sep 17 00:00:00 2001 From: Alberto Ruiz Date: Sat, 7 Jun 2014 11:46:36 +0200 Subject: refactoring static --- packages/base/src/Numeric/LinearAlgebra/Real.hs | 231 +-------------- packages/base/src/Numeric/LinearAlgebra/Static.hs | 334 ++++++++++++++++++---- 2 files changed, 282 insertions(+), 283 deletions(-) (limited to 'packages/base/src/Numeric') diff --git a/packages/base/src/Numeric/LinearAlgebra/Real.hs b/packages/base/src/Numeric/LinearAlgebra/Real.hs index aa48687..97c462e 100644 --- a/packages/base/src/Numeric/LinearAlgebra/Real.hs +++ b/packages/base/src/Numeric/LinearAlgebra/Real.hs @@ -62,28 +62,13 @@ import Numeric.HMatrix hiding ( import qualified Numeric.HMatrix as LA import Data.Proxy(Proxy) import Numeric.LinearAlgebra.Static -import Text.Printf import Control.Arrow((***)) ๐‘– :: Sized โ„‚ s c => s -๐‘– = konst i_C +๐‘– = konst iC -instance forall n . KnownNat n => Show (R n) - where - show (ud1 -> v) - | singleV v = "("++show (v!0)++" :: R "++show d++")" - | otherwise = "(vector"++ drop 8 (show v)++" :: R "++show d++")" - where - d = fromIntegral . natVal $ (undefined :: Proxy n) :: Int -instance forall n . KnownNat n => Show (C n) - where - show (C (Dim v)) - | singleV v = "("++show (v!0)++" :: C "++show d++")" - | otherwise = "(vector"++ drop 8 (show v)++" :: C "++show d++")" - where - d = fromIntegral . natVal $ (undefined :: Proxy n) :: Int @@ -91,12 +76,6 @@ ud1 :: R n -> Vector โ„ ud1 (R (Dim v)) = v -mkR :: Vector โ„ -> R n -mkR = R . Dim - -mkC :: Vector โ„‚ -> C n -mkC = C . Dim - infixl 4 & (&) :: forall n . KnownNat n => R n -> โ„ -> R (n+1) @@ -143,95 +122,12 @@ dim = mkR (scalar d) -------------------------------------------------------------------------------- -newtype L m n = L (Dim m (Dim n (Matrix โ„))) - -newtype M m n = M (Dim m (Dim n (Matrix โ„‚))) ud2 :: L m n -> Matrix โ„ ud2 (L (Dim (Dim x))) = x -mkL :: Matrix โ„ -> L m n -mkL x = L (Dim (Dim x)) - -mkM :: Matrix โ„‚ -> M m n -mkM x = M (Dim (Dim x)) - -instance forall m n . (KnownNat m, KnownNat n) => Show (L m n) - where - show (isDiag -> Just (z,y,(m',n'))) = printf "(diag %s %s :: L %d %d)" (show z) (drop 9 $ show y) m' n' - show (ud2 -> x) - | singleM x = printf "(%s :: L %d %d)" (show (x `atIndex` (0,0))) m' n' - | otherwise = "(matrix"++ dropWhile (/='\n') (show x)++" :: L "++show m'++" "++show n'++")" - where - m' = fromIntegral . natVal $ (undefined :: Proxy m) :: Int - n' = fromIntegral . natVal $ (undefined :: Proxy n) :: Int - -instance forall m n . (KnownNat m, KnownNat n) => Show (M m n) - where - show (isDiagC -> Just (z,y,(m',n'))) = printf "(diag %s %s :: M %d %d)" (show z) (drop 9 $ show y) m' n' - show (M (Dim (Dim x))) - | singleM x = printf "(%s :: M %d %d)" (show (x `atIndex` (0,0))) m' n' - | otherwise = "(matrix"++ dropWhile (/='\n') (show x)++" :: M "++show m'++" "++show n'++")" - where - m' = fromIntegral . natVal $ (undefined :: Proxy m) :: Int - n' = fromIntegral . natVal $ (undefined :: Proxy n) :: Int - - -------------------------------------------------------------------------------- - -instance forall n. KnownNat n => Sized โ„‚ (C n) (Vector โ„‚) - where - konst x = mkC (LA.scalar x) - unwrap (C (Dim v)) = v - fromList xs = C (gvect "C" xs) - extract (unwrap -> v) - | singleV v = LA.konst (v!0) d - | otherwise = v - where - d = fromIntegral . natVal $ (undefined :: Proxy n) - - -instance forall n. KnownNat n => Sized โ„ (R n) (Vector โ„) - where - konst x = mkR (LA.scalar x) - unwrap = ud1 - fromList xs = R (gvect "R" xs) - extract (unwrap -> v) - | singleV v = LA.konst (v!0) d - | otherwise = v - where - d = fromIntegral . natVal $ (undefined :: Proxy n) - - - -instance forall m n . (KnownNat m, KnownNat n) => Sized โ„ (L m n) (Matrix โ„) - where - konst x = mkL (LA.scalar x) - fromList xs = L (gmat "L" xs) - unwrap = ud2 - extract (isDiag -> Just (z,y,(m',n'))) = diagRect z y m' n' - extract (unwrap -> a) - | singleM a = LA.konst (a `atIndex` (0,0)) (m',n') - | otherwise = a - where - m' = fromIntegral . natVal $ (undefined :: Proxy m) - n' = fromIntegral . natVal $ (undefined :: Proxy n) - - -instance forall m n . (KnownNat m, KnownNat n) => Sized โ„‚ (M m n) (Matrix โ„‚) - where - konst x = mkM (LA.scalar x) - fromList xs = M (gmat "M" xs) - unwrap (M (Dim (Dim m))) = m - extract (isDiagC -> Just (z,y,(m',n'))) = diagRect z y m' n' - extract (unwrap -> a) - | singleM a = LA.konst (a `atIndex` (0,0)) (m',n') - | otherwise = a - where - m' = fromIntegral . natVal $ (undefined :: Proxy m) - n' = fromIntegral . natVal $ (undefined :: Proxy n) - -------------------------------------------------------------------------------- diagR :: forall m n k . (KnownNat m, KnownNat n, KnownNat k) => โ„ -> R k -> L m n @@ -267,41 +163,6 @@ blockAt x r c a = mkL res --------------------------------------------------------------------------------- - -class Disp t - where - disp :: Int -> t -> IO () - - -instance (KnownNat m, KnownNat n) => Disp (L m n) - where - disp n x = do - let a = extract x - let su = LA.dispf n a - printf "L %d %d" (rows a) (cols a) >> putStr (dropWhile (/='\n') $ su) - -instance (KnownNat m, KnownNat n) => Disp (M m n) - where - disp n x = do - let a = extract x - let su = LA.dispcf n a - printf "M %d %d" (rows a) (cols a) >> putStr (dropWhile (/='\n') $ su) - - -instance KnownNat n => Disp (R n) - where - disp n v = do - let su = LA.dispf n (asRow $ extract v) - putStr "R " >> putStr (tail . dropWhile (/='x') $ su) - -instance KnownNat n => Disp (C n) - where - disp n v = do - let su = LA.dispcf n (asRow $ extract v) - putStr "C " >> putStr (tail . dropWhile (/='x') $ su) - - -------------------------------------------------------------------------------- @@ -344,28 +205,6 @@ isKonst (unwrap -> x) -isDiag :: forall m n . (KnownNat m, KnownNat n) => L m n -> Maybe (โ„, Vector โ„, (Int,Int)) -isDiag (L x) = isDiagg x - -isDiagC :: forall m n . (KnownNat m, KnownNat n) => M m n -> Maybe (โ„‚, Vector โ„‚, (Int,Int)) -isDiagC (M x) = isDiagg x - - -isDiagg :: forall m n t . (Numeric t, KnownNat m, KnownNat n) => GM m n t -> Maybe (t, Vector t, (Int,Int)) -isDiagg (Dim (Dim x)) - | singleM x = Nothing - | rows x == 1 && m' > 1 || cols x == 1 && n' > 1 = Just (z,yz,(m',n')) - | otherwise = Nothing - where - m' = fromIntegral . natVal $ (undefined :: Proxy m) :: Int - n' = fromIntegral . natVal $ (undefined :: Proxy n) :: Int - v = flatten x - z = v `atIndex` 0 - y = subVector 1 (size v-1) v - ny = size y - zeros = LA.konst 0 (max 0 (min m' n' - ny)) - yz = vjoin [y,zeros] - infixr 8 <> (<>) :: forall m k n. (KnownNat m, KnownNat k, KnownNat n) => L m k -> L k n -> L m n @@ -397,74 +236,6 @@ infixr 8 <ยท> | singleV u || singleV v = sumElements (u * v) | otherwise = udot u v - -instance (KnownNat n, KnownNat m) => Transposable (L m n) (L n m) - where - tr a@(isDiag -> Just _) = mkL (extract a) - tr (extract -> a) = mkL (tr a) - -instance (KnownNat n, KnownNat m) => Transposable (M m n) (M n m) - where - tr a@(isDiagC -> Just _) = mkM (extract a) - tr (extract -> a) = mkM (tr a) - - --------------------------------------------------------------------------------- - -adaptDiag f a@(isDiag -> Just _) b | isFull b = f (mkL (extract a)) b -adaptDiag f a b@(isDiag -> Just _) | isFull a = f a (mkL (extract b)) -adaptDiag f a b = f a b - -isFull m = isDiag m == Nothing && not (singleM (unwrap m)) - - -lift1L f (L v) = L (f v) -lift2L f (L a) (L b) = L (f a b) -lift2LD f = adaptDiag (lift2L f) - - -instance (KnownNat n, KnownNat m) => Num (L n m) - where - (+) = lift2LD (+) - (*) = lift2LD (*) - (-) = lift2LD (-) - abs = lift1L abs - signum = lift1L signum - negate = lift1L negate - fromInteger = L . Dim . Dim . fromInteger - -instance (KnownNat n, KnownNat m) => Fractional (L n m) - where - fromRational = L . Dim . Dim . fromRational - (/) = lift2LD (/) - --------------------------------------------------------------------------------- - -adaptDiagC f a@(isDiagC -> Just _) b | isFullC b = f (mkM (extract a)) b -adaptDiagC f a b@(isDiagC -> Just _) | isFullC a = f a (mkM (extract b)) -adaptDiagC f a b = f a b - -isFullC m = isDiagC m == Nothing && not (singleM (unwrap m)) - -lift1M f (M v) = M (f v) -lift2M f (M a) (M b) = M (f a b) -lift2MD f = adaptDiagC (lift2M f) - -instance (KnownNat n, KnownNat m) => Num (M n m) - where - (+) = lift2MD (+) - (*) = lift2MD (*) - (-) = lift2MD (-) - abs = lift1M abs - signum = lift1M signum - negate = lift1M negate - fromInteger = M . Dim . Dim . fromInteger - -instance (KnownNat n, KnownNat m) => Fractional (M n m) - where - fromRational = M . Dim . Dim . fromRational - (/) = lift2MD (/) - -------------------------------------------------------------------------------- {- diff --git a/packages/base/src/Numeric/LinearAlgebra/Static.hs b/packages/base/src/Numeric/LinearAlgebra/Static.hs index 6acd9a3..2647f20 100644 --- a/packages/base/src/Numeric/LinearAlgebra/Static.hs +++ b/packages/base/src/Numeric/LinearAlgebra/Static.hs @@ -21,14 +21,7 @@ Stability : provisional -} -module Numeric.LinearAlgebra.Static( - Dim(..), - R(..), C(..), - lift1F, lift2F, - vconcat, gvec2, gvec3, gvec4, gvect, gmat, - Sized(..), - singleV, singleM,GM -) where +module Numeric.LinearAlgebra.Static where import GHC.TypeLits @@ -37,17 +30,9 @@ import Data.Packed as D import Data.Packed.ST import Data.Proxy(Proxy) import Foreign.Storable(Storable) +import Text.Printf - - -newtype R n = R (Dim n (Vector โ„)) - deriving (Num,Fractional) - - -newtype C n = C (Dim n (Vector โ„‚)) - deriving (Num,Fractional) - - +-------------------------------------------------------------------------------- newtype Dim (n :: Nat) t = Dim t deriving Show @@ -64,36 +49,28 @@ lift2F f (Dim u) (Dim v) = Dim (f u v) -------------------------------------------------------------------------------- -instance forall n t . (Num (Vector t), Numeric t )=> Num (Dim n (Vector t)) - where - (+) = lift2F (+) - (*) = lift2F (*) - (-) = lift2F (-) - abs = lift1F abs - signum = lift1F signum - negate = lift1F negate - fromInteger x = Dim (fromInteger x) +newtype R n = R (Dim n (Vector โ„)) + deriving (Num,Fractional) -instance (Num (Vector t), Num (Matrix t), Numeric t) => Fractional (Dim n (Vector t)) - where - fromRational x = Dim (fromRational x) - (/) = lift2F (/) +newtype C n = C (Dim n (Vector โ„‚)) + deriving (Num,Fractional) +newtype L m n = L (Dim m (Dim n (Matrix โ„))) -instance (Num (Matrix t), Numeric t) => Num (Dim m (Dim n (Matrix t))) - where - (+) = (lift2F . lift2F) (+) - (*) = (lift2F . lift2F) (*) - (-) = (lift2F . lift2F) (-) - abs = (lift1F . lift1F) abs - signum = (lift1F . lift1F) signum - negate = (lift1F . lift1F) negate - fromInteger x = Dim (Dim (fromInteger x)) +newtype M m n = M (Dim m (Dim n (Matrix โ„‚))) -instance (Num (Vector t), Num (Matrix t), Numeric t) => Fractional (Dim m (Dim n (Matrix t))) - where - fromRational x = Dim (Dim (fromRational x)) - (/) = (lift2F.lift2F) (/) + +mkR :: Vector โ„ -> R n +mkR = R . Dim + +mkC :: Vector โ„‚ -> C n +mkC = C . Dim + +mkL :: Matrix โ„ -> L m n +mkL x = L (Dim (Dim x)) + +mkM :: Matrix โ„‚ -> M m n +mkM x = M (Dim (Dim x)) -------------------------------------------------------------------------------- @@ -105,14 +82,6 @@ ud (Dim v) = v mkV :: forall (n :: Nat) t . t -> Dim n t mkV = Dim -type GM m n t = Dim m (Dim n (Matrix t)) - ---ud2 :: Dim m (Dim n (Matrix t)) -> Matrix t ---ud2 (Dim (Dim m)) = m - -mkM :: forall (m :: Nat) (n :: Nat) t . t -> Dim m (Dim n t) -mkM = Dim . Dim - vconcat :: forall n m t . (KnownNat n, KnownNat m, Numeric t) => V n t -> V m t -> V (n+m) t @@ -166,9 +135,14 @@ gvect st xs' abort info = error $ st++" "++show d++" can't be created from elements "++info +-------------------------------------------------------------------------------- + +type GM m n t = Dim m (Dim n (Matrix t)) + + gmat :: forall m n t . (Show t, KnownNat m, KnownNat n, Numeric t) => String -> [t] -> GM m n t gmat st xs' - | ok = mkM x + | ok = Dim (Dim x) | not (null rest) && null (tail rest) = abort (show xs') | not (null rest) = abort (init (show (xs++take 1 rest))++", ... ]") | otherwise = abort (show xs) @@ -181,6 +155,7 @@ gmat st xs' n' = fromIntegral . natVal $ (undefined :: Proxy n) :: Int abort info = error $ st ++" "++show m' ++ " " ++ show n'++" can't be created from elements " ++ info +-------------------------------------------------------------------------------- class Num t => Sized t s d | s -> t, s -> d where @@ -192,3 +167,256 @@ class Num t => Sized t s d | s -> t, s -> d singleV v = size v == 1 singleM m = rows m == 1 && cols m == 1 + +instance forall n. KnownNat n => Sized โ„‚ (C n) (Vector โ„‚) + where + konst x = mkC (LA.scalar x) + unwrap (C (Dim v)) = v + fromList xs = C (gvect "C" xs) + extract (unwrap -> v) + | singleV v = LA.konst (v!0) d + | otherwise = v + where + d = fromIntegral . natVal $ (undefined :: Proxy n) + + +instance forall n. KnownNat n => Sized โ„ (R n) (Vector โ„) + where + konst x = mkR (LA.scalar x) + unwrap (R (Dim v)) = v + fromList xs = R (gvect "R" xs) + extract (unwrap -> v) + | singleV v = LA.konst (v!0) d + | otherwise = v + where + d = fromIntegral . natVal $ (undefined :: Proxy n) + + + +instance forall m n . (KnownNat m, KnownNat n) => Sized โ„ (L m n) (Matrix โ„) + where + konst x = mkL (LA.scalar x) + fromList xs = L (gmat "L" xs) + unwrap (L (Dim (Dim m))) = m + extract (isDiag -> Just (z,y,(m',n'))) = diagRect z y m' n' + extract (unwrap -> a) + | singleM a = LA.konst (a `atIndex` (0,0)) (m',n') + | otherwise = a + where + m' = fromIntegral . natVal $ (undefined :: Proxy m) + n' = fromIntegral . natVal $ (undefined :: Proxy n) + + +instance forall m n . (KnownNat m, KnownNat n) => Sized โ„‚ (M m n) (Matrix โ„‚) + where + konst x = mkM (LA.scalar x) + fromList xs = M (gmat "M" xs) + unwrap (M (Dim (Dim m))) = m + extract (isDiagC -> Just (z,y,(m',n'))) = diagRect z y m' n' + extract (unwrap -> a) + | singleM a = LA.konst (a `atIndex` (0,0)) (m',n') + | otherwise = a + where + m' = fromIntegral . natVal $ (undefined :: Proxy m) + n' = fromIntegral . natVal $ (undefined :: Proxy n) + +-------------------------------------------------------------------------------- + +instance (KnownNat n, KnownNat m) => Transposable (L m n) (L n m) + where + tr a@(isDiag -> Just _) = mkL (extract a) + tr (extract -> a) = mkL (tr a) + +instance (KnownNat n, KnownNat m) => Transposable (M m n) (M n m) + where + tr a@(isDiagC -> Just _) = mkM (extract a) + tr (extract -> a) = mkM (tr a) + +-------------------------------------------------------------------------------- + +isDiag :: forall m n . (KnownNat m, KnownNat n) => L m n -> Maybe (โ„, Vector โ„, (Int,Int)) +isDiag (L x) = isDiagg x + +isDiagC :: forall m n . (KnownNat m, KnownNat n) => M m n -> Maybe (โ„‚, Vector โ„‚, (Int,Int)) +isDiagC (M x) = isDiagg x + + +isDiagg :: forall m n t . (Numeric t, KnownNat m, KnownNat n) => GM m n t -> Maybe (t, Vector t, (Int,Int)) +isDiagg (Dim (Dim x)) + | singleM x = Nothing + | rows x == 1 && m' > 1 || cols x == 1 && n' > 1 = Just (z,yz,(m',n')) + | otherwise = Nothing + where + m' = fromIntegral . natVal $ (undefined :: Proxy m) :: Int + n' = fromIntegral . natVal $ (undefined :: Proxy n) :: Int + v = flatten x + z = v `atIndex` 0 + y = subVector 1 (size v-1) v + ny = size y + zeros = LA.konst 0 (max 0 (min m' n' - ny)) + yz = vjoin [y,zeros] + +-------------------------------------------------------------------------------- + +instance forall n . KnownNat n => Show (R n) + where + show (R (Dim v)) + | singleV v = "("++show (v!0)++" :: R "++show d++")" + | otherwise = "(vector"++ drop 8 (show v)++" :: R "++show d++")" + where + d = fromIntegral . natVal $ (undefined :: Proxy n) :: Int + +instance forall n . KnownNat n => Show (C n) + where + show (C (Dim v)) + | singleV v = "("++show (v!0)++" :: C "++show d++")" + | otherwise = "(vector"++ drop 8 (show v)++" :: C "++show d++")" + where + d = fromIntegral . natVal $ (undefined :: Proxy n) :: Int + +instance forall m n . (KnownNat m, KnownNat n) => Show (L m n) + where + show (isDiag -> Just (z,y,(m',n'))) = printf "(diag %s %s :: L %d %d)" (show z) (drop 9 $ show y) m' n' + show (L (Dim (Dim x))) + | singleM x = printf "(%s :: L %d %d)" (show (x `atIndex` (0,0))) m' n' + | otherwise = "(matrix"++ dropWhile (/='\n') (show x)++" :: L "++show m'++" "++show n'++")" + where + m' = fromIntegral . natVal $ (undefined :: Proxy m) :: Int + n' = fromIntegral . natVal $ (undefined :: Proxy n) :: Int + +instance forall m n . (KnownNat m, KnownNat n) => Show (M m n) + where + show (isDiagC -> Just (z,y,(m',n'))) = printf "(diag %s %s :: M %d %d)" (show z) (drop 9 $ show y) m' n' + show (M (Dim (Dim x))) + | singleM x = printf "(%s :: M %d %d)" (show (x `atIndex` (0,0))) m' n' + | otherwise = "(matrix"++ dropWhile (/='\n') (show x)++" :: M "++show m'++" "++show n'++")" + where + m' = fromIntegral . natVal $ (undefined :: Proxy m) :: Int + n' = fromIntegral . natVal $ (undefined :: Proxy n) :: Int + +-------------------------------------------------------------------------------- + +instance forall n t . (Num (Vector t), Numeric t )=> Num (Dim n (Vector t)) + where + (+) = lift2F (+) + (*) = lift2F (*) + (-) = lift2F (-) + abs = lift1F abs + signum = lift1F signum + negate = lift1F negate + fromInteger x = Dim (fromInteger x) + +instance (Num (Vector t), Num (Matrix t), Numeric t) => Fractional (Dim n (Vector t)) + where + fromRational x = Dim (fromRational x) + (/) = lift2F (/) + + +instance (Num (Matrix t), Numeric t) => Num (Dim m (Dim n (Matrix t))) + where + (+) = (lift2F . lift2F) (+) + (*) = (lift2F . lift2F) (*) + (-) = (lift2F . lift2F) (-) + abs = (lift1F . lift1F) abs + signum = (lift1F . lift1F) signum + negate = (lift1F . lift1F) negate + fromInteger x = Dim (Dim (fromInteger x)) + +instance (Num (Vector t), Num (Matrix t), Numeric t) => Fractional (Dim m (Dim n (Matrix t))) + where + fromRational x = Dim (Dim (fromRational x)) + (/) = (lift2F.lift2F) (/) + +-------------------------------------------------------------------------------- + + +adaptDiag f a@(isDiag -> Just _) b | isFull b = f (mkL (extract a)) b +adaptDiag f a b@(isDiag -> Just _) | isFull a = f a (mkL (extract b)) +adaptDiag f a b = f a b + +isFull m = isDiag m == Nothing && not (singleM (unwrap m)) + + +lift1L f (L v) = L (f v) +lift2L f (L a) (L b) = L (f a b) +lift2LD f = adaptDiag (lift2L f) + + +instance (KnownNat n, KnownNat m) => Num (L n m) + where + (+) = lift2LD (+) + (*) = lift2LD (*) + (-) = lift2LD (-) + abs = lift1L abs + signum = lift1L signum + negate = lift1L negate + fromInteger = L . Dim . Dim . fromInteger + +instance (KnownNat n, KnownNat m) => Fractional (L n m) + where + fromRational = L . Dim . Dim . fromRational + (/) = lift2LD (/) + +-------------------------------------------------------------------------------- + +adaptDiagC f a@(isDiagC -> Just _) b | isFullC b = f (mkM (extract a)) b +adaptDiagC f a b@(isDiagC -> Just _) | isFullC a = f a (mkM (extract b)) +adaptDiagC f a b = f a b + +isFullC m = isDiagC m == Nothing && not (singleM (unwrap m)) + +lift1M f (M v) = M (f v) +lift2M f (M a) (M b) = M (f a b) +lift2MD f = adaptDiagC (lift2M f) + +instance (KnownNat n, KnownNat m) => Num (M n m) + where + (+) = lift2MD (+) + (*) = lift2MD (*) + (-) = lift2MD (-) + abs = lift1M abs + signum = lift1M signum + negate = lift1M negate + fromInteger = M . Dim . Dim . fromInteger + +instance (KnownNat n, KnownNat m) => Fractional (M n m) + where + fromRational = M . Dim . Dim . fromRational + (/) = lift2MD (/) + +-------------------------------------------------------------------------------- + + +class Disp t + where + disp :: Int -> t -> IO () + + +instance (KnownNat m, KnownNat n) => Disp (L m n) + where + disp n x = do + let a = extract x + let su = LA.dispf n a + printf "L %d %d" (rows a) (cols a) >> putStr (dropWhile (/='\n') $ su) + +instance (KnownNat m, KnownNat n) => Disp (M m n) + where + disp n x = do + let a = extract x + let su = LA.dispcf n a + printf "M %d %d" (rows a) (cols a) >> putStr (dropWhile (/='\n') $ su) + + +instance KnownNat n => Disp (R n) + where + disp n v = do + let su = LA.dispf n (asRow $ extract v) + putStr "R " >> putStr (tail . dropWhile (/='x') $ su) + +instance KnownNat n => Disp (C n) + where + disp n v = do + let su = LA.dispcf n (asRow $ extract v) + putStr "C " >> putStr (tail . dropWhile (/='x') $ su) + +-------------------------------------------------------------------------------- -- cgit v1.2.3