Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Bidi s = Bidi {
- embeddingLevels :: IORef (Ptr Level)
- parentLink :: IORef (Maybe (Bidi s))
- getBidi :: ForeignPtr UBiDi
- pattern MAP_NOWHERE :: Int
- open :: PrimMonad m => m (Bidi (PrimState m))
- openSized :: PrimMonad m => Int32 -> Int32 -> m (Bidi (PrimState m))
- countParagraphs :: PrimMonad m => Bidi (PrimState m) -> m Int32
- countRuns :: PrimMonad m => Bidi (PrimState m) -> m Int32
- getCustomizedClass :: PrimMonad m => Bidi (PrimState m) -> Char -> m CharDirection
- getLength :: PrimMonad m => Bidi (PrimState m) -> m Int32
- getLevelAt :: PrimMonad m => Bidi (PrimState m) -> Int32 -> m Level
- getLevels :: PrimMonad m => Bidi (PrimState m) -> m (PrimArray Level)
- getLogicalIndex :: PrimMonad m => Bidi (PrimState m) -> Int32 -> m Int32
- getLogicalMap :: PrimMonad m => Bidi (PrimState m) -> m (PrimArray Int32)
- getLogicalRun :: PrimMonad m => Bidi (PrimState m) -> Int32 -> m (Int32, Level)
- getParaLevel :: PrimMonad m => Bidi (PrimState m) -> m Level
- getParagraph :: PrimMonad m => Bidi (PrimState m) -> Int32 -> m (Int32, Int32, Int32, Level)
- getParagraphByIndex :: PrimMonad m => Bidi (PrimState m) -> Int32 -> m (Int32, Int32, Level)
- getProcessedLength :: PrimMonad m => Bidi (PrimState m) -> m Int32
- getResultLength :: PrimMonad m => Bidi (PrimState m) -> m Int32
- getText :: PrimMonad m => Bidi (PrimState m) -> m Text
- getVisualIndex :: PrimMonad m => Bidi (PrimState m) -> Int32 -> m Int32
- getVisualMap :: PrimMonad m => Bidi (PrimState m) -> m (PrimArray Int32)
- getVisualRun :: PrimMonad m => Bidi (PrimState m) -> Int32 -> m (Int32, Int32, Direction)
- invertMap :: PrimArray Int32 -> PrimArray Int32
- isInverse :: PrimMonad m => Bidi (PrimState m) -> m Bool
- isOrderParagraphsLTR :: PrimMonad m => Bidi (PrimState m) -> m Bool
- orderParagraphsLTR :: PrimMonad m => Bidi (PrimState m) -> Bool -> m ()
- reorderLogical :: PrimArray Level -> PrimArray Int32
- reorderVisual :: PrimArray Level -> PrimArray Int32
- setContext :: PrimMonad m => Bidi (PrimState m) -> Text -> Text -> m ()
- setInverse :: PrimMonad m => Bidi (PrimState m) -> Bool -> m ()
- setLine :: PrimMonad m => Bidi (PrimState m) -> Int32 -> Int32 -> Bidi (PrimState m) -> m ()
- setPara :: PrimMonad m => Bidi (PrimState m) -> Text -> Level -> Maybe (Vector Level) -> m ()
- newtype Level where
- Level Word8
- pattern DEFAULT_LTR :: Level
- pattern DEFAULT_RTL :: Level
- pattern MAX_EXPLICIT_LEVEL :: Level
- isRTL :: Level -> Bool
- isLTR :: Level -> Bool
- isOverride :: Level -> Bool
- override :: Level -> Level
- pattern LEVEL_OVERRIDE :: Word8
- data Direction
- getBaseDirection :: Text -> Direction
- getDirection :: PrimMonad m => Bidi (PrimState m) -> m Direction
- data ReorderingMode
- getReorderingMode :: PrimMonad m => Bidi (PrimState m) -> m ReorderingMode
- setReorderingMode :: PrimMonad m => Bidi (PrimState m) -> ReorderingMode -> m ()
- newtype ReorderingOption where
- ReorderingOption Int32
- pattern OPTION_DEFAULT :: ReorderingOption
- pattern OPTION_INSERT_MARKS :: ReorderingOption
- pattern OPTION_REMOVE_CONTROLS :: ReorderingOption
- pattern OPTION_STREAMING :: ReorderingOption
- getReorderingOptions :: PrimMonad m => Bidi (PrimState m) -> m ReorderingOption
- setReorderingOptions :: PrimMonad m => Bidi (PrimState m) -> ReorderingOption -> m ()
- newtype CharDirection where
- CharDirection Int32
- pattern LEFT_TO_RIGHT :: CharDirection
- pattern RIGHT_TO_LEFT :: CharDirection
- pattern EUROPEAN_NUMBER :: CharDirection
- pattern EUROPEAN_NUMBER_SEPARATOR :: CharDirection
- pattern EUROPEAN_NUMBER_TERMINATOR :: CharDirection
- pattern ARABIC_NUMBER :: CharDirection
- pattern COMMON_NUMBER_SEPARATOR :: CharDirection
- pattern BLOCK_SEPARATOR :: CharDirection
- pattern SEGMENT_SEPARATOR :: CharDirection
- pattern WHITE_SPACE_NEUTRAL :: CharDirection
- pattern OTHER_NEUTRAL :: CharDirection
- pattern LEFT_TO_RIGHT_EMBEDDING :: CharDirection
- pattern LEFT_TO_RIGHT_OVERRIDE :: CharDirection
- pattern RIGHT_TO_LEFT_ARABIC :: CharDirection
- pattern RIGHT_TO_LEFT_EMBEDDING :: CharDirection
- pattern RIGHT_TO_LEFT_OVERRIDE :: CharDirection
- pattern POP_DIRECTIONAL_FORMAT :: CharDirection
- pattern DIR_NON_SPACING_MARK :: CharDirection
- pattern BOUNDARY_NEUTRAL :: CharDirection
- pattern FIRST_STRONG_ISOLATE :: CharDirection
- pattern LEFT_TO_RIGHT_ISOLATE :: CharDirection
- pattern RIGHT_TO_LEFT_ISOLATE :: CharDirection
- pattern POP_DIRECTIONAL_ISOLATE :: CharDirection
- pattern BIDI_CLASS_DEFAULT :: CharDirection
- type ClassCallback = Ptr () -> Int32 -> IO CharDirection
- mkClassCallback :: ClassCallback -> IO (FunPtr ClassCallback)
- setClassCallback :: PrimMonad m => Bidi (PrimState m) -> FunPtr ClassCallback -> Ptr () -> m (FunPtr ClassCallback, Ptr ())
- getClassCallback :: PrimMonad m => Bidi (PrimState m) -> m (FunPtr ClassCallback, Ptr ())
- newtype WriteOptions where
- WriteOptions Int16
- pattern DO_MIRRORING :: WriteOptions
- pattern INSERT_LRM_FOR_NUMERIC :: WriteOptions
- pattern KEEP_BASE_COMBINING :: WriteOptions
- pattern REMOVE_BIDI_CONTROLS :: WriteOptions
- pattern OUTPUT_REVERSE :: WriteOptions
- writeReordered :: PrimMonad m => Bidi (PrimState m) -> WriteOptions -> m Text
- writeReverse :: Text -> WriteOptions -> Text
- data UBiDi
- newtype UErrorCode = UErrorCode Int32
Documentation
Bidi | |
|
pattern MAP_NOWHERE :: Int Source #
Special value which can be returned by the mapping functions when a logical index has no corresponding visual index or vice-versa.
Returned by getVisualIndex
, getVisualMap
, getLogicalIndex
, getLogicalMap
countParagraphs :: PrimMonad m => Bidi (PrimState m) -> m Int32 Source #
getCustomizedClass :: PrimMonad m => Bidi (PrimState m) -> Char -> m CharDirection Source #
getLogicalMap :: PrimMonad m => Bidi (PrimState m) -> m (PrimArray Int32) Source #
getParaLevel :: PrimMonad m => Bidi (PrimState m) -> m Level Source #
getParagraph :: PrimMonad m => Bidi (PrimState m) -> Int32 -> m (Int32, Int32, Int32, Level) Source #
Given a paragraph or line bidirectional object bidi
, and a charIndex
into the text
in the range 0
to
, this will return
the index of the paragraph, the index of the first character in the text,
the index of the end of the paragraph, and the level of the paragraph.getProcessedLength
bidi -1
If the paragraph index is known, it can be more efficient to use getParagraphByIndex
getParagraphByIndex :: PrimMonad m => Bidi (PrimState m) -> Int32 -> m (Int32, Int32, Level) Source #
getProcessedLength :: PrimMonad m => Bidi (PrimState m) -> m Int32 Source #
getResultLength :: PrimMonad m => Bidi (PrimState m) -> m Int32 Source #
getVisualMap :: PrimMonad m => Bidi (PrimState m) -> m (PrimArray Int32) Source #
getVisualRun :: PrimMonad m => Bidi (PrimState m) -> Int32 -> m (Int32, Int32, Direction) Source #
Get one run's logical start, length, and directionality which will be LTR or RTL.
countRuns
should be called before the runs are retrieved
isOrderParagraphsLTR :: PrimMonad m => Bidi (PrimState m) -> m Bool Source #
orderParagraphsLTR :: PrimMonad m => Bidi (PrimState m) -> Bool -> m () Source #
reorderLogical :: PrimArray Level -> PrimArray Int32 Source #
reorderVisual :: PrimArray Level -> PrimArray Int32 Source #
setInverse :: PrimMonad m => Bidi (PrimState m) -> Bool -> m () Source #
setLine :: PrimMonad m => Bidi (PrimState m) -> Int32 -> Int32 -> Bidi (PrimState m) -> m () Source #
setPara :: PrimMonad m => Bidi (PrimState m) -> Text -> Level -> Maybe (Vector Level) -> m () Source #
Levels
pattern DEFAULT_LTR :: Level | |
pattern DEFAULT_RTL :: Level | |
pattern MAX_EXPLICIT_LEVEL :: Level |
Instances
Eq Level Source # | |
Ord Level Source # | |
Show Level Source # | |
Storable Level Source # | |
Prim Level Source # | |
Defined in Data.Text.ICU.Bidi alignment# :: Level -> Int# indexByteArray# :: ByteArray# -> Int# -> Level readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Level #) writeByteArray# :: MutableByteArray# s -> Int# -> Level -> State# s -> State# s setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Level -> State# s -> State# s indexOffAddr# :: Addr# -> Int# -> Level readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Level #) writeOffAddr# :: Addr# -> Int# -> Level -> State# s -> State# s setOffAddr# :: Addr# -> Int# -> Int# -> Level -> State# s -> State# s |
isOverride :: Level -> Bool Source #
pattern LEVEL_OVERRIDE :: Word8 Source #
Direction
Instances
getBaseDirection :: Text -> Direction Source #
getDirection :: PrimMonad m => Bidi (PrimState m) -> m Direction Source #
Reordering
data ReorderingMode Source #
ReorderDefault | |
ReorderNumbersSpecial | |
ReorderGroupNumbersWithR | |
ReorderRunsOnly | |
ReorderInverseNumbersAsL | |
ReorderInverseLikeDirect | |
ReorderInverseForNumbersSpecial | |
ReorderCount |
Instances
getReorderingMode :: PrimMonad m => Bidi (PrimState m) -> m ReorderingMode Source #
setReorderingMode :: PrimMonad m => Bidi (PrimState m) -> ReorderingMode -> m () Source #
newtype ReorderingOption Source #
ReorderingOption
values indicate which options are
specified to affect the Bidi algorithm.
pattern OPTION_DEFAULT :: ReorderingOption | option for @since ICU 3.6 |
pattern OPTION_INSERT_MARKS :: ReorderingOption | @since ICU 3.6 |
pattern OPTION_REMOVE_CONTROLS :: ReorderingOption | @since ICU 3.6 |
pattern OPTION_STREAMING :: ReorderingOption |
Instances
getReorderingOptions :: PrimMonad m => Bidi (PrimState m) -> m ReorderingOption Source #
setReorderingOptions :: PrimMonad m => Bidi (PrimState m) -> ReorderingOption -> m () Source #
Character Direction Classes
newtype CharDirection Source #
Character Directions.
This is morally the same as text-icu's Direction type, but that one is missing a few definitions =(
When issue 44 is resolved, this will
be able to be text.icu's Data.Text.ICU.Char.Direction
.
Instances
type ClassCallback = Ptr () -> Int32 -> IO CharDirection Source #
mkClassCallback :: ClassCallback -> IO (FunPtr ClassCallback) Source #
setClassCallback :: PrimMonad m => Bidi (PrimState m) -> FunPtr ClassCallback -> Ptr () -> m (FunPtr ClassCallback, Ptr ()) Source #
getClassCallback :: PrimMonad m => Bidi (PrimState m) -> m (FunPtr ClassCallback, Ptr ()) Source #
Writing
newtype WriteOptions Source #
pattern DO_MIRRORING :: WriteOptions | |
pattern INSERT_LRM_FOR_NUMERIC :: WriteOptions | |
pattern KEEP_BASE_COMBINING :: WriteOptions | |
pattern REMOVE_BIDI_CONTROLS :: WriteOptions | |
pattern OUTPUT_REVERSE :: WriteOptions |
Instances
writeReordered :: PrimMonad m => Bidi (PrimState m) -> WriteOptions -> m Text Source #
writeReverse :: Text -> WriteOptions -> Text Source #
Internal
newtype UErrorCode Source #