-- |
-- Module      : Data.VectorSpace.Free.FiniteSupportedSequence
-- Copyright   : (c) Justus Sagemüller 2016
-- License     : GPL v3
-- 
-- Maintainer  : (@) jsag $ hvl.no
-- Stability   : experimental
-- Portability : portable
-- 
{-# LANGUAGE TypeFamilies            #-}
{-# LANGUAGE FlexibleInstances       #-}
{-# LANGUAGE FlexibleContexts        #-}
{-# LANGUAGE ConstrainedClassMethods #-}
{-# LANGUAGE MultiWayIf              #-}
{-# LANGUAGE ScopedTypeVariables     #-}
{-# LANGUAGE UnicodeSyntax           #-}

module Data.VectorSpace.Free.FiniteSupportedSequence (
                               FinSuppSeq (..)
                             , SparseSuppSeq (..)
                             , SemisparseSuppSeq (..)
                             ) where

import Data.AffineSpace
import Data.VectorSpace
import Data.VectorSpace.Free.Class
import Data.Basis

import qualified Data.Foldable as Foldable

import qualified Data.Vector.Generic as Arr
import qualified Data.Vector.Unboxed as UArr
import qualified Data.Vector.Generic.Mutable as MArr

import GHC.Exts (IsList(..))

import Control.Arrow (first, second)
import Control.Monad (forM_)



-- | The space of finitely-supported sequences is an /infinite/-dimensional space.
--   An vector of length /l/ is here understood as an infinite sequence that begins
--   with /l/ nonzero values, and continues with infinite zeroes.
-- 
--   You may also consider this as the type that languages like Octave/Matlab
--   (as well as Haskell's <http://hackage.haskell.org/package/hmatrix/ hmatrix> library)
--   approximate with their “vectors”, with one important difference: there is
--   no such thing as a dimensional-mismatch error, since we consider all these vectors
--   as elements of the same infinite-dimensional space. Adding two different-size
--   vectors will simply zero-pad the shorter, and unlike in Matlab this behaviour extends
--   consequently to matrix multiplication etc. (defined in
--   <http://hackage.haskell.org/package/linearmap-category/ linearmap-category>)
-- 
--   Of course it /can/ make sense to constrain the dimension, but for this the
--   type system should be used, not runtime checks.
-- 
--   (This is the same
--   behaviour that the <http://hackage.haskell.org/package/linear/ linear> library
--   gives to the standard list and vector types, but the problem there is that it
--   can't use unboxed arrays as these are not functors, but unboxing is crucial for
--   performance.)
newtype FinSuppSeq n = FinSuppSeq { FinSuppSeq n -> Vector n
getFiniteSeq :: UArr.Vector n }


{-# INLINE liftU2FSS #-}
liftU2FSS :: UArr.Unbox n => (n -> n -> n) -> FinSuppSeq n -> FinSuppSeq n -> FinSuppSeq n
-- Adapted from:
-- http://hackage.haskell.org/package/linear-1.20.5/docs/src/Linear.Vector.html#line-200 
liftU2FSS :: (n -> n -> n) -> FinSuppSeq n -> FinSuppSeq n -> FinSuppSeq n
liftU2FSS n -> n -> n
f (FinSuppSeq Vector n
u) (FinSuppSeq Vector n
v) = Vector n -> FinSuppSeq n
forall n. Vector n -> FinSuppSeq n
FinSuppSeq (Vector n -> FinSuppSeq n) -> Vector n -> FinSuppSeq n
forall a b. (a -> b) -> a -> b
$ case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int
lu Int
lv of
    Ordering
LT | Int
lu Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0   -> Vector n
v
       | Bool
otherwise -> (forall s. MVector s n -> ST s ()) -> Vector n -> Vector n
forall a.
Unbox a =>
(forall s. MVector s a -> ST s ()) -> Vector a -> Vector a
UArr.modify
           (\ MVector s n
w -> [Int] -> (Int -> ST s ()) -> ST s ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
Foldable.forM_ [Int
0..Int
luInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1] ((Int -> ST s ()) -> ST s ()) -> (Int -> ST s ()) -> ST s ()
forall a b. (a -> b) -> a -> b
$
                \Int
i -> MVector (PrimState (ST s)) n -> Int -> n -> ST s ()
forall (m :: * -> *) (v :: * -> * -> *) a.
(PrimMonad m, MVector v a) =>
v (PrimState m) a -> Int -> a -> m ()
MArr.unsafeWrite MVector s n
MVector (PrimState (ST s)) n
w Int
i (n -> ST s ()) -> n -> ST s ()
forall a b. (a -> b) -> a -> b
$ n -> n -> n
f (Vector n -> Int -> n
forall a. Unbox a => Vector a -> Int -> a
UArr.unsafeIndex Vector n
u Int
i)
                                               (Vector n -> Int -> n
forall a. Unbox a => Vector a -> Int -> a
UArr.unsafeIndex Vector n
v Int
i)) Vector n
v
    Ordering
EQ -> (n -> n -> n) -> Vector n -> Vector n -> Vector n
forall a b c.
(Unbox a, Unbox b, Unbox c) =>
(a -> b -> c) -> Vector a -> Vector b -> Vector c
UArr.zipWith n -> n -> n
f Vector n
u Vector n
v
    Ordering
GT | Int
lv Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0   -> Vector n
u
       | Bool
otherwise -> (forall s. MVector s n -> ST s ()) -> Vector n -> Vector n
forall a.
Unbox a =>
(forall s. MVector s a -> ST s ()) -> Vector a -> Vector a
UArr.modify
            (\ MVector s n
w -> [Int] -> (Int -> ST s ()) -> ST s ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
Foldable.forM_ [Int
0..Int
lvInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1] ((Int -> ST s ()) -> ST s ()) -> (Int -> ST s ()) -> ST s ()
forall a b. (a -> b) -> a -> b
$
                \Int
i -> MVector (PrimState (ST s)) n -> Int -> n -> ST s ()
forall (m :: * -> *) (v :: * -> * -> *) a.
(PrimMonad m, MVector v a) =>
v (PrimState m) a -> Int -> a -> m ()
MArr.unsafeWrite MVector s n
MVector (PrimState (ST s)) n
w Int
i (n -> ST s ()) -> n -> ST s ()
forall a b. (a -> b) -> a -> b
$ n -> n -> n
f (Vector n -> Int -> n
forall a. Unbox a => Vector a -> Int -> a
UArr.unsafeIndex Vector n
u Int
i)
                                               (Vector n -> Int -> n
forall a. Unbox a => Vector a -> Int -> a
UArr.unsafeIndex Vector n
v Int
i)) Vector n
u
 where lu :: Int
lu = Vector n -> Int
forall a. Unbox a => Vector a -> Int
UArr.length Vector n
u
       lv :: Int
lv = Vector n -> Int
forall a. Unbox a => Vector a -> Int
UArr.length Vector n
v


instance (Num n, UArr.Unbox n) => AffineSpace (FinSuppSeq n) where
  type Diff (FinSuppSeq n) = FinSuppSeq n
  .-. :: FinSuppSeq n -> FinSuppSeq n -> Diff (FinSuppSeq n)
(.-.) = FinSuppSeq n -> FinSuppSeq n -> Diff (FinSuppSeq n)
forall v. AdditiveGroup v => v -> v -> v
(^-^)
  .+^ :: FinSuppSeq n -> Diff (FinSuppSeq n) -> FinSuppSeq n
(.+^) = FinSuppSeq n -> Diff (FinSuppSeq n) -> FinSuppSeq n
forall v. AdditiveGroup v => v -> v -> v
(^+^)
  
instance (Num n, UArr.Unbox n) => AdditiveGroup (FinSuppSeq n) where
  zeroV :: FinSuppSeq n
zeroV = Vector n -> FinSuppSeq n
forall n. Vector n -> FinSuppSeq n
FinSuppSeq (Vector n -> FinSuppSeq n) -> Vector n -> FinSuppSeq n
forall a b. (a -> b) -> a -> b
$ Vector n
forall a. Unbox a => Vector a
UArr.empty
  ^+^ :: FinSuppSeq n -> FinSuppSeq n -> FinSuppSeq n
(^+^) = (n -> n -> n) -> FinSuppSeq n -> FinSuppSeq n -> FinSuppSeq n
forall n.
Unbox n =>
(n -> n -> n) -> FinSuppSeq n -> FinSuppSeq n -> FinSuppSeq n
liftU2FSS n -> n -> n
forall a. Num a => a -> a -> a
(+)
  negateV :: FinSuppSeq n -> FinSuppSeq n
negateV (FinSuppSeq Vector n
v) = Vector n -> FinSuppSeq n
forall n. Vector n -> FinSuppSeq n
FinSuppSeq (Vector n -> FinSuppSeq n) -> Vector n -> FinSuppSeq n
forall a b. (a -> b) -> a -> b
$ (n -> n) -> Vector n -> Vector n
forall a b. (Unbox a, Unbox b) => (a -> b) -> Vector a -> Vector b
UArr.map n -> n
forall a. Num a => a -> a
negate Vector n
v
  
instance (Num n, UArr.Unbox n) => VectorSpace (FinSuppSeq n) where
  type Scalar (FinSuppSeq n) = n
  Scalar (FinSuppSeq n)
μ*^ :: Scalar (FinSuppSeq n) -> FinSuppSeq n -> FinSuppSeq n
*^FinSuppSeq Vector n
v = Vector n -> FinSuppSeq n
forall n. Vector n -> FinSuppSeq n
FinSuppSeq (Vector n -> FinSuppSeq n) -> Vector n -> FinSuppSeq n
forall a b. (a -> b) -> a -> b
$ (n -> n) -> Vector n -> Vector n
forall a b. (Unbox a, Unbox b) => (a -> b) -> Vector a -> Vector b
UArr.map (n
Scalar (FinSuppSeq n)
μn -> n -> n
forall a. Num a => a -> a -> a
*) Vector n
v
  
instance (Num n, AdditiveGroup n, UArr.Unbox n) => FreeVectorSpace (FinSuppSeq n) where
  FinSuppSeq Vector n
v^*^ :: FinSuppSeq n -> FinSuppSeq n -> FinSuppSeq n
^*^FinSuppSeq Vector n
w = Vector n -> FinSuppSeq n
forall n. Vector n -> FinSuppSeq n
FinSuppSeq ((n -> n -> n) -> Vector n -> Vector n -> Vector n
forall a b c.
(Unbox a, Unbox b, Unbox c) =>
(a -> b -> c) -> Vector a -> Vector b -> Vector c
UArr.zipWith n -> n -> n
forall a. Num a => a -> a -> a
(*) Vector n
v Vector n
w)
  vmap :: (Scalar (FinSuppSeq n) -> Scalar (FinSuppSeq n))
-> FinSuppSeq n -> FinSuppSeq n
vmap Scalar (FinSuppSeq n) -> Scalar (FinSuppSeq n)
f (FinSuppSeq Vector n
v) = Vector n -> FinSuppSeq n
forall n. Vector n -> FinSuppSeq n
FinSuppSeq (Vector n -> FinSuppSeq n) -> Vector n -> FinSuppSeq n
forall a b. (a -> b) -> a -> b
$ (n -> n) -> Vector n -> Vector n
forall a b. (Unbox a, Unbox b) => (a -> b) -> Vector a -> Vector b
UArr.map n -> n
Scalar (FinSuppSeq n) -> Scalar (FinSuppSeq n)
f Vector n
v

instance (Num n, AdditiveGroup n, UArr.Unbox n) => InnerSpace (FinSuppSeq n) where
  FinSuppSeq Vector n
v<.> :: FinSuppSeq n -> FinSuppSeq n -> Scalar (FinSuppSeq n)
<.>FinSuppSeq Vector n
w = Vector n -> n
forall a. (Unbox a, Num a) => Vector a -> a
UArr.sum ((n -> n -> n) -> Vector n -> Vector n -> Vector n
forall a b c.
(Unbox a, Unbox b, Unbox c) =>
(a -> b -> c) -> Vector a -> Vector b -> Vector c
UArr.zipWith n -> n -> n
forall a. Num a => a -> a -> a
(*) Vector n
v Vector n
w)

instance (Num n, UArr.Unbox n) => HasBasis (FinSuppSeq n) where
  type Basis (FinSuppSeq n) = Int
  basisValue :: Basis (FinSuppSeq n) -> FinSuppSeq n
basisValue Basis (FinSuppSeq n)
i = Vector n -> FinSuppSeq n
forall n. Vector n -> FinSuppSeq n
FinSuppSeq (Vector n -> FinSuppSeq n) -> Vector n -> FinSuppSeq n
forall a b. (a -> b) -> a -> b
$ Int -> n -> Vector n
forall a. Unbox a => Int -> a -> Vector a
UArr.replicate Int
Basis (FinSuppSeq n)
i n
0 Vector n -> n -> Vector n
forall a. Unbox a => Vector a -> a -> Vector a
`UArr.snoc` n
1
  decompose :: FinSuppSeq n -> [(Basis (FinSuppSeq n), Scalar (FinSuppSeq n))]
decompose = [Int] -> [n] -> [(Int, n)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..] ([n] -> [(Int, n)])
-> (FinSuppSeq n -> [n]) -> FinSuppSeq n -> [(Int, n)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FinSuppSeq n -> [n]
forall l. IsList l => l -> [Item l]
toList
  decompose' :: FinSuppSeq n -> Basis (FinSuppSeq n) -> Scalar (FinSuppSeq n)
decompose' (FinSuppSeq Vector n
v) Basis (FinSuppSeq n)
i = n -> (n -> n) -> Maybe n -> n
forall b a. b -> (a -> b) -> Maybe a -> b
maybe n
0 n -> n
forall a. a -> a
id (Maybe n -> n) -> Maybe n -> n
forall a b. (a -> b) -> a -> b
$ Vector n
v Vector n -> Int -> Maybe n
forall a. Unbox a => Vector a -> Int -> Maybe a
UArr.!? Int
Basis (FinSuppSeq n)
i

instance UArr.Unbox n => IsList (FinSuppSeq n) where
  type Item (FinSuppSeq n) = n
  fromListN :: Int -> [Item (FinSuppSeq n)] -> FinSuppSeq n
fromListN Int
l = Vector n -> FinSuppSeq n
forall n. Vector n -> FinSuppSeq n
FinSuppSeq (Vector n -> FinSuppSeq n)
-> ([n] -> Vector n) -> [n] -> FinSuppSeq n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Item (Vector n)] -> Vector n
forall l. IsList l => Int -> [Item l] -> l
fromListN Int
l
  fromList :: [Item (FinSuppSeq n)] -> FinSuppSeq n
fromList = Vector n -> FinSuppSeq n
forall n. Vector n -> FinSuppSeq n
FinSuppSeq (Vector n -> FinSuppSeq n)
-> ([n] -> Vector n) -> [n] -> FinSuppSeq n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [n] -> Vector n
forall l. IsList l => [Item l] -> l
fromList
  toList :: FinSuppSeq n -> [Item (FinSuppSeq n)]
toList = Vector n -> [n]
forall l. IsList l => l -> [Item l]
toList (Vector n -> [n])
-> (FinSuppSeq n -> Vector n) -> FinSuppSeq n -> [n]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FinSuppSeq n -> Vector n
forall n. FinSuppSeq n -> Vector n
getFiniteSeq

instance (UArr.Unbox n, Show n) => Show (FinSuppSeq n) where
  show :: FinSuppSeq n -> String
show = (String
"fromList "String -> ShowS
forall a. [a] -> [a] -> [a]
++) ShowS -> (FinSuppSeq n -> String) -> FinSuppSeq n -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [n] -> String
forall a. Show a => a -> String
show ([n] -> String) -> (FinSuppSeq n -> [n]) -> FinSuppSeq n -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FinSuppSeq n -> [n]
forall l. IsList l => l -> [Item l]
toList





-- | Sparsely supported sequences (what other languages would call /sparse vectors/)
--   are sequences consisting of lots of zeroes, with finitely many
--   nonzeroes scattered around. Only these nonzero elements are stored.
data SparseSuppSeq n = SparseSuppSeq {
       SparseSuppSeq n -> Vector (Int, n)
sparseNonzeroes :: UArr.Vector (Int,n)
     }

instance (Num n, UArr.Unbox n) => AffineSpace (SparseSuppSeq n) where
  type Diff (SparseSuppSeq n) = SparseSuppSeq n
  .-. :: SparseSuppSeq n -> SparseSuppSeq n -> Diff (SparseSuppSeq n)
(.-.) = SparseSuppSeq n -> SparseSuppSeq n -> Diff (SparseSuppSeq n)
forall v. AdditiveGroup v => v -> v -> v
(^-^)
  .+^ :: SparseSuppSeq n -> Diff (SparseSuppSeq n) -> SparseSuppSeq n
(.+^) = SparseSuppSeq n -> Diff (SparseSuppSeq n) -> SparseSuppSeq n
forall v. AdditiveGroup v => v -> v -> v
(^+^)
  
instance (Num n, UArr.Unbox n) => AdditiveGroup (SparseSuppSeq n) where
  zeroV :: SparseSuppSeq n
zeroV = Vector (Int, n) -> SparseSuppSeq n
forall n. Vector (Int, n) -> SparseSuppSeq n
SparseSuppSeq (Vector (Int, n) -> SparseSuppSeq n)
-> Vector (Int, n) -> SparseSuppSeq n
forall a b. (a -> b) -> a -> b
$ Vector (Int, n)
forall a. Unbox a => Vector a
UArr.empty
  SparseSuppSeq Vector (Int, n)
u ^+^ :: SparseSuppSeq n -> SparseSuppSeq n -> SparseSuppSeq n
^+^ SparseSuppSeq Vector (Int, n)
v = Vector (Int, n) -> SparseSuppSeq n
forall n. Vector (Int, n) -> SparseSuppSeq n
SparseSuppSeq Vector (Int, n)
w
   where w :: Vector (Int, n)
w = Int
-> ((Int, Int) -> Maybe ((Int, n), (Int, Int)))
-> (Int, Int)
-> Vector (Int, n)
forall (v :: * -> *) a b.
Vector v a =>
Int -> (b -> Maybe (a, b)) -> b -> v a
Arr.unfoldrN (Vector (Int, n) -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
Arr.length Vector (Int, n)
u Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Vector (Int, n) -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
Arr.length Vector (Int, n)
v) (Int, Int) -> Maybe ((Int, n), (Int, Int))
seekws (Int
0,Int
0)
         seekws :: (Int, Int) -> Maybe ((Int, n), (Int, Int))
seekws (Int
pu,Int
pv) = case (Vector (Int, n)
u Vector (Int, n) -> Int -> Maybe (Int, n)
forall (v :: * -> *) a. Vector v a => v a -> Int -> Maybe a
Arr.!? Int
pu, Vector (Int, n)
v Vector (Int, n) -> Int -> Maybe (Int, n)
forall (v :: * -> *) a. Vector v a => v a -> Int -> Maybe a
Arr.!? Int
pv) of
                     (Just (Int
ju,n
uj), Just (Int
jv,n
vj))
                       -> if | Int
juInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>Int
jv     -> ((Int, n), (Int, Int)) -> Maybe ((Int, n), (Int, Int))
forall a. a -> Maybe a
Just ((Int
jv, n
vj), (Int
pu, Int
pvInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1))
                             | Int
juInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<Int
jv     -> ((Int, n), (Int, Int)) -> Maybe ((Int, n), (Int, Int))
forall a. a -> Maybe a
Just ((Int
ju, n
uj), (Int
puInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1, Int
pv))
                             | Bool
otherwise -> ((Int, n), (Int, Int)) -> Maybe ((Int, n), (Int, Int))
forall a. a -> Maybe a
Just ((Int
ju, n
ujn -> n -> n
forall a. Num a => a -> a -> a
+n
vj), (Int
puInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1, Int
pvInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1))
                     (Just (Int
ju,n
uj), Maybe (Int, n)
Nothing)
                                         -> ((Int, n), (Int, Int)) -> Maybe ((Int, n), (Int, Int))
forall a. a -> Maybe a
Just ((Int
ju, n
uj), (Int
puInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1, Int
pv))
                     (Maybe (Int, n)
Nothing, Just (Int
jv,n
vj))
                                         -> ((Int, n), (Int, Int)) -> Maybe ((Int, n), (Int, Int))
forall a. a -> Maybe a
Just ((Int
jv, n
vj), (Int
pu, Int
pvInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1))
                     (Maybe (Int, n)
Nothing, Maybe (Int, n)
Nothing)  -> Maybe ((Int, n), (Int, Int))
forall a. Maybe a
Nothing
  negateV :: SparseSuppSeq n -> SparseSuppSeq n
negateV (SparseSuppSeq Vector (Int, n)
v) = Vector (Int, n) -> SparseSuppSeq n
forall n. Vector (Int, n) -> SparseSuppSeq n
SparseSuppSeq (Vector (Int, n) -> SparseSuppSeq n)
-> Vector (Int, n) -> SparseSuppSeq n
forall a b. (a -> b) -> a -> b
$ ((Int, n) -> (Int, n)) -> Vector (Int, n) -> Vector (Int, n)
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b) -> v a -> v b
Arr.map ((n -> n) -> (Int, n) -> (Int, n)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second n -> n
forall a. Num a => a -> a
negate) Vector (Int, n)
v

instance (Num n, UArr.Unbox n) => VectorSpace (SparseSuppSeq n) where
  type Scalar (SparseSuppSeq n) = n
  Scalar (SparseSuppSeq n)
μ *^ :: Scalar (SparseSuppSeq n) -> SparseSuppSeq n -> SparseSuppSeq n
*^ SparseSuppSeq Vector (Int, n)
v = Vector (Int, n) -> SparseSuppSeq n
forall n. Vector (Int, n) -> SparseSuppSeq n
SparseSuppSeq (Vector (Int, n) -> SparseSuppSeq n)
-> Vector (Int, n) -> SparseSuppSeq n
forall a b. (a -> b) -> a -> b
$ ((Int, n) -> (Int, n)) -> Vector (Int, n) -> Vector (Int, n)
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b) -> v a -> v b
Arr.map ((n -> n) -> (Int, n) -> (Int, n)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second (n -> n -> n
forall a. Num a => a -> a -> a
*n
Scalar (SparseSuppSeq n)
μ)) Vector (Int, n)
v

instance (Num n, UArr.Unbox n) => FreeVectorSpace (SparseSuppSeq n) where
  SparseSuppSeq Vector (Int, n)
u ^*^ :: SparseSuppSeq n -> SparseSuppSeq n -> SparseSuppSeq n
^*^ SparseSuppSeq Vector (Int, n)
v = Vector (Int, n) -> SparseSuppSeq n
forall n. Vector (Int, n) -> SparseSuppSeq n
SparseSuppSeq Vector (Int, n)
w
   where w :: Vector (Int, n)
w = Int
-> ((Int, Int) -> Maybe ((Int, n), (Int, Int)))
-> (Int, Int)
-> Vector (Int, n)
forall (v :: * -> *) a b.
Vector v a =>
Int -> (b -> Maybe (a, b)) -> b -> v a
Arr.unfoldrN (Vector (Int, n) -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
Arr.length Vector (Int, n)
u Int -> Int -> Int
forall a. Ord a => a -> a -> a
`min` Vector (Int, n) -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
Arr.length Vector (Int, n)
v) (Int, Int) -> Maybe ((Int, n), (Int, Int))
seekws (Int
0,Int
0)
         seekws :: (Int, Int) -> Maybe ((Int, n), (Int, Int))
seekws (Int
pu,Int
pv) = case (Vector (Int, n)
u Vector (Int, n) -> Int -> Maybe (Int, n)
forall (v :: * -> *) a. Vector v a => v a -> Int -> Maybe a
Arr.!? Int
pu, Vector (Int, n)
v Vector (Int, n) -> Int -> Maybe (Int, n)
forall (v :: * -> *) a. Vector v a => v a -> Int -> Maybe a
Arr.!? Int
pv) of
                     (Just (Int
ju,n
uj), Just (Int
jv,n
vj))
                       -> if | Int
juInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>Int
jv     -> (Int, Int) -> Maybe ((Int, n), (Int, Int))
seekws (Int
pu, Int
pvInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
                             | Int
juInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<Int
jv     -> (Int, Int) -> Maybe ((Int, n), (Int, Int))
seekws (Int
puInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1, Int
pv)
                             | Bool
otherwise -> ((Int, n), (Int, Int)) -> Maybe ((Int, n), (Int, Int))
forall a. a -> Maybe a
Just ((Int
ju, n
ujn -> n -> n
forall a. Num a => a -> a -> a
*n
vj), (Int
puInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1, Int
pvInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1))
                     (Maybe (Int, n), Maybe (Int, n))
_ -> Maybe ((Int, n), (Int, Int))
forall a. Maybe a
Nothing
  vmap :: (Scalar (SparseSuppSeq n) -> Scalar (SparseSuppSeq n))
-> SparseSuppSeq n -> SparseSuppSeq n
vmap Scalar (SparseSuppSeq n) -> Scalar (SparseSuppSeq n)
f (SparseSuppSeq Vector (Int, n)
v) = Vector (Int, n) -> SparseSuppSeq n
forall n. Vector (Int, n) -> SparseSuppSeq n
SparseSuppSeq (Vector (Int, n) -> SparseSuppSeq n)
-> Vector (Int, n) -> SparseSuppSeq n
forall a b. (a -> b) -> a -> b
$ ((Int, n) -> (Int, n)) -> Vector (Int, n) -> Vector (Int, n)
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b) -> v a -> v b
Arr.map ((n -> n) -> (Int, n) -> (Int, n)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second n -> n
Scalar (SparseSuppSeq n) -> Scalar (SparseSuppSeq n)
f) Vector (Int, n)
v

instance (Num n, AdditiveGroup n, UArr.Unbox n) => InnerSpace (SparseSuppSeq n) where
  SparseSuppSeq n
v <.> :: SparseSuppSeq n -> SparseSuppSeq n -> Scalar (SparseSuppSeq n)
<.> SparseSuppSeq n
w = case SparseSuppSeq n
v SparseSuppSeq n -> SparseSuppSeq n -> SparseSuppSeq n
forall v. FreeVectorSpace v => v -> v -> v
^*^ SparseSuppSeq n
w of SparseSuppSeq Vector (Int, n)
vw -> (n -> (Int, n) -> n) -> n -> Vector (Int, n) -> n
forall (v :: * -> *) b a.
Vector v b =>
(a -> b -> a) -> a -> v b -> a
Arr.foldl' (\n
acc (Int
_,n
q) -> n
accn -> n -> n
forall a. Num a => a -> a -> a
+n
q) n
0 Vector (Int, n)
vw

instance (Num n, UArr.Unbox n) => HasBasis (SparseSuppSeq n) where
  type Basis (SparseSuppSeq n) = Int
  basisValue :: Basis (SparseSuppSeq n) -> SparseSuppSeq n
basisValue Basis (SparseSuppSeq n)
i = Vector (Int, n) -> SparseSuppSeq n
forall n. Vector (Int, n) -> SparseSuppSeq n
SparseSuppSeq (Vector (Int, n) -> SparseSuppSeq n)
-> Vector (Int, n) -> SparseSuppSeq n
forall a b. (a -> b) -> a -> b
$ (Int, n) -> Vector (Int, n)
forall a. Unbox a => a -> Vector a
UArr.singleton (Int
Basis (SparseSuppSeq n)
i,n
1)
  decompose :: SparseSuppSeq n
-> [(Basis (SparseSuppSeq n), Scalar (SparseSuppSeq n))]
decompose (SparseSuppSeq Vector (Int, n)
v) = Vector (Int, n) -> [(Int, n)]
forall a. Unbox a => Vector a -> [a]
UArr.toList Vector (Int, n)
v
  decompose' :: SparseSuppSeq n
-> Basis (SparseSuppSeq n) -> Scalar (SparseSuppSeq n)
decompose' (SparseSuppSeq Vector (Int, n)
v) Basis (SparseSuppSeq n)
i = Int -> Int -> n
goBisect Int
0 (Vector (Int, n) -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
Arr.length Vector (Int, n)
v)
   where goBisect :: Int -> Int -> n
goBisect Int
jb Int
jt
           | Int
jbInt -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
jt     = n
0
           | Bool
otherwise  = case (Int -> Ordering) -> (Int, n) -> (Ordering, n)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first (Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare`Int
Basis (SparseSuppSeq n)
i) ((Int, n) -> (Ordering, n)) -> (Int, n) -> (Ordering, n)
forall a b. (a -> b) -> a -> b
$ Vector (Int, n)
v Vector (Int, n) -> Int -> (Int, n)
forall (v :: * -> *) a. Vector v a => v a -> Int -> a
Arr.! Int
jm of
                            (Ordering
LT,n
_) -> Int -> Int -> n
goBisect (Int
jmInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Int
jt
                            (Ordering
EQ,n
q) -> n
q
                            (Ordering
GT,n
_) -> Int -> Int -> n
goBisect Int
jb Int
jm
          where jm :: Int
jm = (Int
jbInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
jt)Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div`Int
2

instance (UArr.Unbox n, Eq n, Num n) => IsList (SparseSuppSeq n) where
  type Item (SparseSuppSeq n) = n
  fromListN :: Int -> [Item (SparseSuppSeq n)] -> SparseSuppSeq n
fromListN Int
n [Item (SparseSuppSeq n)]
xs = Vector (Int, n) -> SparseSuppSeq n
forall n. Vector (Int, n) -> SparseSuppSeq n
SparseSuppSeq (Vector (Int, n) -> SparseSuppSeq n)
-> Vector (Int, n) -> SparseSuppSeq n
forall a b. (a -> b) -> a -> b
$ Int
-> ((Int, [n]) -> Maybe ((Int, n), (Int, [n])))
-> (Int, [n])
-> Vector (Int, n)
forall (v :: * -> *) a b.
Vector v a =>
Int -> (b -> Maybe (a, b)) -> b -> v a
Arr.unfoldrN Int
n (Int, [n]) -> Maybe ((Int, n), (Int, [n]))
forall b a.
(Eq b, Num b, Num a) =>
(a, [b]) -> Maybe ((a, b), (a, [b]))
go (Int
0,[n]
[Item (SparseSuppSeq n)]
xs)
   where go :: (a, [b]) -> Maybe ((a, b), (a, [b]))
go (a
_,[]) = Maybe ((a, b), (a, [b]))
forall a. Maybe a
Nothing
         go (a
j,b
0:[b]
xs) = (a, [b]) -> Maybe ((a, b), (a, [b]))
go (a
ja -> a -> a
forall a. Num a => a -> a -> a
+a
1,[b]
xs)
         go (a
j,b
x:[b]
xs) = ((a, b), (a, [b])) -> Maybe ((a, b), (a, [b]))
forall a. a -> Maybe a
Just ((a
j,b
x), (a
ja -> a -> a
forall a. Num a => a -> a -> a
+a
1,[b]
xs))
  fromList :: [Item (SparseSuppSeq n)] -> SparseSuppSeq n
fromList [Item (SparseSuppSeq n)]
l = Int -> [Item (SparseSuppSeq n)] -> SparseSuppSeq n
forall l. IsList l => Int -> [Item l] -> l
fromListN ([n] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [n]
[Item (SparseSuppSeq n)]
l) [Item (SparseSuppSeq n)]
l
  toList :: SparseSuppSeq n -> [Item (SparseSuppSeq n)]
toList (SparseSuppSeq Vector (Int, n)
xs) = Int -> Int -> [n]
go Int
0 Int
0
   where go :: Int -> Int -> [n]
go Int
i Int
j = case Vector (Int, n)
xs Vector (Int, n) -> Int -> Maybe (Int, n)
forall (v :: * -> *) a. Vector v a => v a -> Int -> Maybe a
Arr.!? Int
j of
              Just (Int
i',n
x) | Int
iInt -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
i'  -> n
x n -> [n] -> [n]
forall a. a -> [a] -> [a]
: Int -> Int -> [n]
go (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) (Int
jInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
              Maybe (Int, n)
Nothing              -> []
              Maybe (Int, n)
_                    -> n
0 n -> [n] -> [n]
forall a. a -> [a] -> [a]
: Int -> Int -> [n]
go (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Int
j




-- | Like 'SparseSuppSeq', this type of number-sequence ignores zeroes and only stores
--   nonzero elements with positional information, but it does this not for every single
--   entry separately: only the first position of each contiguous /chunk/ of nonzeroes
--   is tracked. It is thus more suited for vectors that are in some places dense
--   but still have lots of zeroes.
-- 
--   The drawback is that random access (i.e. 'decompose'') has complexity 𝓞(𝑛)
--    – instead of 𝓞(1) for 'FinSuppSeq', or 𝓞(log 𝑛) for 'SparseSuppSeq' –
--   so this type should only be used for “abstract vector operations”.
data SemisparseSuppSeq n = SemisparseSuppSeq {
       SemisparseSuppSeq n -> Vector n
chunkSparseNonzeroes :: UArr.Vector n
     , SemisparseSuppSeq n -> Vector (Int, Int)
sparseNonzeroLocation :: UArr.Vector (Int, Int)
                                        -- ^ Start index of block,
                                        --        size of block of consecutive nonzeroes
     }
     

asSemisparse :: UArr.Unbox n => SparseSuppSeq n -> SemisparseSuppSeq n
asSemisparse :: SparseSuppSeq n -> SemisparseSuppSeq n
asSemisparse (SparseSuppSeq Vector (Int, n)
v) = Vector n -> Vector (Int, Int) -> SemisparseSuppSeq n
forall n. Vector n -> Vector (Int, Int) -> SemisparseSuppSeq n
SemisparseSuppSeq (((Int, n) -> n) -> Vector (Int, n) -> Vector n
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b) -> v a -> v b
Arr.map (Int, n) -> n
forall a b. (a, b) -> b
snd Vector (Int, n)
v)
                                    (Vector (Int, Int) -> SemisparseSuppSeq n)
-> Vector (Int, Int) -> SemisparseSuppSeq n
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> Maybe ((Int, Int), Int)) -> Int -> Vector (Int, Int)
forall (v :: * -> *) a b.
Vector v a =>
Int -> (b -> Maybe (a, b)) -> b -> v a
Arr.unfoldrN (Vector (Int, n) -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
Arr.length Vector (Int, n)
v) Int -> Maybe ((Int, Int), Int)
mkIndex Int
0
 where mkIndex :: Int -> Maybe ((Int, Int), Int)
       mkIndex :: Int -> Maybe ((Int, Int), Int)
mkIndex Int
i
        | Just (Int
j,n
_) <- Vector (Int, n)
v Vector (Int, n) -> Int -> Maybe (Int, n)
forall (v :: * -> *) a. Vector v a => v a -> Int -> Maybe a
Arr.!? Int
i  = case Int -> Maybe ((Int, Int), Int)
mkIndex (Int -> Maybe ((Int, Int), Int)) -> Int -> Maybe ((Int, Int), Int)
forall a b. (a -> b) -> a -> b
$ Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1 of
            Just ((Int
j',Int
l),Int
n) | Int
j'Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
jInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1  -> ((Int, Int), Int) -> Maybe ((Int, Int), Int)
forall a. a -> Maybe a
Just ((Int
j,Int
lInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1), Int
n)
            Maybe ((Int, Int), Int)
_                          -> ((Int, Int), Int) -> Maybe ((Int, Int), Int)
forall a. a -> Maybe a
Just ((Int
j,Int
1), Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
        | Bool
otherwise  = Maybe ((Int, Int), Int)
forall a. Maybe a
Nothing

fromSemisparse ::  n . UArr.Unbox n => SemisparseSuppSeq n -> SparseSuppSeq n
fromSemisparse :: SemisparseSuppSeq n -> SparseSuppSeq n
fromSemisparse (SemisparseSuppSeq Vector n
v Vector (Int, Int)
ssIx) = Vector (Int, n) -> SparseSuppSeq n
forall n. Vector (Int, n) -> SparseSuppSeq n
SparseSuppSeq (Vector (Int, n) -> SparseSuppSeq n)
-> (Vector Int -> Vector (Int, n)) -> Vector Int -> SparseSuppSeq n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vector Int -> Vector n -> Vector (Int, n)
forall (v :: * -> *) a b.
(Vector v a, Vector v b, Vector v (a, b)) =>
v a -> v b -> v (a, b)
`Arr.zip`Vector n
v) (Vector Int -> SparseSuppSeq n) -> Vector Int -> SparseSuppSeq n
forall a b. (a -> b) -> a -> b
$ (forall s. ST s (Mutable Vector s Int)) -> Vector Int
forall (v :: * -> *) a.
Vector v a =>
(forall s. ST s (Mutable v s a)) -> v a
Arr.create (do
         MVector s Int
ix <- Int -> ST s (MVector (PrimState (ST s)) Int)
forall (m :: * -> *) (v :: * -> * -> *) a.
(PrimMonad m, MVector v a) =>
Int -> m (v (PrimState m) a)
MArr.new (Int -> ST s (MVector (PrimState (ST s)) Int))
-> Int -> ST s (MVector (PrimState (ST s)) Int)
forall a b. (a -> b) -> a -> b
$ Vector n -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
Arr.length Vector n
v
         (Int -> (Int, Int) -> ST s Int)
-> Int -> Vector (Int, Int) -> ST s ()
forall (m :: * -> *) (v :: * -> *) b a.
(Monad m, Vector v b) =>
(a -> b -> m a) -> a -> v b -> m ()
Arr.foldM_ (\Int
i (Int
j,Int
l) -> do
                       [Int] -> (Int -> ST s ()) -> ST s ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Int
0..Int
lInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1] -- TODO: faster loop and unsafeWrite
                         ((Int -> ST s ()) -> ST s ()) -> (Int -> ST s ()) -> ST s ()
forall a b. (a -> b) -> a -> b
$ \Int
k -> MVector (PrimState (ST s)) Int -> Int -> Int -> ST s ()
forall (m :: * -> *) (v :: * -> * -> *) a.
(PrimMonad m, MVector v a) =>
v (PrimState m) a -> Int -> a -> m ()
MArr.write MVector s Int
MVector (PrimState (ST s)) Int
ix (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
k) (Int
jInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
k)
                       Int -> ST s Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> ST s Int) -> Int -> ST s Int
forall a b. (a -> b) -> a -> b
$ Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
l
                    ) Int
0 Vector (Int, Int)
ssIx
         MVector s Int -> ST s (MVector s Int)
forall (m :: * -> *) a. Monad m => a -> m a
return MVector s Int
ix
     )

instance (Num n, UArr.Unbox n) => AffineSpace (SemisparseSuppSeq n) where
  type Diff (SemisparseSuppSeq n) = SemisparseSuppSeq n
  .-. :: SemisparseSuppSeq n
-> SemisparseSuppSeq n -> Diff (SemisparseSuppSeq n)
(.-.) = SemisparseSuppSeq n
-> SemisparseSuppSeq n -> Diff (SemisparseSuppSeq n)
forall v. AdditiveGroup v => v -> v -> v
(^-^)
  .+^ :: SemisparseSuppSeq n
-> Diff (SemisparseSuppSeq n) -> SemisparseSuppSeq n
(.+^) = SemisparseSuppSeq n
-> Diff (SemisparseSuppSeq n) -> SemisparseSuppSeq n
forall v. AdditiveGroup v => v -> v -> v
(^+^)
  
instance (Num n, UArr.Unbox n) => AdditiveGroup (SemisparseSuppSeq n) where
  zeroV :: SemisparseSuppSeq n
zeroV = Vector n -> Vector (Int, Int) -> SemisparseSuppSeq n
forall n. Vector n -> Vector (Int, Int) -> SemisparseSuppSeq n
SemisparseSuppSeq Vector n
forall a. Unbox a => Vector a
UArr.empty Vector (Int, Int)
forall a. Unbox a => Vector a
UArr.empty
  SemisparseSuppSeq n
u ^+^ :: SemisparseSuppSeq n -> SemisparseSuppSeq n -> SemisparseSuppSeq n
^+^ SemisparseSuppSeq n
v =  -- TODO: faster, direct implementation
     SparseSuppSeq n -> SemisparseSuppSeq n
forall n. Unbox n => SparseSuppSeq n -> SemisparseSuppSeq n
asSemisparse (SparseSuppSeq n -> SemisparseSuppSeq n)
-> SparseSuppSeq n -> SemisparseSuppSeq n
forall a b. (a -> b) -> a -> b
$ SemisparseSuppSeq n -> SparseSuppSeq n
forall n. Unbox n => SemisparseSuppSeq n -> SparseSuppSeq n
fromSemisparse SemisparseSuppSeq n
u SparseSuppSeq n -> SparseSuppSeq n -> SparseSuppSeq n
forall v. AdditiveGroup v => v -> v -> v
^+^ SemisparseSuppSeq n -> SparseSuppSeq n
forall n. Unbox n => SemisparseSuppSeq n -> SparseSuppSeq n
fromSemisparse SemisparseSuppSeq n
v
  negateV :: SemisparseSuppSeq n -> SemisparseSuppSeq n
negateV (SemisparseSuppSeq Vector n
v Vector (Int, Int)
vis) = Vector n -> Vector (Int, Int) -> SemisparseSuppSeq n
forall n. Vector n -> Vector (Int, Int) -> SemisparseSuppSeq n
SemisparseSuppSeq ((n -> n) -> Vector n -> Vector n
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b) -> v a -> v b
Arr.map n -> n
forall a. Num a => a -> a
negate Vector n
v) Vector (Int, Int)
vis
  
instance (Num n, UArr.Unbox n) => VectorSpace (SemisparseSuppSeq n) where
  type Scalar (SemisparseSuppSeq n) = n
  Scalar (SemisparseSuppSeq n)
μ *^ :: Scalar (SemisparseSuppSeq n)
-> SemisparseSuppSeq n -> SemisparseSuppSeq n
*^ SemisparseSuppSeq Vector n
v Vector (Int, Int)
ix = Vector n -> Vector (Int, Int) -> SemisparseSuppSeq n
forall n. Vector n -> Vector (Int, Int) -> SemisparseSuppSeq n
SemisparseSuppSeq ((n -> n) -> Vector n -> Vector n
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b) -> v a -> v b
Arr.map (n
Scalar (SemisparseSuppSeq n)
μn -> n -> n
forall a. Num a => a -> a -> a
*) Vector n
v) Vector (Int, Int)
ix

instance (Num n, UArr.Unbox n) => FreeVectorSpace (SemisparseSuppSeq n) where
  SemisparseSuppSeq n
u ^*^ :: SemisparseSuppSeq n -> SemisparseSuppSeq n -> SemisparseSuppSeq n
^*^ SemisparseSuppSeq n
v =  -- TODO: faster, direct implementation
      SparseSuppSeq n -> SemisparseSuppSeq n
forall n. Unbox n => SparseSuppSeq n -> SemisparseSuppSeq n
asSemisparse (SparseSuppSeq n -> SemisparseSuppSeq n)
-> SparseSuppSeq n -> SemisparseSuppSeq n
forall a b. (a -> b) -> a -> b
$ SemisparseSuppSeq n -> SparseSuppSeq n
forall n. Unbox n => SemisparseSuppSeq n -> SparseSuppSeq n
fromSemisparse SemisparseSuppSeq n
u SparseSuppSeq n -> SparseSuppSeq n -> SparseSuppSeq n
forall v. FreeVectorSpace v => v -> v -> v
^*^ SemisparseSuppSeq n -> SparseSuppSeq n
forall n. Unbox n => SemisparseSuppSeq n -> SparseSuppSeq n
fromSemisparse SemisparseSuppSeq n
v
  vmap :: (Scalar (SemisparseSuppSeq n) -> Scalar (SemisparseSuppSeq n))
-> SemisparseSuppSeq n -> SemisparseSuppSeq n
vmap Scalar (SemisparseSuppSeq n) -> Scalar (SemisparseSuppSeq n)
f (SemisparseSuppSeq Vector n
v Vector (Int, Int)
ix) = Vector n -> Vector (Int, Int) -> SemisparseSuppSeq n
forall n. Vector n -> Vector (Int, Int) -> SemisparseSuppSeq n
SemisparseSuppSeq ((n -> n) -> Vector n -> Vector n
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b) -> v a -> v b
Arr.map n -> n
Scalar (SemisparseSuppSeq n) -> Scalar (SemisparseSuppSeq n)
f Vector n
v) Vector (Int, Int)
ix

instance (Num n, AdditiveGroup n, UArr.Unbox n) => InnerSpace (SemisparseSuppSeq n) where
  SemisparseSuppSeq n
v <.> :: SemisparseSuppSeq n
-> SemisparseSuppSeq n -> Scalar (SemisparseSuppSeq n)
<.> SemisparseSuppSeq n
w = SemisparseSuppSeq n -> SparseSuppSeq n
forall n. Unbox n => SemisparseSuppSeq n -> SparseSuppSeq n
fromSemisparse SemisparseSuppSeq n
v SparseSuppSeq n -> SparseSuppSeq n -> Scalar (SparseSuppSeq n)
forall v. InnerSpace v => v -> v -> Scalar v
<.> SemisparseSuppSeq n -> SparseSuppSeq n
forall n. Unbox n => SemisparseSuppSeq n -> SparseSuppSeq n
fromSemisparse SemisparseSuppSeq n
w

instance (Num n, UArr.Unbox n) => HasBasis (SemisparseSuppSeq n) where
  type Basis (SemisparseSuppSeq n) = Int
  basisValue :: Basis (SemisparseSuppSeq n) -> SemisparseSuppSeq n
basisValue Basis (SemisparseSuppSeq n)
i = Vector n -> Vector (Int, Int) -> SemisparseSuppSeq n
forall n. Vector n -> Vector (Int, Int) -> SemisparseSuppSeq n
SemisparseSuppSeq (n -> Vector n
forall a. Unbox a => a -> Vector a
UArr.singleton n
1) ((Int, Int) -> Vector (Int, Int)
forall a. Unbox a => a -> Vector a
UArr.singleton (Int
Basis (SemisparseSuppSeq n)
i,Int
1))
  decompose :: SemisparseSuppSeq n
-> [(Basis (SemisparseSuppSeq n), Scalar (SemisparseSuppSeq n))]
decompose = SparseSuppSeq n -> [(Int, n)]
forall v. HasBasis v => v -> [(Basis v, Scalar v)]
decompose (SparseSuppSeq n -> [(Int, n)])
-> (SemisparseSuppSeq n -> SparseSuppSeq n)
-> SemisparseSuppSeq n
-> [(Int, n)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SemisparseSuppSeq n -> SparseSuppSeq n
forall n. Unbox n => SemisparseSuppSeq n -> SparseSuppSeq n
fromSemisparse
  decompose' :: SemisparseSuppSeq n
-> Basis (SemisparseSuppSeq n) -> Scalar (SemisparseSuppSeq n)
decompose' SemisparseSuppSeq n
v = SparseSuppSeq n
-> Basis (SparseSuppSeq n) -> Scalar (SparseSuppSeq n)
forall v. HasBasis v => v -> Basis v -> Scalar v
decompose' (SparseSuppSeq n
 -> Basis (SparseSuppSeq n) -> Scalar (SparseSuppSeq n))
-> SparseSuppSeq n
-> Basis (SparseSuppSeq n)
-> Scalar (SparseSuppSeq n)
forall a b. (a -> b) -> a -> b
$ SemisparseSuppSeq n -> SparseSuppSeq n
forall n. Unbox n => SemisparseSuppSeq n -> SparseSuppSeq n
fromSemisparse SemisparseSuppSeq n
v

instance (UArr.Unbox n, Eq n, Num n) => IsList (SemisparseSuppSeq n) where
  type Item (SemisparseSuppSeq n) = n
  fromListN :: Int -> [Item (SemisparseSuppSeq n)] -> SemisparseSuppSeq n
fromListN Int
n = SparseSuppSeq n -> SemisparseSuppSeq n
forall n. Unbox n => SparseSuppSeq n -> SemisparseSuppSeq n
asSemisparse (SparseSuppSeq n -> SemisparseSuppSeq n)
-> ([n] -> SparseSuppSeq n) -> [n] -> SemisparseSuppSeq n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Item (SparseSuppSeq n)] -> SparseSuppSeq n
forall l. IsList l => Int -> [Item l] -> l
fromListN Int
n
  fromList :: [Item (SemisparseSuppSeq n)] -> SemisparseSuppSeq n
fromList = SparseSuppSeq n -> SemisparseSuppSeq n
forall n. Unbox n => SparseSuppSeq n -> SemisparseSuppSeq n
asSemisparse (SparseSuppSeq n -> SemisparseSuppSeq n)
-> ([n] -> SparseSuppSeq n) -> [n] -> SemisparseSuppSeq n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [n] -> SparseSuppSeq n
forall l. IsList l => [Item l] -> l
fromList
  toList :: SemisparseSuppSeq n -> [Item (SemisparseSuppSeq n)]
toList = SparseSuppSeq n -> [n]
forall l. IsList l => l -> [Item l]
toList (SparseSuppSeq n -> [n])
-> (SemisparseSuppSeq n -> SparseSuppSeq n)
-> SemisparseSuppSeq n
-> [n]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SemisparseSuppSeq n -> SparseSuppSeq n
forall n. Unbox n => SemisparseSuppSeq n -> SparseSuppSeq n
fromSemisparse