summaryrefslogtreecommitdiff
path: root/libraries/ghc-boot
diff options
context:
space:
mode:
authorSylvain Henry <sylvain@haskus.fr>2020-11-30 11:15:13 +0100
committerMarge Bot <ben+marge-bot@smart-cactus.org>2020-12-11 22:42:48 -0500
commit76be0e32d6638c04521b74421a9ce2380593fb54 (patch)
tree4ed92438a09861d6d23692611f4985de51fc4264 /libraries/ghc-boot
parent690c894616a539c59cb8e58d2bba8b9c02c5ad4c (diff)
downloadhaskell-76be0e32d6638c04521b74421a9ce2380593fb54.tar.gz
Move SizedSeq into ghc-boot
Diffstat (limited to 'libraries/ghc-boot')
-rw-r--r--libraries/ghc-boot/GHC/Data/SizedSeq.hs48
-rw-r--r--libraries/ghc-boot/ghc-boot.cabal.in1
2 files changed, 49 insertions, 0 deletions
diff --git a/libraries/ghc-boot/GHC/Data/SizedSeq.hs b/libraries/ghc-boot/GHC/Data/SizedSeq.hs
new file mode 100644
index 0000000000..b48791d863
--- /dev/null
+++ b/libraries/ghc-boot/GHC/Data/SizedSeq.hs
@@ -0,0 +1,48 @@
+{-# LANGUAGE StandaloneDeriving, DeriveGeneric #-}
+module GHC.Data.SizedSeq
+ ( SizedSeq(..)
+ , emptySS
+ , addToSS
+ , addListToSS
+ , ssElts
+ , sizeSS
+ ) where
+
+import Prelude -- See note [Why do we import Prelude here?]
+import Control.DeepSeq
+import Data.Binary
+import Data.List
+import GHC.Generics
+
+data SizedSeq a = SizedSeq {-# UNPACK #-} !Word [a]
+ deriving (Generic, Show)
+
+instance Functor SizedSeq where
+ fmap f (SizedSeq sz l) = SizedSeq sz (fmap f l)
+
+instance Foldable SizedSeq where
+ foldr f c ss = foldr f c (ssElts ss)
+
+instance Traversable SizedSeq where
+ traverse f (SizedSeq sz l) = SizedSeq sz . reverse <$> traverse f (reverse l)
+
+instance Binary a => Binary (SizedSeq a)
+
+instance NFData a => NFData (SizedSeq a) where
+ rnf (SizedSeq _ xs) = rnf xs
+
+emptySS :: SizedSeq a
+emptySS = SizedSeq 0 []
+
+addToSS :: SizedSeq a -> a -> SizedSeq a
+addToSS (SizedSeq n r_xs) x = SizedSeq (n+1) (x:r_xs)
+
+addListToSS :: SizedSeq a -> [a] -> SizedSeq a
+addListToSS (SizedSeq n r_xs) xs
+ = SizedSeq (n + genericLength xs) (reverse xs ++ r_xs)
+
+ssElts :: SizedSeq a -> [a]
+ssElts (SizedSeq _ r_xs) = reverse r_xs
+
+sizeSS :: SizedSeq a -> Word
+sizeSS (SizedSeq n _) = n
diff --git a/libraries/ghc-boot/ghc-boot.cabal.in b/libraries/ghc-boot/ghc-boot.cabal.in
index 45f8fcc1d8..2dec48f034 100644
--- a/libraries/ghc-boot/ghc-boot.cabal.in
+++ b/libraries/ghc-boot/ghc-boot.cabal.in
@@ -39,6 +39,7 @@ Library
exposed-modules:
GHC.BaseDir
GHC.Data.ShortText
+ GHC.Data.SizedSeq
GHC.Utils.Encoding
GHC.LanguageExtensions
GHC.Unit.Database