bidi-icu-0: The unicode bidirectional algorithm via ICU
Safe HaskellNone
LanguageHaskell2010

Data.Text.ICU.Bidi

Synopsis

Documentation

data Bidi s Source #

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

open :: PrimMonad m => m (Bidi (PrimState m)) Source #

openSized :: PrimMonad m => Int32 -> Int32 -> m (Bidi (PrimState m)) Source #

countParagraphs :: PrimMonad m => Bidi (PrimState m) -> m Int32 Source #

countRuns :: PrimMonad m => Bidi (PrimState m) -> m Int32 Source #

getCustomizedClass :: PrimMonad m => Bidi (PrimState m) -> Char -> m CharDirection Source #

getLength :: PrimMonad m => Bidi (PrimState m) -> m Int32 Source #

getLevelAt :: PrimMonad m => Bidi (PrimState m) -> Int32 -> m Level Source #

getLevels :: PrimMonad m => Bidi (PrimState m) -> m (PrimArray Level) Source #

getLogicalIndex :: PrimMonad m => Bidi (PrimState m) -> Int32 -> m Int32 Source #

getLogicalMap :: PrimMonad m => Bidi (PrimState m) -> m (PrimArray Int32) Source #

getLogicalRun :: PrimMonad m => Bidi (PrimState m) -> Int32 -> m (Int32, Level) 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 getProcessedLength bidi -1, 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.

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 #

getText :: PrimMonad m => Bidi (PrimState m) -> m Text Source #

getVisualIndex :: PrimMonad m => Bidi (PrimState m) -> Int32 -> 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

invertMap :: PrimArray Int32 -> PrimArray Int32 Source #

isInverse :: PrimMonad m => Bidi (PrimState m) -> m Bool Source #

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 #

setContext :: PrimMonad m => Bidi (PrimState m) -> Text -> Text -> m () 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

newtype Level Source #

Constructors

Level Word8 

Bundled Patterns

pattern DEFAULT_LTR :: Level 
pattern DEFAULT_RTL :: Level 
pattern MAX_EXPLICIT_LEVEL :: Level 

Instances

Instances details
Eq Level Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Methods

(==) :: Level -> Level -> Bool #

(/=) :: Level -> Level -> Bool #

Ord Level Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Methods

compare :: Level -> Level -> Ordering #

(<) :: Level -> Level -> Bool #

(<=) :: Level -> Level -> Bool #

(>) :: Level -> Level -> Bool #

(>=) :: Level -> Level -> Bool #

max :: Level -> Level -> Level #

min :: Level -> Level -> Level #

Show Level Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Methods

showsPrec :: Int -> Level -> ShowS #

show :: Level -> String #

showList :: [Level] -> ShowS #

Storable Level Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Methods

sizeOf :: Level -> Int #

alignment :: Level -> Int #

peekElemOff :: Ptr Level -> Int -> IO Level #

pokeElemOff :: Ptr Level -> Int -> Level -> IO () #

peekByteOff :: Ptr b -> Int -> IO Level #

pokeByteOff :: Ptr b -> Int -> Level -> IO () #

peek :: Ptr Level -> IO Level #

poke :: Ptr Level -> Level -> IO () #

Prim Level Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Direction

data Direction Source #

Constructors

LTR 
RTL 
Mixed 
Neutral 

Instances

Instances details
Bounded Direction Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Enum Direction Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Eq Direction Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Data Direction Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Direction -> c Direction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Direction #

toConstr :: Direction -> Constr #

dataTypeOf :: Direction -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Direction) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Direction) #

gmapT :: (forall b. Data b => b -> b) -> Direction -> Direction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Direction -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Direction -> r #

gmapQ :: (forall d. Data d => d -> u) -> Direction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Direction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Direction -> m Direction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Direction -> m Direction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Direction -> m Direction #

Ord Direction Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Show Direction Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Ix Direction Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Generic Direction Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Associated Types

type Rep Direction :: Type -> Type #

type Rep Direction Source # 
Instance details

Defined in Data.Text.ICU.Bidi

