[GHC] #14222: Simple text fusion example results in rather duplicative code
GHC
ghc-devs at haskell.org
Tue Sep 12 08:31:05 UTC 2017
#14222: Simple text fusion example results in rather duplicative code
-------------------------------------+-------------------------------------
Reporter: bgamari | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Consider this program,
{{{#!hs
module T14221 where
import Data.Text as T
isNumeric :: Text -> Bool
isNumeric t =
T.all isNumeric' t && T.any isNumber t
where
isNumber c = '0' <= c && c <= '9'
isNumeric' c = isNumber c
|| c == 'e'
|| c == 'E'
|| c == '.'
|| c == '-'
|| c == '+'
}}}
Compiling with `-O` results in over 1 kilobyte of assembler. After looking
at the simplified Core the issue becomes apparent: the case analysis of
`isNumeric'` is duplicated six times,
{{{#!hs
case ww4_X2zB of {
__DEFAULT -> GHC.Types.False;
'+'# -> jump $wloop_all_s2z2 (GHC.Prim.+# ww3_s2z0 2#);
'-'# -> jump $wloop_all_s2z2 (GHC.Prim.+# ww3_s2z0 2#);
'.'# -> jump $wloop_all_s2z2 (GHC.Prim.+# ww3_s2z0 2#);
'E'# -> jump $wloop_all_s2z2 (GHC.Prim.+# ww3_s2z0 2#);
'e'# -> jump $wloop_all_s2z2 (GHC.Prim.+# ww3_s2z0 2#)
};
}}}
It seems to me that we would ideally try to share this bit. Of course,
this may be quite tricky to do in practice.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14222>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list