zenacy-html-2.0.0: A standard compliant HTML parsing library

Safe HaskellNone
LanguageHaskell2010

Zenacy.HTML.Internal.Token

Description

Defines a token type used by the lexer.

Synopsis

Documentation

data Token Source #

Defines the token type. The token type is used for testing and debugging only.

Constructors

TDoctype 
TStart 

Fields

TEnd 

Fields

TComment 

Fields

TChar 

Fields

TEOF 
Instances
Eq Token Source # 
Instance details

Defined in Zenacy.HTML.Internal.Token

Methods

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

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

Ord Token Source # 
Instance details

Defined in Zenacy.HTML.Internal.Token

Methods

compare :: Token -> Token -> Ordering #

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

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

(>) :: Token -> Token -> Bool #

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

max :: Token -> Token -> Token #

min :: Token -> Token -> Token #

Show Token Source # 
Instance details

Defined in Zenacy.HTML.Internal.Token

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

data TokenBuffer s Source #

A type of buffer used to hold tokens.

Constructors

TokenBuffer 

Fields

data TAttr Source #

An HTML element attribute type.

Constructors

TAttr 
Instances
Eq TAttr Source # 
Instance details

Defined in Zenacy.HTML.Internal.Token

Methods

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

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

Ord TAttr Source # 
Instance details

Defined in Zenacy.HTML.Internal.Token

Methods

compare :: TAttr -> TAttr -> Ordering #

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

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

(>) :: TAttr -> TAttr -> Bool #

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

max :: TAttr -> TAttr -> TAttr #

min :: TAttr -> TAttr -> TAttr #

Show TAttr Source # 
Instance details

Defined in Zenacy.HTML.Internal.Token

Methods

showsPrec :: Int -> TAttr -> ShowS #

show :: TAttr -> String #

showList :: [TAttr] -> ShowS #

tokenAttr :: BS -> BS -> TAttr Source #

Makes an attribute.

tokenHasAttr :: BS -> Token -> Bool Source #

Determines if a token has an attribute.

tokenGetAttr :: BS -> Token -> Maybe TAttr Source #

Finds an attribute in a token.

tokenGetAttrVal :: BS -> Token -> Maybe BS Source #

Finds an attribute value for a token.

tokenBuffer :: ST s (STRef s (TokenBuffer s)) Source #

Makes a new token buffer.

tokenCapacity :: STRef s (TokenBuffer s) -> ST s (Int, Int) Source #

Gets the capacity of the buffer.

tokenReset :: STRef s (TokenBuffer s) -> ST s () Source #

Resets a token buffer.

tokenTail :: STRef s (TokenBuffer s) -> ST s Int Source #

Get the token buffer tail offset.

tokenFirst :: STRef s (TokenBuffer s) -> ST s Int Source #

Positions the emitter to the first token and returns its offset.

tokenNext :: STRef s (TokenBuffer s) -> ST s Int Source #

Positions the emitter to the next token and returns its offset.

tokenCount :: STRef s (TokenBuffer s) -> ST s Int Source #

Counts the number of tokens in the buffer.

tokenOffset :: STRef s (TokenBuffer s) -> ST s [Int] Source #

Gets a list of the tokens in the buffer.

tokenList :: STRef s (TokenBuffer s) -> ST s [Token] Source #

Gets a list of the tokens in the buffer.

tokenDrop :: STRef s (TokenBuffer s) -> ST s () Source #

Drops the last token from the buffer.

tokenHasEOF :: STRef s (TokenBuffer s) -> ST s Bool Source #

Returns whether a buffer includes an EOF token.

tokenSlice :: Int -> Int -> STRef s (TokenBuffer s) -> ST s [Word8] Source #

Returns a slice of the data area of a token buffer.

tokenTagStartName :: Int -> STRef s (TokenBuffer s) -> ST s (Maybe [Word8]) Source #

Returns the start tag name at for the token at an offset.

tokenTagEndName :: Int -> STRef s (TokenBuffer s) -> ST s (Maybe [Word8]) Source #

Returns the end tag name at for the token at an offset.

tokenDoctypeType :: Int Source #

Defines the type for a DOCTYPE token.

tokenTagStartType :: Int Source #

Defines the type for a start tag token.

tokenTagEndType :: Int Source #

Defines the type for a end tag token.

tokenCommentType :: Int Source #

Defines the type for a comment token.

tokenCharType :: Int Source #

Defines the type for a character token.

tokenEOFType :: Int Source #

Defines the type for an EOF token.

tokenDoctypeInit :: STRef s (TokenBuffer s) -> ST s () Source #

Adds a new DOCTYPE token to the lexer.

tokenDoctypeNameAppend :: Word8 -> STRef s (TokenBuffer s) -> ST s () Source #

Appends a character to the current DOCTYPE token.

tokenDoctypeSetForceQuirks :: STRef s (TokenBuffer s) -> ST s () Source #

Sets the force quirks flag for the current DOCTYPE.

tokenDoctypePublicIdInit :: STRef s (TokenBuffer s) -> ST s () Source #

Initializes the DOCTYPE public ID.

tokenDoctypePublicIdAppend :: Word8 -> STRef s (TokenBuffer s) -> ST s () Source #

Appends a character to the DOCTYPE public ID.

tokenDoctypeSystemIdInit :: STRef s (TokenBuffer s) -> ST s () Source #

Initializes the DOCTYPE system ID.

tokenDoctypeSystemIdAppend :: Word8 -> STRef s (TokenBuffer s) -> ST s () Source #

Appends a character to the DOCTYPE system ID.

tokenTagStartInit :: STRef s (TokenBuffer s) -> ST s () Source #

Adds a new start tag to the lexer.

tokenTagStartSetSelfClosing :: STRef s (TokenBuffer s) -> ST s () Source #

Adds a new start tag to the lexer.

tokenTagEndInit :: STRef s (TokenBuffer s) -> ST s () Source #

Adds a new end tag to the lexer.

tokenTagNameAppend :: Word8 -> STRef s (TokenBuffer s) -> ST s () Source #

Appends a character to a tag name if the token is a tag.

tokenAttrInit :: STRef s (TokenBuffer s) -> ST s () Source #

Starts a new attribute

tokenAttrNameAppend :: Word8 -> STRef s (TokenBuffer s) -> ST s () Source #

Appends a character to the latest attribute name.

tokenAttrValAppend :: Word8 -> STRef s (TokenBuffer s) -> ST s () Source #

Appends a character to the latest attribute value.

tokenAttrNamePrune :: Int -> STRef s (TokenBuffer s) -> ST s Bool Source #

Checks for duplicate attribute names. Refer to section 12.2.5.33 for details.

tokenCommentInit :: STRef s (TokenBuffer s) -> ST s () Source #

Adds a new comment token to the lexer.

tokenCommentAppend :: Word8 -> STRef s (TokenBuffer s) -> ST s () Source #

Appends a character to the current comment token.

tokenCharInit :: Word8 -> STRef s (TokenBuffer s) -> ST s () Source #

Initializes a text token.

tokenEOFInit :: STRef s (TokenBuffer s) -> ST s () Source #

Initializes an EOF token.

tokenType :: Int -> STRef s (TokenBuffer s) -> ST s Int Source #

Gets the type of a token.

tokenSize :: Int -> STRef s (TokenBuffer s) -> ST s Int Source #

Gets the size of a token.

tokenPack :: Int -> STRef s (TokenBuffer s) -> ST s Token Source #

Unpacks a token at the specified index.