Skip to content
Snippets Groups Projects
Commit a650e95f authored by Ian Lynagh's avatar Ian Lynagh
Browse files

Make Distribution.Compat.Char for isSymbol; fixes the build with GHC 6.4

parent e740aa57
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE CPP, ForeignFunctionInterface #-}
{-# OPTIONS_GHC -cpp -fffi #-}
{-# OPTIONS_NHC98 -cpp #-}
{-# OPTIONS_JHC -fcpp #-}
-- #hide
module Distribution.Compat.Char (isSymbol) where
import Data.Char
#if defined(__GLASGOW_HASKELL__) && (__GLASGOW_HASKELL__ < 606)
import Foreign.C
isSymbol :: Char -> Bool
isSymbol c = case generalCategory c of
MathSymbol -> True
CurrencySymbol -> True
ModifierSymbol -> True
OtherSymbol -> True
_ -> False
-- Euch euch euch: This isn't at all nice. isSymbol is actually defined in
-- GHC.Unicode, but not exported! And nor is generalCategory.
generalCategory :: Char -> GeneralCategory
generalCategory c = toEnum (wgencat (fromIntegral (ord c)))
data GeneralCategory
= UppercaseLetter -- Lu Letter, Uppercase
| LowercaseLetter -- Ll Letter, Lowercase
| TitlecaseLetter -- Lt Letter, Titlecase
| ModifierLetter -- Lm Letter, Modifier
| OtherLetter -- Lo Letter, Other
| NonSpacingMark -- Mn Mark, Non-Spacing
| SpacingCombiningMark -- Mc Mark, Spacing Combining
| EnclosingMark -- Me Mark, Enclosing
| DecimalNumber -- Nd Number, Decimal
| LetterNumber -- Nl Number, Letter
| OtherNumber -- No Number, Other
| ConnectorPunctuation -- Pc Punctuation, Connector
| DashPunctuation -- Pd Punctuation, Dash
| OpenPunctuation -- Ps Punctuation, Open
| ClosePunctuation -- Pe Punctuation, Close
| InitialQuote -- Pi Punctuation, Initial quote
| FinalQuote -- Pf Punctuation, Final quote
| OtherPunctuation -- Po Punctuation, Other
| MathSymbol -- Sm Symbol, Math
| CurrencySymbol -- Sc Symbol, Currency
| ModifierSymbol -- Sk Symbol, Modifier
| OtherSymbol -- So Symbol, Other
| Space -- Zs Separator, Space
| LineSeparator -- Zl Separator, Line
| ParagraphSeparator -- Zp Separator, Paragraph
| Control -- Cc Other, Control
| Format -- Cf Other, Format
| Surrogate -- Cs Other, Surrogate
| PrivateUse -- Co Other, Private Use
| NotAssigned -- Cn Other, Not Assigned
deriving (Eq, Ord, Enum, Read, Show, Bounded)
foreign import ccall unsafe "u_gencat"
wgencat :: CInt -> Int
#endif
...@@ -72,7 +72,8 @@ import Distribution.Simple.Utils (intercalate, lowercase) ...@@ -72,7 +72,8 @@ import Distribution.Simple.Utils (intercalate, lowercase)
import Language.Haskell.Extension (Extension) import Language.Haskell.Extension (Extension)
import Text.PrettyPrint.HughesPJ hiding (braces) import Text.PrettyPrint.HughesPJ hiding (braces)
import Data.Char (isSpace, isUpper, toLower, isAlphaNum, isSymbol, isDigit) import Data.Char (isSpace, isUpper, toLower, isAlphaNum, isDigit)
import Distribution.Compat.Char (isSymbol)
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import Data.Tree as Tree (Tree(..), flatten) import Data.Tree as Tree (Tree(..), flatten)
import System.FilePath (normalise) import System.FilePath (normalise)
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment