[commit: packages/containers] changelog-foldtree, cleaned_bugfix394, develop-0.6, develop-0.6-questionable, master, merge-doc-target, merge-fixes-5.9, merge-restrict-fix-5.8, revert-184-generic, revert-408-bugfix_394: Add Data.Sequence.fromArray. (52ba9e5)

git at git.haskell.org git at git.haskell.org
Mon Apr 17 21:36:17 UTC 2017


Repository : ssh://git@git.haskell.org/containers

On branches: changelog-foldtree,cleaned_bugfix394,develop-0.6,develop-0.6-questionable,master,merge-doc-target,merge-fixes-5.9,merge-restrict-fix-5.8,revert-184-generic,revert-408-bugfix_394
Link       : http://git.haskell.org/packages/containers.git/commitdiff/52ba9e5d9c85d4bd11236c1e43b4847a50a3b771

>---------------------------------------------------------------

commit 52ba9e5d9c85d4bd11236c1e43b4847a50a3b771
Author: Milan Straka <fox at ucw.cz>
Date:   Mon Dec 15 17:58:46 2014 +0100

    Add Data.Sequence.fromArray.
    
    Sugested by David Feuer in #88.
    
    The implementation on GHC uses GHC.Arr module and is considerably faster
    than on non-GHC compilers.


>---------------------------------------------------------------

52ba9e5d9c85d4bd11236c1e43b4847a50a3b771
 Data/Sequence.hs        | 19 +++++++++++++++++++
 tests/seq-properties.hs |  6 ++++++
 2 files changed, 25 insertions(+)

diff --git a/Data/Sequence.hs b/Data/Sequence.hs
index 2e8f84c..690a9fe 100644
--- a/Data/Sequence.hs
+++ b/Data/Sequence.hs
@@ -62,6 +62,7 @@ module Data.Sequence (
     (><),           -- :: Seq a -> Seq a -> Seq a
     fromList,       -- :: [a] -> Seq a
     fromFunction,   -- :: Int -> (Int -> a) -> Seq a
+    fromArray,      -- :: Ix i => Array i a -> Seq a
     -- ** Repetition
     replicate,      -- :: Int -> a -> Seq a
     replicateA,     -- :: Applicative f => Int -> f a -> f (Seq a)
@@ -180,6 +181,13 @@ import Text.Read (Lexeme(Ident), lexP, parens, prec,
 import Data.Data
 #endif
 
+-- Array stuff, with GHC.Arr on GHC
+import Data.Array (Ix, Array)
+import qualified Data.Array
+#ifdef __GLASGOW_HASKELL__
+import qualified GHC.Arr
+#endif
+
 -- Coercion on GHC 7.8+
 #if __GLASGOW_HASKELL__ >= 708
 import Data.Coerce
@@ -1399,6 +1407,17 @@ fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with neg
 #endif
     {-# INLINE lift_elem #-}
 
+-- | /O(n)/. Create a sequence consisting of the elements of an 'Array'.
+-- Note that the resulting sequence elements may be evaluated lazily (as on GHC),
+-- so you must force the entire structure to be sure that the original array
+-- can be garbage-collected.
+fromArray :: Ix i => Array i a -> Seq a
+#ifdef __GLASGOW_HASKELL__
+fromArray a = fromFunction (GHC.Arr.numElements a) (GHC.Arr.unsafeAt a)
+#else
+fromArray a = fromList2 (Data.Array.rangeSize (Data.Array.bounds a)) (Data.Array.elems a)
+#endif
+
 -- Splitting
 
 -- | /O(log(min(i,n-i)))/. The first @i@ elements of a sequence.
diff --git a/tests/seq-properties.hs b/tests/seq-properties.hs
index 14d5a5f..a64e66d 100644
--- a/tests/seq-properties.hs
+++ b/tests/seq-properties.hs
@@ -2,6 +2,7 @@ import Data.Sequence    -- needs to be compiled with -DTESTING for use here
 
 import Control.Applicative (Applicative(..))
 import Control.Arrow ((***))
+import Data.Array (listArray)
 import Data.Foldable (Foldable(..), toList, all, sum)
 import Data.Functor ((<$>), (<$))
 import Data.Maybe
@@ -37,6 +38,7 @@ main = defaultMain
        , testProperty "(><)" prop_append
        , testProperty "fromList" prop_fromList
        , testProperty "fromFunction" prop_fromFunction
+       , testProperty "fromArray" prop_fromArray
        , testProperty "replicate" prop_replicate
        , testProperty "replicateA" prop_replicateA
        , testProperty "replicateM" prop_replicateM
@@ -275,6 +277,10 @@ prop_fromFunction :: [A] -> Bool
 prop_fromFunction xs =
     toList' (fromFunction (Prelude.length xs) (xs!!)) ~= xs
 
+prop_fromArray :: [A] -> Bool
+prop_fromArray xs =
+    toList' (fromArray (listArray (42, 42+Prelude.length xs-1) xs)) ~= xs
+
 -- ** Repetition
 
 prop_replicate :: NonNegative Int -> A -> Bool



More information about the ghc-commits mailing list