type Rep Direction = D1 ('MetaData "Direction" "Data.Text.ICU.Bidi" "bidi-icu-0-inplace" 'False) ((C1 ('MetaCons "LTR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RTL" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Mixed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Neutral" 'PrefixI 'False) (U1 :: Type -> Type)))

getDirection :: PrimMonad m => Bidi (PrimState m) -> m Direction Source #

Reordering

data ReorderingMode Source #

Instances

Instances details
Bounded ReorderingMode Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Enum ReorderingMode Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Eq ReorderingMode Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Data ReorderingMode Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReorderingMode -> c ReorderingMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReorderingMode #

toConstr :: ReorderingMode -> Constr #

dataTypeOf :: ReorderingMode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ReorderingMode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReorderingMode) #

gmapT :: (forall b. Data b => b -> b) -> ReorderingMode -> ReorderingMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReorderingMode -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReorderingMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReorderingMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReorderingMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReorderingMode -> m ReorderingMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReorderingMode -> m ReorderingMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReorderingMode -> m ReorderingMode #

Ord ReorderingMode Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Show ReorderingMode Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Ix ReorderingMode Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Generic ReorderingMode Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Associated Types

type Rep ReorderingMode :: Type -> Type #

type Rep ReorderingMode Source # 
Instance details

Defined in Data.Text.ICU.Bidi

type Rep ReorderingMode = D1 ('MetaData "ReorderingMode" "Data.Text.ICU.Bidi" "bidi-icu-0-inplace" 'False) (((C1 ('MetaCons "ReorderDefault" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ReorderNumbersSpecial" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ReorderGroupNumbersWithR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ReorderRunsOnly" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ReorderInverseNumbersAsL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ReorderInverseLikeDirect" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ReorderInverseForNumbersSpecial" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ReorderCount" 'PrefixI 'False) (U1 :: Type -> Type))))

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.

Constructors

ReorderingOption Int32 

Bundled Patterns

pattern OPTION_DEFAULT :: ReorderingOption

option for setReorderingOptions that disables all the options which can be set with this function

@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

Instances details
Eq ReorderingOption Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Ord ReorderingOption Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Show ReorderingOption Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Bits ReorderingOption Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Default ReorderingOption Source # 
Instance details

Defined in Data.Text.ICU.Bidi

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.

Constructors

CharDirection Int32 

Bundled Patterns

pattern LEFT_TO_RIGHT :: CharDirection

L @stable ICU 2.0

pattern RIGHT_TO_LEFT :: CharDirection

R @stable ICU 2.0

pattern EUROPEAN_NUMBER :: CharDirection

EN @stable ICU 2.0

pattern EUROPEAN_NUMBER_SEPARATOR :: CharDirection

ES @stable ICU 2.0

pattern EUROPEAN_NUMBER_TERMINATOR :: CharDirection

ET @stable ICU 2.0

pattern ARABIC_NUMBER :: CharDirection

AN @stable ICU 2.0

pattern COMMON_NUMBER_SEPARATOR :: CharDirection

CS @stable ICU 2.0

pattern BLOCK_SEPARATOR :: CharDirection

B @stable ICU 2.0

pattern SEGMENT_SEPARATOR :: CharDirection

SS@stable ICU 2.0

pattern WHITE_SPACE_NEUTRAL :: CharDirection

WS @stable ICU 2.0

pattern OTHER_NEUTRAL :: CharDirection

ON @stable ICU 2.0

pattern LEFT_TO_RIGHT_EMBEDDING :: CharDirection

LRE @stable ICU 2.0

pattern LEFT_TO_RIGHT_OVERRIDE :: CharDirection

LRO @stable ICU 2.0

pattern RIGHT_TO_LEFT_ARABIC :: CharDirection

AL @stable ICU 2.0

pattern RIGHT_TO_LEFT_EMBEDDING :: CharDirection

RLE @stable ICU 2.0

pattern RIGHT_TO_LEFT_OVERRIDE :: CharDirection

RLO @stable ICU 2.0

pattern POP_DIRECTIONAL_FORMAT :: CharDirection

PDF @stable ICU 2.0

pattern DIR_NON_SPACING_MARK :: CharDirection

NSM @stable ICU 2.0

pattern BOUNDARY_NEUTRAL :: CharDirection

BN @stable ICU 52

pattern FIRST_STRONG_ISOLATE :: CharDirection

FSI @stable ICU 52

pattern LEFT_TO_RIGHT_ISOLATE :: CharDirection

LRI @stable ICU 52

pattern RIGHT_TO_LEFT_ISOLATE :: CharDirection

RLI @stable ICU 52

pattern POP_DIRECTIONAL_ISOLATE :: CharDirection

PDI @stable ICU 52

pattern BIDI_CLASS_DEFAULT :: CharDirection

ICU 58 The numeric value may change over time, see ICU ticket #12420.

Instances

Instances details
Eq CharDirection Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Ord CharDirection Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Show CharDirection Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Storable CharDirection Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Prim CharDirection Source # 
Instance details

Defined in Data.Text.ICU.Bidi

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 #

Constructors

WriteOptions Int16 

Instances

Instances details
Eq WriteOptions Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Ord WriteOptions Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Show WriteOptions Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Storable WriteOptions Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Bits WriteOptions Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Default WriteOptions Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Methods

def :: WriteOptions

Prim WriteOptions Source # 
Instance details

Defined in Data.Text.ICU.Bidi

writeReordered :: PrimMonad m => Bidi (PrimState m) -> WriteOptions -> m Text Source #

Internal

newtype UErrorCode Source #

Constructors

UErrorCode Int32 

Instances

Instances details
Enum UErrorCode Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Eq UErrorCode Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Integral UErrorCode Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Num UErrorCode Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Ord UErrorCode Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Real UErrorCode Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Show UErrorCode Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Exception UErrorCode Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Storable UErrorCode Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Default UErrorCode Source # 
Instance details

Defined in Data.Text.ICU.Bidi

Methods

def :: UErrorCode