Skip to content

Commit

Permalink
Add direction support
Browse files Browse the repository at this point in the history
--HG--
extra : convert_revision : a88d9ffd30e266d75d865b5c0168f8c4e0263808
  • Loading branch information
bos committed Sep 15, 2010
1 parent 55a5198 commit 136272d
Show file tree
Hide file tree
Showing 3 changed files with 40 additions and 19 deletions.
52 changes: 33 additions & 19 deletions Data/Text/ICU/Char.hs
Expand Up @@ -17,35 +17,38 @@ module Data.Text.ICU.Char
, Direction(..)
-- * Functions
, blockCode
, direction
) where

import Data.Char (ord)
import Data.Text.ICU.Internal (UChar32)
import Data.Typeable (Typeable)
import Foreign.C.Types (CInt)

-- | The language directional property of a character set.
data Direction =
LeftToRight -- ^ L
| RightToLeft -- ^ R
| EuropeanNumber -- ^ EN
| EuropeanNumberSeparator -- ^ ES
| EuropeanNumberTerminator -- ^ ET
| ArabicNumber -- ^ AN
| CommonNumberSeparator -- ^ CS
| BlockSeparator -- ^ B
| SegmentSeparator -- ^ S
| WhiteSpaceNeutral -- ^ WS
| OtherNeutral -- ^ ON
| LeftToRightEmbedding -- ^ LRE
| LeftToRightOverride -- ^ LRO
| RightToLeftArabic -- ^ AL
| RightToLeftEmbedding -- ^ RLE
| RightToLeftOverride -- ^ RLO
| PopDirectionalFormat -- ^ PDF
| DirNonSpacingMark -- ^ NSM
| BoundaryNeutral -- ^ BN
LeftToRight
| RightToLeft
| EuropeanNumber
| EuropeanNumberSeparator
| EuropeanNumberTerminator
| ArabicNumber
| CommonNumberSeparator
| BlockSeparator
| SegmentSeparator
| WhiteSpaceNeutral
| OtherNeutral
| LeftToRightEmbedding
| LeftToRightOverride
| RightToLeftArabic
| RightToLeftEmbedding
| RightToLeftOverride
| PopDirectionalFormat
| DirNonSpacingMark
| BoundaryNeutral
deriving (Eq, Enum, Bounded, Show, Typeable)

-- | Descriptions of Unicode blocks.
data BlockCode =
NoBlock
| BasicLatin
Expand Down Expand Up @@ -227,7 +230,18 @@ blockCode :: Char -> BlockCode
blockCode = toEnum . fromIntegral . ublock_getCode . fromIntegral . ord
{-# INLINE blockCode #-}

-- | Returns the bidirectional category value for the code point,
-- which is used in the Unicode bidirectional algorithm (UAX #9
-- <http://www.unicode.org/reports/tr9/>).
direction :: Char -> Direction
direction = toEnum . fromIntegral . u_charDirection . fromIntegral . ord
{-# INLINE direction #-}

type UBlockCode = CInt
type UCharDirection = CInt

foreign import ccall unsafe "hs_text_icu.h __hs_ublock_getCode" ublock_getCode
:: UChar32 -> UBlockCode

foreign import ccall unsafe "hs_text_icu.h __hs_u_charDirection" u_charDirection
:: UChar32 -> UCharDirection
5 changes: 5 additions & 0 deletions cbits/text_icu.c
Expand Up @@ -280,3 +280,8 @@ UBlockCode __hs_ublock_getCode(UChar32 c)
{
return ublock_getCode(c);
}

UCharDirection __hs_u_charDirection(UChar32 c)
{
return u_charDirection(c);
}
2 changes: 2 additions & 0 deletions include/hs_text_icu.h
Expand Up @@ -5,6 +5,7 @@
#include "unicode/utypes.h"

#include "unicode/ubrk.h"
#include "unicode/uchar.h"
#include "unicode/ucol.h"
#include "unicode/ucnv.h"
#include "unicode/uiter.h"
Expand Down Expand Up @@ -32,6 +33,7 @@ int32_t __hs_ubrk_getRuleStatusVec(UBreakIterator *bi, int32_t *fillInVec,
/* uchar.h */

UBlockCode __hs_ublock_getCode(UChar32 c);
UCharDirection __hs_u_charDirection(UChar32 c);

/* ucol.h */

Expand Down

0 comments on commit 136272d

Please sign in to comment.