License | GPL-3 |
---|---|
Stability | experimental |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
Extensions |
|
Text.BBCode
Description
Usually you only need to import that module, which reexports most of the functionality.
If you need lens
definitions for types, import Text.BBCode.Lens
If you need interface to parsing, see Text.BBCode.Parser
Synopsis
- nl :: BBCode
- hr :: BBCode
- br :: BBCode
- clear :: BBCode
- listEl :: BBCode
- text :: Text -> BBCode
- doc :: [BBCode] -> BBCode
- docNL :: [BBCode] -> BBCode
- bold :: BBCode -> BBCode
- italic :: BBCode -> BBCode
- underline :: BBCode -> BBCode
- strikethrough :: BBCode -> BBCode
- indent :: BBCode -> BBCode
- nfo :: BBCode -> BBCode
- oneline :: BBCode -> BBCode
- code :: Text -> BBCode
- pre :: Text -> BBCode
- box :: BBCode -> BBCode
- image :: Text -> BBCode
- quote :: BBCode -> BBCode
- spoiler :: BBCode -> BBCode
- list :: [BBCode] -> BBCode
- boxAlign :: BoxPosition -> BBCode -> BBCode
- imageAlign :: ImagePosition -> Text -> BBCode
- quoteNamed :: Text -> BBCode -> BBCode
- spoilerNamed :: Text -> BBCode -> BBCode
- listFlavor :: Foldable t => ListFlavor -> t BBCode -> BBCode
- color :: Text -> BBCode -> BBCode
- url :: Text -> BBCode -> BBCode
- size :: Natural -> BBCode -> BBCode
- align :: AlignPosition -> BBCode -> BBCode
- font :: Text -> BBCode -> BBCode
- data BBCode where
- data El
- class IsArgument a where
- toArgument :: a -> Text
- data ListFlavor where
- data AlignPosition where
- data ImagePosition where
- data BoxPosition where
- pretty :: BBCode -> Text
- bbcode :: Parser BBCode
- runParserMaybeEnv :: ParsecT e s (Reader r) a -> r -> s -> Maybe a
Builder
Functions for constructing AST in a more elegant way than directly using type constructors.
This wrappers are usually no more than partially applied data
constructors. An exception to that is list
and listFlavor
functions,
which adds listEl
before each element. This is implementation detail
and shouldn't bother you unless you work with AST directly
Void elements
Void elements' data constructors only specify the type of the
element(e.g. HR
, Clear
, ...
),
such element don't have any content unlike other types of elements.
see ElVoid
Notice it is not a function, but a value.
listEl
represents "[*]"
listEl == 'ElVoid' 'ListElement'
Simple elements
Simple elements have contents, usually BBCode
. text
is not actually a
simple element builder and included here just for convenience
see ElSimple
docNL :: [BBCode] -> BBCode Source #
intersperse
list with nl
and wrap it in ElDocument
strikethrough :: BBCode -> BBCode Source #
list :: [BBCode] -> BBCode Source #
Each element of list is prepended with listElement
, meaning you can't
create list with contents but without elements
>>>
list [bold "10", italic "15"]
ElSimple List (ElDocument [ElVoid ListElement,ElSimple Bold (ElText "10"),ElVoid ListElement,ElSimple Italic (ElText "15")])
Elements with an argument
Apart from having contents, following elements also have argument. It can indicate position, color, or something else.
see ElArg
imageAlign :: ImagePosition -> Text -> BBCode Source #
Like image
but with alignment argument
listFlavor :: Foldable t => ListFlavor -> t BBCode -> BBCode Source #
Ordered list
>>>
listFlavor LatinUpper [bold "I am bald", boxAlign BoxRight "get boxxxed"]
ElArg List "A" (ElDocument [ElVoid ListElement,ElSimple Bold (ElText "I am bald"),ElVoid ListElement,ElArg Box "right" (ElText "get boxxxed")])
color :: Text -> BBCode -> BBCode Source #
Change color of inner BBCode First argument is either color name (e.g. blue) or hex color(e.g. #333 or #151515)
url :: Text -> BBCode -> BBCode Source #
Create a hyperlink
first argument is expected to be valid URL
size :: Natural -> BBCode -> BBCode Source #
Change font size of inner bbcode
arg
∈ [10, 29] and arg
is natural
font :: Text -> BBCode -> BBCode Source #
Change font of inner BBCode
argument should be a valid font name
Types
BBCode AST
Constructors
ElVoid :: El -> BBCode | Element that has neither closing part nor arguments |
ElSimple :: El -> BBCode -> BBCode | Element that has closing part but no arguments |
ElArg :: El -> Text -> BBCode -> BBCode | Element that has closing part and exactly one argument
|
ElText :: Text -> BBCode | Plain text
|
ElDocument :: [BBCode] -> BBCode | Just a list of BBCode elements, just as type signature says.
|
Instances
IsString BBCode Source # | Allows easier BBCode construction
|
Defined in Text.BBCode.Internal.Types Methods fromString :: String -> BBCode Source # | |
Monoid BBCode Source # | Identity is defined as zero-width Text
|
Semigroup BBCode Source # | |
Show BBCode Source # | Don't use it to render BBCode! |
Eq BBCode Source # | |
Type of an element. BBCode
declares three constructors for elements: ElVoid
, ElSimple
, ElArg
. But El
can be split into four cateogories:
1) void elements,
2) simple elements,
3) elements with optional argument,
4) element with one argument
There is no enforcement of combining BBCode
constuctors and El
values, that means you can create ElSimple HR (ElText "smth")
but that would make no sense. pretty
would emit a runtime error if you try to pass such value.
Constructors
HR | void element |
BR | void element |
Clear | void element |
ListElement | void element |
Bold | simple element |
Italic | simple element |
Underline | simple element |
Strikethrough | simple element |
Indent | simple element |
NFO | simple element |
Oneline | simple element |
Code | simple element |
Preformatted | simple element |
Box | element with optional argument |
Image | element with optional argument |
Quote | element with optional argument |
Spoiler | element with optional argument |
List | element with optional argument |
Color | element with one argument |
URL | element with one argument |
Size | element with one argument |
Align | element with one argument |
Font | element with one argument |
class IsArgument a where Source #
Used for building BBCode safely. Instead of passing Text
to builder functions,
you pass values of types that implement IsArgument
. Then toArgument
is used
to convert that value to Text.
Methods
toArgument :: a -> Text Source #
Instances
IsArgument AlignPosition Source # | |
Defined in Text.BBCode.Internal.Types Methods toArgument :: AlignPosition -> Text Source # | |
IsArgument BoxPosition Source # | |
Defined in Text.BBCode.Internal.Types Methods toArgument :: BoxPosition -> Text Source # | |
IsArgument ImagePosition Source # | |
Defined in Text.BBCode.Internal.Types Methods toArgument :: ImagePosition -> Text Source # | |
IsArgument ListFlavor Source # | |
Defined in Text.BBCode.Internal.Types Methods toArgument :: ListFlavor -> Text Source # |
data ListFlavor where Source #
Argument to listFlavor
Constructors
Roman :: ListFlavor | Numeric 1, 2, 3,.. |
ArabicUpper :: ListFlavor | Arabic I, II, III,.. |
ArabicLower :: ListFlavor | Arabic i, ii, iii,.. |
LatinUpper :: ListFlavor | Alphabetical A, B, C,.. |
LatinLower :: ListFlavor | Alphabetical a, b, c,.. |
Instances
Show ListFlavor Source # | |
Defined in Text.BBCode.Internal.Types | |
IsArgument ListFlavor Source # | |
Defined in Text.BBCode.Internal.Types Methods toArgument :: ListFlavor -> Text Source # | |
Eq ListFlavor Source # | |
Defined in Text.BBCode.Internal.Types Methods (==) :: ListFlavor -> ListFlavor -> Bool Source # (/=) :: ListFlavor -> ListFlavor -> Bool Source # |
Alignment and position
There are three different position types because align
, image
,
boxAlign
all have different sets of valid positions. You can notice
that all these types have different number of valid positions.
data AlignPosition where Source #
Argument to align
Constructors
AlignLeft :: AlignPosition | |
AlignRight :: AlignPosition | |
AlignCenter :: AlignPosition | |
AlignJustify :: AlignPosition |
Instances
Show AlignPosition Source # | |
Defined in Text.BBCode.Internal.Types | |
IsArgument AlignPosition Source # | |
Defined in Text.BBCode.Internal.Types Methods toArgument :: AlignPosition -> Text Source # | |
Eq AlignPosition Source # | |
Defined in Text.BBCode.Internal.Types Methods (==) :: AlignPosition -> AlignPosition -> Bool Source # (/=) :: AlignPosition -> AlignPosition -> Bool Source # |
data ImagePosition where Source #
Argument to imageAlign
Constructors
ImageLeft :: ImagePosition | |
ImageRight :: ImagePosition |
Instances
Show ImagePosition Source # | |
Defined in Text.BBCode.Internal.Types | |
IsArgument ImagePosition Source # | |
Defined in Text.BBCode.Internal.Types Methods toArgument :: ImagePosition -> Text Source # | |
Eq ImagePosition Source # | |
Defined in Text.BBCode.Internal.Types Methods (==) :: ImagePosition -> ImagePosition -> Bool Source # (/=) :: ImagePosition -> ImagePosition -> Bool Source # |
data BoxPosition where Source #
Argument to boxAlign
Constructors
BoxLeft :: BoxPosition | |
BoxCenter :: BoxPosition | |
BoxRight :: BoxPosition |
Instances
Show BoxPosition Source # | |
Defined in Text.BBCode.Internal.Types | |
IsArgument BoxPosition Source # | |
Defined in Text.BBCode.Internal.Types Methods toArgument :: BoxPosition -> Text Source # | |
Eq BoxPosition Source # | |
Defined in Text.BBCode.Internal.Types Methods (==) :: BoxPosition -> BoxPosition -> Bool Source # (/=) :: BoxPosition -> BoxPosition -> Bool Source # |
Pretty-printer
pretty :: BBCode -> Text Source #
Serialize BBCode AST
Parsing
should give you pretty
xx
, but currently that rarely works mostly
because of whitespaces. Whitespaces are appended when prettifying, but not
stripped when parsing. This leads to redundant whitespaces in parsed AST
Can cause error at runtime if unrepresentable element is passed
>>>
pretty $ ElSimple HR "abc"
Prelude.undefined
Parser
A small part of Text.BBCode.Parser. Dedicated module has an interface to parsing specific elements as well as different parser runners.
These should be sufficient for parsing whole document.
bbcode :: Parser BBCode Source #
Parse zero or more BBCode elements
Doesn't necessarily return value wrapped in ElDocument
, it returns
(
if it parses no elements, or just element if parses
just one element. Otherwise it is mempty
:: BBCode)ElDocument
runParserMaybeEnv :: ParsecT e s (Reader r) a -> r -> s -> Maybe a Source #
parseMaybe
specialized for Parser