[commit: hsc2hs] master: Improve the implementation of stringify (0cb9781)

git at git.haskell.org git at git.haskell.org
Wed Oct 1 09:45:18 UTC 2014


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

On branch  : master
Link       : http://git.haskell.org/hsc2hs.git/commitdiff/0cb9781b9f9eb7590ad8594e0b7a0cd886c127cb

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

commit 0cb9781b9f9eb7590ad8594e0b7a0cd886c127cb
Author: David Feuer <David.Feuer at gmail.com>
Date:   Wed Oct 1 11:41:24 2014 +0200

    Improve the implementation of stringify
    
    The new version should be faster and allocate considerably
    less. It's also at least as simple as the old version.


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

0cb9781b9f9eb7590ad8594e0b7a0cd886c127cb
 CrossCodegen.hs | 26 +++++++++++++++-----------
 1 file changed, 15 insertions(+), 11 deletions(-)

diff --git a/CrossCodegen.hs b/CrossCodegen.hs
index db9b124..5a62d05 100644
--- a/CrossCodegen.hs
+++ b/CrossCodegen.hs
@@ -384,7 +384,9 @@ binarySearch z nonNegative l u = do
         mid = (l+u+1) `div` 2
     inTopHalf <- compareConst z (GreaterOrEqual $ (if nonNegative then Unsigned else Signed) mid)
     let (l',u') = if inTopHalf then (mid,u) else (l,(mid-1))
-    assert (mid > l && mid <= u && u > l && u' >= l' && u' - l' < u - l && u' <= u && l' >= l)
+    assert (l < mid && mid <= u &&             -- l < mid <= u
+            l <= l' && l' <= u' && u' <= u &&  -- l <= l' <= u' <= u
+            u'-l' < u-l)                       -- |u' - l'| < |u - l|
            (binarySearch z nonNegative l' u')
 
 -- Establishes bounds on the unknown integer. By searching increasingly
@@ -426,17 +428,19 @@ haskellize (firstLetter:next) = toLower firstLetter : loop False next
           loop _ ('_':as) = loop True as
           loop upper (a:as) = (if upper then toUpper a else toLower a) : loop False as
 
--- For #{enum} codegen; in normal hsc2hs, any whitespace in the enum types & constructors
--- will be mangled by the C preprocessor. This mimics the same mangling.
+-- For #{enum} codegen; in normal hsc2hs, any whitespace in the enum types &
+-- constructors will be mangled by the C preprocessor. This mimics the same
+-- mangling.
 stringify :: String -> String
-stringify s = reverse .  dropWhile isSpace . reverse -- drop trailing space
-              . dropWhile isSpace                    -- drop leading space
-              . compressSpaces                       -- replace each span of
-                                                     -- whitespace with a single space
-              $ s
-    where compressSpaces [] = []
-          compressSpaces (a:as) | isSpace a = ' ' : compressSpaces (dropWhile isSpace as)
-          compressSpaces (a:as) = a : compressSpaces as
+-- Spec: stringify = unwords . words
+stringify xs = go False (dropWhile isSpace xs)
+  where
+    go _haveSpace [] = []
+    go  haveSpace (x:xs)
+      | isSpace x = go True xs
+      | otherwise = if haveSpace
+                    then ' ' : x : go False xs
+                    else x : go False xs
 
 computeEnum :: ZCursor Token -> TestMonad String
 computeEnum z@(ZCursor (Special _ _ enumText) _ _) = 



More information about the ghc-commits mailing list