[Git][ghc/ghc][wip/no-dlist] compiler: replace DList with OrdList
Cheng Shao pushed to branch wip/no-dlist at Glasgow Haskell Compiler / GHC Commits: 9f4f8a7a by Cheng Shao at 2025-12-08T10:33:08+01:00 compiler: replace DList with OrdList This patch removes `DList` logic from the compiler and replaces it with `OrdList` which also supports O(1) concatenation and should be more memory efficient than the church-encoded `DList`. - - - - - 2 changed files: - compiler/GHC/Parser/String.hs - compiler/GHC/StgToCmm/InfoTableProv.hs Changes: ===================================== compiler/GHC/Parser/String.hs ===================================== @@ -21,6 +21,7 @@ import Data.Char (chr, ord) import qualified Data.Foldable1 as Foldable1 import qualified Data.List.NonEmpty as NonEmpty import Data.Maybe (listToMaybe, mapMaybe) +import GHC.Data.OrdList (fromOL, nilOL, snocOL) import GHC.Data.StringBuffer (StringBuffer) import qualified GHC.Data.StringBuffer as StringBuffer import GHC.Parser.CharClass ( @@ -169,16 +170,16 @@ collapseGaps = go [] -> panic "gap unexpectedly ended" resolveEscapes :: HasChar c => [c] -> Either (c, LexErr) [c] -resolveEscapes = go dlistEmpty +resolveEscapes = go nilOL where go !acc = \case - [] -> pure $ dlistToList acc + [] -> pure $ fromOL acc Char '\\' : Char '&' : cs -> go acc cs backslash@(Char '\\') : cs -> case resolveEscapeChar cs of - Right (esc, cs') -> go (acc `dlistSnoc` setChar esc backslash) cs' + Right (esc, cs') -> go (acc `snocOL` setChar esc backslash) cs' Left (c, e) -> Left (c, e) - c : cs -> go (acc `dlistSnoc` c) cs + c : cs -> go (acc `snocOL` c) cs -- ----------------------------------------------------------------------------- -- Escape characters @@ -422,17 +423,3 @@ It's more precisely defined with the following algorithm: * Lines with only whitespace characters 3. Calculate the longest prefix of whitespace shared by all lines in the remaining list -} - --- ----------------------------------------------------------------------------- --- DList - -newtype DList a = DList ([a] -> [a]) - -dlistEmpty :: DList a -dlistEmpty = DList id - -dlistToList :: DList a -> [a] -dlistToList (DList f) = f [] - -dlistSnoc :: DList a -> a -> DList a -dlistSnoc (DList f) x = DList (f . (x :)) ===================================== compiler/GHC/StgToCmm/InfoTableProv.hs ===================================== @@ -11,6 +11,7 @@ import GHC.IO (unsafePerformIO) #endif import Data.Char +import Data.Foldable import GHC.Prelude import GHC.Platform import GHC.Types.SrcLoc (pprUserRealSpan, srcSpanFile) @@ -18,6 +19,7 @@ import GHC.Types.Unique.DSM import GHC.Unit.Module import GHC.Utils.Outputable import GHC.Data.FastString (fastStringToShortText, unpackFS, LexicalFastString(..)) +import GHC.Data.OrdList (OrdList, nilOL, snocOL) import GHC.Cmm import GHC.Cmm.CLabel @@ -286,7 +288,7 @@ data CgInfoProvEnt = CgInfoProvEnt , ipeSrcSpan :: !StrTabOffset } -data StringTable = StringTable { stStrings :: DList ShortText +data StringTable = StringTable { stStrings :: !(OrdList ShortText) , stLength :: !Int , stLookup :: !(M.Map ShortText StrTabOffset) } @@ -295,7 +297,7 @@ type StrTabOffset = Word32 emptyStringTable :: StringTable emptyStringTable = - StringTable { stStrings = emptyDList + StringTable { stStrings = nilOL , stLength = 0 , stLookup = M.empty } @@ -303,7 +305,7 @@ emptyStringTable = getStringTableStrings :: StringTable -> BS.ByteString getStringTableStrings st = BSL.toStrict $ BSB.toLazyByteString - $ foldMap f $ dlistToList (stStrings st) + $ foldMap' f $ stStrings st where f x = BSB.shortByteString (ST.contents x) `mappend` BSB.word8 0 @@ -312,7 +314,7 @@ lookupStringTable str = state $ \st -> case M.lookup str (stLookup st) of Just off -> (off, st) Nothing -> - let !st' = st { stStrings = stStrings st `snoc` str + let !st' = st { stStrings = stStrings st `snocOL` str , stLength = stLength st + ST.byteLength str + 1 , stLookup = M.insert str res (stLookup st) } @@ -359,14 +361,3 @@ foreign import ccall unsafe "ZSTD_compressBound" defaultCompressionLevel :: Int defaultCompressionLevel = 3 - -newtype DList a = DList ([a] -> [a]) - -emptyDList :: DList a -emptyDList = DList id - -snoc :: DList a -> a -> DList a -snoc (DList f) x = DList (f . (x:)) - -dlistToList :: DList a -> [a] -dlistToList (DList f) = f [] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9f4f8a7a906bc3a8d9bbccbd33b95663... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9f4f8a7a906bc3a8d9bbccbd33b95663... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Cheng Shao (@TerrorJack)