Skip to content

Commit

Permalink
Character mirroring
Browse files Browse the repository at this point in the history
--HG--
extra : convert_revision : e301814f80625d4a88d2934fc2e2d45623f981cb
  • Loading branch information
bos committed Sep 15, 2010
1 parent 136272d commit 0d4c18b
Show file tree
Hide file tree
Showing 3 changed files with 47 additions and 2 deletions.
37 changes: 35 additions & 2 deletions Data/Text/ICU/Char.hs
Expand Up @@ -18,10 +18,12 @@ module Data.Text.ICU.Char
-- * Functions
, blockCode
, direction
, isMirrored
, mirror
) where

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

Expand Down Expand Up @@ -237,6 +239,31 @@ direction :: Char -> Direction
direction = toEnum . fromIntegral . u_charDirection . fromIntegral . ord
{-# INLINE direction #-}

-- | Determines whether the code point has the @Bidi_Mirrored@
-- property. This property is set for characters that are commonly
-- used in Right-To-Left contexts and need to be displayed with a
-- "mirrored" glyph.
isMirrored :: Char -> Bool
isMirrored = asBool . u_isMirrored . fromIntegral . ord
{-# INLINE isMirrored #-}

-- Map the specified character to a "mirror-image" character.
--
-- For characters with the @Bidi_Mirrored@ property, implementations
-- sometimes need a "poor man's" mapping to another Unicode (code
-- point) such that the default glyph may serve as the mirror image of
-- the default glyph of the specified character. This is useful for
-- text conversion to and from codepages with visual order, and for
-- displays without glyph selection capabilities.
--
-- The return value is another Unicode code point that may serve as a
-- mirror-image substitute, or the original character itself if there
-- is no such mapping or the character lacks the @Bidi_Mirrored@
-- property.
mirror :: Char -> Char
mirror = chr . fromIntegral . u_charMirror . fromIntegral . ord
{-# INLINE mirror #-}

type UBlockCode = CInt
type UCharDirection = CInt

Expand All @@ -245,3 +272,9 @@ foreign import ccall unsafe "hs_text_icu.h __hs_ublock_getCode" ublock_getCode

foreign import ccall unsafe "hs_text_icu.h __hs_u_charDirection" u_charDirection
:: UChar32 -> UCharDirection

foreign import ccall unsafe "hs_text_icu.h __hs_u_isMirrored" u_isMirrored
:: UChar32 -> UBool

foreign import ccall unsafe "hs_text_icu.h __hs_u_charMirror" u_charMirror
:: UChar32 -> UChar32
10 changes: 10 additions & 0 deletions cbits/text_icu.c
Expand Up @@ -285,3 +285,13 @@ UCharDirection __hs_u_charDirection(UChar32 c)
{
return u_charDirection(c);
}

UBool __hs_u_isMirrored(UChar32 c)
{
return u_isMirrored(c);
}

UChar32 __hs_u_charMirror(UChar32 c)
{
return u_charMirror(c);
}
2 changes: 2 additions & 0 deletions include/hs_text_icu.h
Expand Up @@ -34,6 +34,8 @@ int32_t __hs_ubrk_getRuleStatusVec(UBreakIterator *bi, int32_t *fillInVec,

UBlockCode __hs_ublock_getCode(UChar32 c);
UCharDirection __hs_u_charDirection(UChar32 c);
UBool __hs_u_isMirrored(UChar32 c);
UChar32 __hs_u_charMirror(UChar32 c);

/* ucol.h */

Expand Down

0 comments on commit 0d4c18b

Please sign in to comment.