unicode-tricks-0.11.0.0: Functions to work with unicode blocks more convenient.
Maintainerhapytexeu+gh@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe
LanguageHaskell2010

Data.Char.Brackets

Description

Unicode considers 60 characters to be brackets: brackets are organized in pairs: each opening bracket has a corresponding closing bracket and vice versa.

The following characters are considered brackets where the first character is closed by the last character, the second by the last but one, etc.:

([{༺༼᚛⁅⁽₍⌈⌊〈❨❪❬❮❰❲❴⟅⟦⟨⟪⟬⟮⦃⦅⦇⦉⦋⦍⦏⦑⦓⦕⦗⧘⧚⧼⸢⸤⸦⸨〈《「『【〔〖〘〚﹙﹛﹝([{⦅「」⦆}])﹞﹜﹚〛〙〗〕】』」》〉⸩⸧⸥⸣⧽⧛⧙⦘⦖⦔⦒⦎⦐⦌⦊⦈⦆⦄⟯⟭⟫⟩⟧⟆❵❳❱❯❭❫❩〉⌋⌉₎⁾⁆᚜༽༻}])

These characters span over several code blocks.

Synopsis

Listing and converting brackets

bracketMaps :: [(Char, Char)] Source #

A list of 2-tuples where the first item of each tuple is the opening bracket, and the second item its closing counterpart.

brackets Source #

Arguments

:: [Char]

The list of all Chars that are brackets.

The list of all brackets characters.

openBrackets Source #

Arguments

:: [Char]

The list of all Chars that are opening brackets.

A list of Chars that contains all opening brackets.

closeBrackets Source #

Arguments

:: [Char]

The list of all Chars that are closing brackets.

A list of Chars that contains all closing brackets.

toOpen :: Map Char Char Source #

A Map that maps the given close bracket characters to the corresponding open bracket.

toClose :: Map Char Char Source #

A Map that maps the given open bracket characters to the corresponding close bracket.

Check the given bracket type

data BracketType Source #

A data type that is used to specify the type of bracket.

Constructors

Open

The bracket is used to "open" a context.

Close

The bracket is used to "close" a context.

Instances

Instances details
Bounded BracketType Source # 
Instance details

Defined in Data.Char.Brackets

Enum BracketType Source # 
Instance details

Defined in Data.Char.Brackets

Eq BracketType Source # 
Instance details

Defined in Data.Char.Brackets

Data BracketType Source # 
Instance details

Defined in Data.Char.Brackets

Methods

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

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

toConstr :: BracketType -> Constr #

dataTypeOf :: BracketType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BracketType Source # 
Instance details

Defined in Data.Char.Brackets

Read BracketType Source # 
Instance details

Defined in Data.Char.Brackets

Show BracketType Source # 
Instance details

Defined in Data.Char.Brackets

Generic BracketType Source # 
Instance details

Defined in Data.Char.Brackets

Associated Types

type Rep BracketType :: Type -> Type #

Arbitrary BracketType Source # 
Instance details

Defined in Data.Char.Brackets

NFData BracketType Source # 
Instance details

Defined in Data.Char.Brackets

Methods

rnf :: BracketType -> () #

Hashable BracketType Source # 
Instance details

Defined in Data.Char.Brackets

type Rep BracketType Source # 
Instance details

Defined in Data.Char.Brackets

type Rep BracketType = D1 ('MetaData "BracketType" "Data.Char.Brackets" "unicode-tricks-0.11.0.0-C7NrNgm5l6sAip6k96QRri" 'False) (C1 ('MetaCons "Open" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Close" 'PrefixI 'False) (U1 :: Type -> Type))

isBracket Source #

Arguments

:: Char

The given Char to test.

-> Bool

True if the given Char is an open bracket; False otherwise.

Check if the given Char is a bracket character.

bracketType :: Char -> Maybe BracketType Source #

Check the BracketType of the Char wrapped in a Just data construct; Nothing if the given Char is not a bracket character.

bracketType' :: Char -> BracketType Source #

Check the BracketType of the Char. For a Char that is not a bracket the behavior is unspecified.

isOpenBracket Source #

Arguments

:: Char

The given Char to test.

-> Bool

True if the Char is an open bracket; False otherwise.

Check if the given Char is an open bracket.

isCloseBracket Source #

Arguments

:: Char

The given Char to test.

-> Bool

True if the Char is an close bracket; False otherwise.

Check if the given Char is a close bracket.

Determine the opposite bracket

getOppositeChar Source #

Arguments

:: Char

The given Char for which we want to determine the opposite bracket.

-> Maybe Char

The opposite bracket wrapped in a Just if the given Char is a bracket character; Nothing otherwise.

Get the bracket character that is the counterpart of the given bracket character wrapped in a Just data constructor. If the given Char is not a bracket, Nothing is returned.

getOppositeChar' Source #

Arguments

:: Char

The given Char for which we want to determine the opposite bracket.

-> Char

The opposite bracket if the given Char is a bracket; otherwise the given Char.

Get the bracket character that is the counterpart of the given bracket character. If the given Char is not a bracket, the given Char is returned.