From 2926e6e5c1947375879d9dbe0f678c61cb129ce5 Mon Sep 17 00:00:00 2001
From: simonmar <unknown>
Date: Mon, 25 Sep 2000 11:32:55 +0000
Subject: [PATCH] [project @ 2000-09-25 11:32:55 by simonmar] INLINE is_ctype,
 otherwise charType gets inlined in the RHS by virtue of only being used once,
 and we lose the opportunity to inline is_ctype.

---
 ghc/compiler/parser/Ctype.lhs | 1 +
 1 file changed, 1 insertion(+)

diff --git a/ghc/compiler/parser/Ctype.lhs b/ghc/compiler/parser/Ctype.lhs
index adcaec27efbb..4d9c6007d727 100644
--- a/ghc/compiler/parser/Ctype.lhs
+++ b/ghc/compiler/parser/Ctype.lhs
@@ -35,6 +35,7 @@ The predicates below look costly, but aren't, GHC+GCC do a great job
 at the big case below.
 
 \begin{code}
+{-# INLINE is_ctype #-}
 is_ctype :: Int -> Char# -> Bool
 is_ctype mask c = (fromIntegral (charType (C# c)) .&. fromIntegral mask) /= (0::Int32)
 
-- 
GitLab