ddc-core-0.4.3.1: Disciplined Disciple Compiler core language and type checker.

Safe HaskellSafe
LanguageHaskell98

DDC.Core.Lexer.Tokens

Contents

Synopsis

Documentation

data Located a Source #

A located thing.

Constructors

Located !SourcePos !a 

Instances

Eq a => Eq (Located a) Source # 

Methods

(==) :: Located a -> Located a -> Bool #

(/=) :: Located a -> Located a -> Bool #

Show a => Show (Located a) Source # 

Methods

showsPrec :: Int -> Located a -> ShowS #

show :: Located a -> String #

showList :: [Located a] -> ShowS #

columnOfLocated :: Located a -> Int Source #

Yield the column number of a located thing.

Tokens

data Token n Source #

Tokens accepted by the core language parser.

Constructors

KErrorJunk String

Some junk symbol that isn't part of the language.

KErrorUnterm String

The first part of an unterminated string.

KM !TokenMeta

Meta tokens contain out-of-band information that is eliminated before parsing proper.

KA !TokenAtom

Atomic tokens are keywords, punctuation and baked-in constructor names.

KN !(TokenNamed n)

A named token that is specific to the language fragment (maybe it's a primop), or a user defined name.

Instances

Eq n => Eq (Token n) Source # 

Methods

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

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

Show n => Show (Token n) Source # 

Methods

showsPrec :: Int -> Token n -> ShowS #

show :: Token n -> String #

showList :: [Token n] -> ShowS #

data TokenMeta Source #

Meta tokens contain out-of-band information that is eliminated before parsing proper.

Constructors

KNewLine 
KComment String

Comment string.

KCommentUnterminated

This is injected by dropCommentBlock when it finds an unterminated block comment.

KOffsideClosingBrace

This is injected by applyOffside when it finds an explit close brace in a position where it would close a synthetic one.

data TokenAtom Source #

Atomic tokens are keywords, punctuation and baked-in constructor names. They don't contain user-defined names or primops specific to the language fragment.

Constructors

KPragma Text

Pragmas.

KSymbol Symbol

Symbols.

KKeyword Keyword

Keywords.

KBuiltin Builtin

Builtin names.

KOp String

Infix operators, like in 1 + 2.

KOpVar String

Wrapped operator, like in (+) 1 2.

KIndex Int

Debrujn indices.

KLiteral Literal Bool

Literal values.

data TokenNamed n Source #

A token with a user-defined name.

Constructors

KCon n 
KVar n 

Instances

Eq n => Eq (TokenNamed n) Source # 

Methods

(==) :: TokenNamed n -> TokenNamed n -> Bool #

(/=) :: TokenNamed n -> TokenNamed n -> Bool #

Show n => Show (TokenNamed n) Source # 

data Symbol Source #

Symbol tokens.

Constructors

SRoundBra

Like '('

SRoundKet

Like ')'

SSquareBra

Like '['

SSquareKet

Like ']'

SBraceBra

Like '{'

SBraceKet

Like '}'

SSquareColonBra

Like '[:'

SSquareColonKet

Like ':]'

SBraceColonBra

Like '{:'

SBraceColonKet

Like ':}'

SBigLambdaSlash

Like /\\

SArrowTilde

Like ~>

SArrowDashRight

Like '->'

SArrowDashLeft

Like '<-'

SArrowEquals

Like '=>'

SAt

Like '@'

SHat

Like ^

SDot

Like .

SBar

Like '|'

SComma

Like ','

SEquals

Like '='

SLambda

Like 'λ'

SSemiColon

Like ';'

SBackSlash

Like \\

SBigLambda

Like 'Λ'

SUnderscore

Like '_'

Instances

data Builtin Source #

Builtin name tokens.

data Literal Source #

Types of literal values known to the compiler.

Note that literals are embedded in the name type of each fragment rather than in the expression itself so that fragments can choose which types of literals they support.

Description

describeToken :: Pretty n => Token n -> String Source #

Describe a token for parser error messages.

describeTokenMeta :: TokenMeta -> String Source #

Describe a TokMeta, for lexer error messages.

describeTokenAtom :: TokenAtom -> String Source #

Describe a TokAtom, for parser error messages.

describeTokenNamed :: Pretty n => TokenNamed n -> String Source #

Describe a TokNamed, for parser error messages.

sayKeyword :: Keyword -> String Source #

Yield the string name of a keyword.

saySymbol :: Symbol -> String Source #

Yield the string name of a symbol token.

sayBuiltin :: Builtin -> String Source #

Yield the string name of a Builtin.

Renaming

renameToken :: Ord n2 => (n1 -> Maybe n2) -> Token n1 -> Maybe (Token n2) Source #

Apply a function to all the names in a Tok.

Predicates

isVarName :: String -> Bool Source #

Check if this string is a variable name.

isVarStart :: Char -> Bool Source #

Charater can start a variable name.

isVarBody :: Char -> Bool Source #

Character can be part of a variable body.

isConName :: String -> Bool Source #

String is a constructor name.

isConStart :: Char -> Bool Source #

Character can start a constructor name.

isConBody :: Char -> Bool Source #

Charater can be part of a constructor body.

isLitName :: String -> Bool Source #

String is the name of a literal.

isLitStart :: Char -> Bool Source #

Character can start a literal.

isLitBody :: Char -> Bool Source #

Character can be part of a literal body.

Literal Reading

readLitInteger :: String -> Maybe Integer Source #

Read a signed integer.

readLitNat :: String -> Maybe Integer Source #

Read an integer with an explicit format specifier like 1234i.

readLitInt :: String -> Maybe Integer Source #

Read an integer literal with an explicit format specifier like 1234i.

readLitSize :: String -> Maybe Integer Source #

Read an size literal with an explicit format specifier like 1234s.

readLitWordOfBits :: String -> Maybe (Integer, Int) Source #

Read a word with an explicit format speficier.

readLitFloatOfBits :: String -> Maybe (Double, Int) Source #

Read a float literal with an explicit format specifier like 123.00f32#.

readBinary :: Num a => String -> a Source #

Read a binary string as a number.

readHex :: (Enum a, Num a) => String -> a Source #

Read a hex string as a number.