Skip to content

Commit

Permalink
Make sparse polynomials a special case of multivariate
Browse files Browse the repository at this point in the history
  • Loading branch information
Bodigrim committed Sep 15, 2020
1 parent 0ded6de commit 809d6bf
Show file tree
Hide file tree
Showing 23 changed files with 1,291 additions and 1,041 deletions.
19 changes: 13 additions & 6 deletions poly.cabal
Expand Up @@ -26,23 +26,30 @@ library
exposed-modules:
Data.Poly
Data.Poly.Laurent
Data.Poly.Orthogonal
Data.Poly.Semiring
Data.Poly.Orthogonal

Data.Poly.Sparse
Data.Poly.Sparse.Laurent
Data.Poly.Sparse.Multi
Data.Poly.Sparse.Semiring

Data.Poly.Multi
Data.Poly.Multi.Laurent
Data.Poly.Multi.Semiring
other-modules:
Data.Poly.Internal.Convert

Data.Poly.Internal.Dense
Data.Poly.Internal.Dense.Field
Data.Poly.Internal.Dense.DFT
Data.Poly.Internal.Dense.GcdDomain
Data.Poly.Internal.Dense.Laurent
Data.Poly.Internal.Sparse
Data.Poly.Internal.Sparse.Field
Data.Poly.Internal.Sparse.GcdDomain
Data.Poly.Internal.Sparse.Laurent

Data.Poly.Internal.Multi
Data.Poly.Internal.Multi.Core
Data.Poly.Internal.Multi.Field
Data.Poly.Internal.Multi.GcdDomain
Data.Poly.Internal.Multi.Laurent
build-depends:
base >= 4.9 && < 5,
deepseq >= 1.1 && < 1.5,
Expand Down
44 changes: 33 additions & 11 deletions src/Data/Poly/Internal/Convert.hs
Expand Up @@ -7,6 +7,7 @@
-- Conversions between polynomials.
--

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}

module Data.Poly.Internal.Convert
Expand All @@ -20,46 +21,67 @@ import Control.Monad.ST
import Data.Semiring (Semiring(..))
import qualified Data.Vector.Generic as G
import qualified Data.Vector.Generic.Mutable as MG
import qualified Data.Vector.Unboxed.Sized as SU

import qualified Data.Poly.Internal.Dense as Dense
import qualified Data.Poly.Internal.Sparse as Sparse
import qualified Data.Poly.Internal.Multi as Sparse

-- | Convert from dense to sparse polynomials.
--
-- >>> :set -XFlexibleContexts
-- >>> denseToSparse (1 + Data.Poly.X^2) :: Data.Poly.Sparse.UPoly Int
-- 1 * X^2 + 1
denseToSparse :: (Eq a, Num a, G.Vector v a, G.Vector v (Word, a)) => Dense.Poly v a -> Sparse.Poly v a
denseToSparse
:: (Eq a, Num a, G.Vector v a, G.Vector v (SU.Vector 1 Word, a))
=> Dense.Poly v a
-> Sparse.Poly v a
denseToSparse = denseToSparseInternal 0

denseToSparse' :: (Eq a, Semiring a, G.Vector v a, G.Vector v (Word, a)) => Dense.Poly v a -> Sparse.Poly v a
denseToSparse'
:: (Eq a, Semiring a, G.Vector v a, G.Vector v (SU.Vector 1 Word, a))
=> Dense.Poly v a
-> Sparse.Poly v a
denseToSparse' = denseToSparseInternal zero

denseToSparseInternal :: (Eq a, G.Vector v a, G.Vector v (Word, a)) => a -> Dense.Poly v a -> Sparse.Poly v a
denseToSparseInternal z = Sparse.Poly . G.imapMaybe (\i c -> if c == z then Nothing else Just (fromIntegral i, c)) . Dense.unPoly
denseToSparseInternal
:: (Eq a, G.Vector v a, G.Vector v (SU.Vector 1 Word, a))
=> a
-> Dense.Poly v a
-> Sparse.Poly v a
denseToSparseInternal z = Sparse.MultiPoly . G.imapMaybe (\i c -> if c == z then Nothing else Just (fromIntegral i, c)) . Dense.unPoly

-- | Convert from sparse to dense polynomials.
--
-- >>> :set -XFlexibleContexts
-- >>> sparseToDense (1 + Data.Poly.Sparse.X^2) :: Data.Poly.UPoly Int
-- 1 * X^2 + 0 * X + 1
sparseToDense :: (Num a, G.Vector v a, G.Vector v (Word, a)) => Sparse.Poly v a -> Dense.Poly v a
sparseToDense
:: (Num a, G.Vector v a, G.Vector v (SU.Vector 1 Word, a))
=> Sparse.Poly v a
-> Dense.Poly v a
sparseToDense = sparseToDenseInternal 0

sparseToDense' :: (Semiring a, G.Vector v a, G.Vector v (Word, a)) => Sparse.Poly v a -> Dense.Poly v a
sparseToDense'
:: (Semiring a, G.Vector v a, G.Vector v (SU.Vector 1 Word, a))
=> Sparse.Poly v a
-> Dense.Poly v a
sparseToDense' = sparseToDenseInternal zero

sparseToDenseInternal :: (G.Vector v a, G.Vector v (Word, a)) => a -> Sparse.Poly v a -> Dense.Poly v a
sparseToDenseInternal z (Sparse.Poly xs)
sparseToDenseInternal
:: (G.Vector v a, G.Vector v (SU.Vector 1 Word, a))
=> a
-> Sparse.Poly v a
-> Dense.Poly v a
sparseToDenseInternal z (Sparse.MultiPoly xs)
| G.null xs = Dense.Poly G.empty
| otherwise = runST $ do
let len = fromIntegral (fst (G.unsafeLast xs) + 1)
let len = fromIntegral (SU.head (fst (G.unsafeLast xs)) + 1)
ys <- MG.unsafeNew len
MG.set ys z
let go xi yi
| xi >= G.length xs = pure ()
| (yi', c) <- G.unsafeIndex xs xi
, yi == fromIntegral yi'
, yi == fromIntegral (SU.head yi')
= MG.unsafeWrite ys yi c >> go (xi + 1) (yi + 1)
| otherwise = go xi (yi + 1)
go 0 0
Expand Down

0 comments on commit 809d6bf

Please sign in to comment.