bbcode-0.1.0.1: Library for parsing, constructing, and printing BBCode
LicenseGPL-3
Stabilityexperimental
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageGHC2021
Extensions
  • OverloadedStrings
  • DisambiguateRecordFields
  • RecordWildCards
  • ViewPatterns
  • ApplicativeDo
  • LambdaCase

Text.BBCode

Description

Here is a longer description of this module, containing some commentary with some markup.

Synopsis

Documentation

nl :: BBCode Source #

Newline

nl == 'text' "\n"

text :: Text -> BBCode Source #

text == 'ElText'

hr :: BBCode Source #

Horizontal line

hr == 'ElVoid' 'HR'

br :: BBCode Source #

Line break

br == 'ElVoid' 'BR'

clear :: BBCode Source #

clear == 'ElVoid' 'Clear'

listEl :: BBCode Source #

Notice it is not a function, but a value.

listEl represents "[*]"

listEl == 'ElVoid' 'ListElement'

bold :: BBCode -> BBCode Source #

bold, italic, underline, and all the rest functions BBCode -> BBCode work the same way by wrapping argument in another element.

italic :: BBCode -> BBCode Source #

bold, italic, underline, and all the rest functions BBCode -> BBCode work the same way by wrapping argument in another element.

underline :: BBCode -> BBCode Source #

bold, italic, underline, and all the rest functions BBCode -> BBCode work the same way by wrapping argument in another element.

strikethrough :: BBCode -> BBCode Source #

bold, italic, underline, and all the rest functions BBCode -> BBCode work the same way by wrapping argument in another element.

indent :: BBCode -> BBCode Source #

bold, italic, underline, and all the rest functions BBCode -> BBCode work the same way by wrapping argument in another element.

nfo :: BBCode -> BBCode Source #

bold, italic, underline, and all the rest functions BBCode -> BBCode work the same way by wrapping argument in another element.

oneline :: BBCode -> BBCode Source #

bold, italic, underline, and all the rest functions BBCode -> BBCode work the same way by wrapping argument in another element.

code :: Text -> BBCode Source #

Code element contains plain text

pre :: Text -> BBCode Source #

Preformatted element contains plain text

box :: BBCode -> BBCode Source #

bold, italic, underline, and all the rest functions BBCode -> BBCode work the same way by wrapping argument in another element.

image :: Text -> BBCode Source #

Takes image URL

quote :: BBCode -> BBCode Source #

bold, italic, underline, and all the rest functions BBCode -> BBCode work the same way by wrapping argument in another element.

spoiler :: BBCode -> BBCode Source #

bold, italic, underline, and all the rest functions BBCode -> BBCode work the same way by wrapping argument in another element.

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")])

boxAlign :: BoxPosition -> BBCode -> BBCode Source #

Like box but with alignment argument

imageAlign :: ImagePosition -> Text -> BBCode Source #

Like image but with alignment argument

quoteNamed :: Text -> BBCode -> BBCode Source #

Named quote

spoilerNamed :: Text -> BBCode -> BBCode Source #

Named spoiler

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

data BBCode where Source #

BBCode AST

Constructors

ElVoid :: El -> BBCode

Element that has neither closing part nor arguments

ElVoid HR represents "[hr]"

ElSimple :: El -> BBCode -> BBCode

Element that has closing part but no arguments

ElSimple Bold (ElText "abc") represents "[b]abc[/b]"

ElArg :: El -> Text -> BBCode -> BBCode

Element that has closing part and exactly one argument

ElArg Color "red" (ElText "I am red") represents "[color=red]I am red[/color]"

ElText :: Text -> BBCode

Plain text

ElText "I am text" represents "I am text"@

ElDocument :: [BBCode] -> BBCode

Just a list of BBCode elements, just as type signature says.

ElDocument [ElSimple Bold (ElText "Bold not bald"), ElText "legit text"] represents "[b]Bold not bald[/b]legit text"

Instances

Instances details
IsString BBCode Source #

Allows easier BBCode construction

>>> ElSimple Bold "I am bold"
ElSimple Bold (ElText "I am bold")

Recall that ElSimple takes El and BBCode, but not Text

Instance details

Defined in Text.BBCode.Internal.Types

Monoid BBCode Source #

Identity is defined as zero-width Text

>>> mempty :: BBCode
ElText ""
Instance details

Defined in Text.BBCode.Internal.Types

Semigroup BBCode Source # 
Instance details

Defined in Text.BBCode.Internal.Types

Show BBCode Source #

Don't use it to render BBCode!

Instance details

Defined in Text.BBCode.Internal.Types

Eq BBCode Source # 
Instance details

Defined in Text.BBCode.Internal.Types

data El 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

Instances

Instances details
Bounded El Source #

Addition to Enum instance

Instance details

Defined in Text.BBCode.Internal.Types

Enum El Source #

Allows internal module to quickly list elements of different categories (Void, Simple, Optional, One)

Instance details

Defined in Text.BBCode.Internal.Types

Methods

succ :: El -> El Source #

pred :: El -> El Source #

toEnum :: Int -> El Source #

fromEnum :: El -> Int Source #

enumFrom :: El -> [El] Source #

enumFromThen :: El -> El -> [El] Source #

enumFromTo :: El -> El -> [El] Source #

enumFromThenTo :: El -> El -> El -> [El] Source #

Show El Source # 
Instance details

Defined in Text.BBCode.Internal.Types

Eq El Source # 
Instance details

Defined in Text.BBCode.Internal.Types

Methods

(==) :: El -> El -> Bool Source #

(/=) :: El -> El -> Bool Source #

Ord El Source #

Allows having Map with key type El (used in Parser)

Instance details

Defined in Text.BBCode.Internal.Types

Methods

compare :: El -> El -> Ordering Source #

(<) :: El -> El -> Bool Source #

(<=) :: El -> El -> Bool Source #

(>) :: El -> El -> Bool Source #

(>=) :: El -> El -> Bool Source #

max :: El -> El -> El Source #

min :: El -> El -> El Source #

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 #

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,..

pretty :: BBCode -> Text Source #

Serialize BBCode AST

Should be reversible by parsing, but it is not guaranteed

Can cause error at runtime if unrepresentable element is passed, e.g. >>> pretty $ ElSimple HR "abc" Prelude.undefined

bbcode :: Parser BBCode Source #

Parse zero or more BBCode elements Doesn't necessarily return value wrapped in ElDocument, it returns (mempty :: BBCode) if it parses no elements, or just element if parses just one element. Otherwise it is ElDocument

runParserMaybeEnv :: ParsecT e s (Reader r) a -> r -> s -> Maybe a Source #

parseMaybe specialized for Parser