Skip to content

Commit

Permalink
in stage1, we should get isPrint and isUpper from Compat.Unicode, not…
Browse files Browse the repository at this point in the history
… Data.Char
  • Loading branch information
Simon Marlow committed Mar 29, 2006
1 parent c117f1b commit 274a7b1
Show file tree
Hide file tree
Showing 2 changed files with 13 additions and 4 deletions.
6 changes: 3 additions & 3 deletions ghc/compiler/parser/Lexer.x
Original file line number Diff line number Diff line change
Expand Up @@ -44,14 +44,14 @@ import Ctype
import Util ( maybePrefixMatch, readRational )

import DATA_BITS
import Data.Char
import Data.Char ( chr )
import Ratio
--import TRACE

#if __GLASGOW_HASKELL__ >= 605
import Data.Char ( GeneralCategory(..), generalCategory )
import Data.Char ( GeneralCategory(..), generalCategory, isPrint, isUpper )
#else
import Compat.Unicode ( GeneralCategory(..), generalCategory )
import Compat.Unicode ( GeneralCategory(..), generalCategory, isPrint, isUpper )
#endif
}

Expand Down
11 changes: 10 additions & 1 deletion ghc/lib/compat/Compat/Unicode.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
{-# OPTIONS -cpp #-}
module Compat.Unicode (
GeneralCategory(..), generalCategory,
GeneralCategory(..), generalCategory, isPrint, isUpper
) where

#if __GLASGOW_HASKELL__ > 604
Expand Down Expand Up @@ -54,4 +54,13 @@ generalCategory c = toEnum (wgencat (fromIntegral (ord c)))

foreign import ccall unsafe "u_gencat"
wgencat :: CInt -> Int

isPrint c = iswprint (fromIntegral (ord c)) /= 0
isUpper c = iswupper (fromIntegral (ord c)) /= 0

foreign import ccall unsafe "u_iswprint"
iswprint :: CInt -> CInt

foreign import ccall unsafe "u_iswupper"
iswupper :: CInt -> CInt
#endif

0 comments on commit 274a7b1

Please sign in to comment.