{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Language.Rzk.VSCode.Tokenize where
import Language.Rzk.Syntax
import Language.Rzk.Syntax.Print
import Language.Rzk.VSCode.Tokens
tokenizeModule :: Module -> [VSToken]
tokenizeModule :: Module -> [VSToken]
tokenizeModule (Module BNFC'Position
_loc LanguageDecl' BNFC'Position
langDecl [Command' BNFC'Position]
commands) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ LanguageDecl' BNFC'Position -> [VSToken]
tokenizeLanguageDecl LanguageDecl' BNFC'Position
langDecl
, forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Command' BNFC'Position -> [VSToken]
tokenizeCommand [Command' BNFC'Position]
commands
]
tokenizeLanguageDecl :: LanguageDecl -> [VSToken]
tokenizeLanguageDecl :: LanguageDecl' BNFC'Position -> [VSToken]
tokenizeLanguageDecl LanguageDecl' BNFC'Position
_ = []
tokenizeCommand :: Command -> [VSToken]
tokenizeCommand :: Command' BNFC'Position -> [VSToken]
tokenizeCommand Command' BNFC'Position
command = case Command' BNFC'Position
command of
CommandSetOption{} -> []
CommandUnsetOption{} -> []
CommandCheck BNFC'Position
_loc Term' BNFC'Position
term Term' BNFC'Position
type_ -> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term' BNFC'Position -> [VSToken]
tokenizeTerm [Term' BNFC'Position
term, Term' BNFC'Position
type_]
CommandCompute BNFC'Position
_loc Term' BNFC'Position
term -> Term' BNFC'Position -> [VSToken]
tokenizeTerm Term' BNFC'Position
term
CommandComputeNF BNFC'Position
_loc Term' BNFC'Position
term -> Term' BNFC'Position -> [VSToken]
tokenizeTerm Term' BNFC'Position
term
CommandComputeWHNF BNFC'Position
_loc Term' BNFC'Position
term -> Term' BNFC'Position -> [VSToken]
tokenizeTerm Term' BNFC'Position
term
CommandPostulate BNFC'Position
_loc VarIdent' BNFC'Position
name DeclUsedVars' BNFC'Position
_declUsedVars [Param' BNFC'Position]
params Term' BNFC'Position
type_ -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken VarIdent' BNFC'Position
name VSTokenType
vs_function [VSTokenModifier
vs_declaration]
, forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Param' BNFC'Position -> [VSToken]
tokenizeParam [Param' BNFC'Position]
params
, Term' BNFC'Position -> [VSToken]
tokenizeTerm Term' BNFC'Position
type_
]
CommandDefine BNFC'Position
_loc VarIdent' BNFC'Position
name DeclUsedVars' BNFC'Position
_declUsedVars [Param' BNFC'Position]
params Term' BNFC'Position
type_ Term' BNFC'Position
term -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken VarIdent' BNFC'Position
name VSTokenType
vs_function [VSTokenModifier
vs_declaration]
, forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Param' BNFC'Position -> [VSToken]
tokenizeParam [Param' BNFC'Position]
params
, forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term' BNFC'Position -> [VSToken]
tokenizeTerm [Term' BNFC'Position
type_, Term' BNFC'Position
term]
]
CommandAssume BNFC'Position
_loc [VarIdent' BNFC'Position]
vars Term' BNFC'Position
type_ -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (\VarIdent' BNFC'Position
var -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken VarIdent' BNFC'Position
var VSTokenType
vs_parameter [VSTokenModifier
vs_declaration]) [VarIdent' BNFC'Position]
vars
, Term' BNFC'Position -> [VSToken]
tokenizeTerm Term' BNFC'Position
type_
]
CommandSection BNFC'Position
_loc SectionName' BNFC'Position
_nameStart [Command' BNFC'Position]
commands SectionName' BNFC'Position
_nameEnd ->
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Command' BNFC'Position -> [VSToken]
tokenizeCommand [Command' BNFC'Position]
commands
tokenizeParam :: Param -> [VSToken]
tokenizeParam :: Param' BNFC'Position -> [VSToken]
tokenizeParam = \case
ParamPattern BNFC'Position
_loc Pattern
pat -> Pattern -> [VSToken]
tokenizePattern Pattern
pat
ParamPatternType BNFC'Position
_loc [Pattern]
pats Term' BNFC'Position
type_ -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pattern -> [VSToken]
tokenizePattern [Pattern]
pats
, Term' BNFC'Position -> [VSToken]
tokenizeTerm Term' BNFC'Position
type_ ]
ParamPatternShape BNFC'Position
_loc [Pattern]
pats Term' BNFC'Position
cube Term' BNFC'Position
tope -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pattern -> [VSToken]
tokenizePattern [Pattern]
pats
, Term' BNFC'Position -> [VSToken]
tokenizeTerm Term' BNFC'Position
cube
, Term' BNFC'Position -> [VSToken]
tokenizeTope Term' BNFC'Position
tope ]
ParamPatternShapeDeprecated BNFC'Position
_loc Pattern
pat Term' BNFC'Position
cube Term' BNFC'Position
tope -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ Pattern -> [VSToken]
tokenizePattern Pattern
pat
, Term' BNFC'Position -> [VSToken]
tokenizeTerm Term' BNFC'Position
cube
, Term' BNFC'Position -> [VSToken]
tokenizeTope Term' BNFC'Position
tope ]
tokenizePattern :: Pattern -> [VSToken]
tokenizePattern :: Pattern -> [VSToken]
tokenizePattern = \case
PatternVar BNFC'Position
_loc VarIdent' BNFC'Position
var -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken VarIdent' BNFC'Position
var VSTokenType
vs_parameter [VSTokenModifier
vs_declaration]
PatternPair BNFC'Position
_loc Pattern
l Pattern
r -> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pattern -> [VSToken]
tokenizePattern [Pattern
l, Pattern
r]
pat :: Pattern
pat@(PatternUnit BNFC'Position
_loc) -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Pattern
pat VSTokenType
vs_enumMember [VSTokenModifier
vs_declaration]
tokenizeTope :: Term -> [VSToken]
tokenizeTope :: Term' BNFC'Position -> [VSToken]
tokenizeTope = Maybe VSTokenType -> Term' BNFC'Position -> [VSToken]
tokenizeTerm' (forall a. a -> Maybe a
Just VSTokenType
vs_string)
tokenizeTerm :: Term -> [VSToken]
tokenizeTerm :: Term' BNFC'Position -> [VSToken]
tokenizeTerm = Maybe VSTokenType -> Term' BNFC'Position -> [VSToken]
tokenizeTerm' forall a. Maybe a
Nothing
tokenizeTerm' :: Maybe VSTokenType -> Term -> [VSToken]
tokenizeTerm' :: Maybe VSTokenType -> Term' BNFC'Position -> [VSToken]
tokenizeTerm' Maybe VSTokenType
varTokenType = Term' BNFC'Position -> [VSToken]
go
where
go :: Term' BNFC'Position -> [VSToken]
go Term' BNFC'Position
term = case Term' BNFC'Position
term of
Hole{} -> []
Var{} -> case Maybe VSTokenType
varTokenType of
Maybe VSTokenType
Nothing -> []
Just VSTokenType
token_type -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
token_type []
Universe{} -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_class [VSTokenModifier
vs_defaultLibrary]
UniverseCube{} -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_class [VSTokenModifier
vs_defaultLibrary]
UniverseTope{} -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_class [VSTokenModifier
vs_defaultLibrary]
CubeUnit{} -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_enum [VSTokenModifier
vs_defaultLibrary]
CubeUnitStar{} -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_enumMember [VSTokenModifier
vs_defaultLibrary]
ASCII_CubeUnitStar{} -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_enumMember [VSTokenModifier
vs_defaultLibrary]
Cube2{} -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_enum [VSTokenModifier
vs_defaultLibrary]
Cube2_0{} -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_enumMember [VSTokenModifier
vs_defaultLibrary]
ASCII_Cube2_0{} -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_enumMember [VSTokenModifier
vs_defaultLibrary]
Cube2_1{} -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_enumMember [VSTokenModifier
vs_defaultLibrary]
ASCII_Cube2_1{} -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_enumMember [VSTokenModifier
vs_defaultLibrary]
CubeProduct BNFC'Position
_loc Term' BNFC'Position
l Term' BNFC'Position
r -> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term' BNFC'Position -> [VSToken]
go [Term' BNFC'Position
l, Term' BNFC'Position
r]
TopeTop{} -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_string [VSTokenModifier
vs_defaultLibrary]
ASCII_TopeTop{} -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_string [VSTokenModifier
vs_defaultLibrary]
TopeBottom{} -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_string [VSTokenModifier
vs_defaultLibrary]
ASCII_TopeBottom{} -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_string [VSTokenModifier
vs_defaultLibrary]
TopeAnd BNFC'Position
_loc Term' BNFC'Position
l Term' BNFC'Position
r -> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term' BNFC'Position -> [VSToken]
tokenizeTope [Term' BNFC'Position
l, Term' BNFC'Position
r]
ASCII_TopeAnd BNFC'Position
_loc Term' BNFC'Position
l Term' BNFC'Position
r -> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term' BNFC'Position -> [VSToken]
tokenizeTope [Term' BNFC'Position
l, Term' BNFC'Position
r]
TopeOr BNFC'Position
_loc Term' BNFC'Position
l Term' BNFC'Position
r -> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term' BNFC'Position -> [VSToken]
tokenizeTope [Term' BNFC'Position
l, Term' BNFC'Position
r]
ASCII_TopeOr BNFC'Position
_loc Term' BNFC'Position
l Term' BNFC'Position
r -> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term' BNFC'Position -> [VSToken]
tokenizeTope [Term' BNFC'Position
l, Term' BNFC'Position
r]
TopeEQ BNFC'Position
_loc Term' BNFC'Position
l Term' BNFC'Position
r -> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term' BNFC'Position -> [VSToken]
tokenizeTope [Term' BNFC'Position
l, Term' BNFC'Position
r]
ASCII_TopeEQ BNFC'Position
_loc Term' BNFC'Position
l Term' BNFC'Position
r -> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term' BNFC'Position -> [VSToken]
tokenizeTope [Term' BNFC'Position
l, Term' BNFC'Position
r]
TopeLEQ BNFC'Position
_loc Term' BNFC'Position
l Term' BNFC'Position
r -> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term' BNFC'Position -> [VSToken]
tokenizeTope [Term' BNFC'Position
l, Term' BNFC'Position
r]
ASCII_TopeLEQ BNFC'Position
_loc Term' BNFC'Position
l Term' BNFC'Position
r -> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term' BNFC'Position -> [VSToken]
tokenizeTope [Term' BNFC'Position
l, Term' BNFC'Position
r]
RecBottom{} -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_function [VSTokenModifier
vs_defaultLibrary]
RecOr BNFC'Position
_loc [Restriction' BNFC'Position]
rs -> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Restriction' BNFC'Position -> [VSToken]
tokenizeRestriction [Restriction' BNFC'Position]
rs
TypeFun BNFC'Position
_loc ParamDecl' BNFC'Position
paramDecl Term' BNFC'Position
ret -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ ParamDecl' BNFC'Position -> [VSToken]
tokenizeParamDecl ParamDecl' BNFC'Position
paramDecl
, Term' BNFC'Position -> [VSToken]
go Term' BNFC'Position
ret ]
ASCII_TypeFun BNFC'Position
_loc ParamDecl' BNFC'Position
paramDecl Term' BNFC'Position
ret -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ ParamDecl' BNFC'Position -> [VSToken]
tokenizeParamDecl ParamDecl' BNFC'Position
paramDecl
, Term' BNFC'Position -> [VSToken]
go Term' BNFC'Position
ret ]
TypeSigma BNFC'Position
loc Pattern
pat Term' BNFC'Position
a Term' BNFC'Position
b -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken (forall a. a -> VarIdentToken -> VarIdent' a
VarIdent BNFC'Position
loc VarIdentToken
"∑") VSTokenType
vs_class [VSTokenModifier
vs_defaultLibrary]
, Pattern -> [VSToken]
tokenizePattern Pattern
pat
, forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term' BNFC'Position -> [VSToken]
go [Term' BNFC'Position
a, Term' BNFC'Position
b] ]
ASCII_TypeSigma BNFC'Position
loc Pattern
pat Term' BNFC'Position
a Term' BNFC'Position
b -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken (forall a. a -> VarIdentToken -> VarIdent' a
VarIdent BNFC'Position
loc VarIdentToken
"Sigma") VSTokenType
vs_class [VSTokenModifier
vs_defaultLibrary]
, Pattern -> [VSToken]
tokenizePattern Pattern
pat
, forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term' BNFC'Position -> [VSToken]
go [Term' BNFC'Position
a, Term' BNFC'Position
b] ]
TypeId BNFC'Position
_loc Term' BNFC'Position
x Term' BNFC'Position
a Term' BNFC'Position
y -> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term' BNFC'Position -> [VSToken]
go [Term' BNFC'Position
x, Term' BNFC'Position
a, Term' BNFC'Position
y]
TypeIdSimple BNFC'Position
_loc Term' BNFC'Position
x Term' BNFC'Position
y -> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term' BNFC'Position -> [VSToken]
go [Term' BNFC'Position
x, Term' BNFC'Position
y]
TypeRestricted BNFC'Position
_loc Term' BNFC'Position
type_ [Restriction' BNFC'Position]
rs -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ Term' BNFC'Position -> [VSToken]
go Term' BNFC'Position
type_
, forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Restriction' BNFC'Position -> [VSToken]
tokenizeRestriction [Restriction' BNFC'Position]
rs ]
App BNFC'Position
_loc Term' BNFC'Position
f Term' BNFC'Position
x -> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term' BNFC'Position -> [VSToken]
go [Term' BNFC'Position
f, Term' BNFC'Position
x]
Lambda BNFC'Position
_loc [Param' BNFC'Position]
params Term' BNFC'Position
body -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Param' BNFC'Position -> [VSToken]
tokenizeParam [Param' BNFC'Position]
params
, Term' BNFC'Position -> [VSToken]
go Term' BNFC'Position
body ]
ASCII_Lambda BNFC'Position
loc [Param' BNFC'Position]
params Term' BNFC'Position
body -> Term' BNFC'Position -> [VSToken]
go (forall a. a -> [Param' a] -> Term' a -> Term' a
Lambda BNFC'Position
loc [Param' BNFC'Position]
params Term' BNFC'Position
body)
Pair BNFC'Position
_loc Term' BNFC'Position
l Term' BNFC'Position
r -> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term' BNFC'Position -> [VSToken]
go [Term' BNFC'Position
l, Term' BNFC'Position
r]
First BNFC'Position
loc Term' BNFC'Position
t -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken (forall a. a -> VarIdentToken -> VarIdent' a
VarIdent BNFC'Position
loc VarIdentToken
"π₁") VSTokenType
vs_function [VSTokenModifier
vs_defaultLibrary]
, Term' BNFC'Position -> [VSToken]
go Term' BNFC'Position
t ]
ASCII_First BNFC'Position
loc Term' BNFC'Position
t -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken (forall a. a -> VarIdentToken -> VarIdent' a
VarIdent BNFC'Position
loc VarIdentToken
"first") VSTokenType
vs_function [VSTokenModifier
vs_defaultLibrary]
, Term' BNFC'Position -> [VSToken]
go Term' BNFC'Position
t ]
Second BNFC'Position
loc Term' BNFC'Position
t -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken (forall a. a -> VarIdentToken -> VarIdent' a
VarIdent BNFC'Position
loc VarIdentToken
"π₂") VSTokenType
vs_function [VSTokenModifier
vs_defaultLibrary]
, Term' BNFC'Position -> [VSToken]
go Term' BNFC'Position
t ]
ASCII_Second BNFC'Position
loc Term' BNFC'Position
t -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken (forall a. a -> VarIdentToken -> VarIdent' a
VarIdent BNFC'Position
loc VarIdentToken
"second") VSTokenType
vs_function [VSTokenModifier
vs_defaultLibrary]
, Term' BNFC'Position -> [VSToken]
go Term' BNFC'Position
t ]
TypeUnit BNFC'Position
_loc -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_enum [VSTokenModifier
vs_defaultLibrary]
Unit BNFC'Position
_loc -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_enumMember [VSTokenModifier
vs_defaultLibrary]
Refl{} -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_function [VSTokenModifier
vs_defaultLibrary]
ReflTerm BNFC'Position
loc Term' BNFC'Position
x -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken (forall a. a -> VarIdentToken -> VarIdent' a
VarIdent BNFC'Position
loc VarIdentToken
"refl") VSTokenType
vs_function [VSTokenModifier
vs_defaultLibrary]
, Term' BNFC'Position -> [VSToken]
go Term' BNFC'Position
x ]
ReflTermType BNFC'Position
loc Term' BNFC'Position
x Term' BNFC'Position
a -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken (forall a. a -> VarIdentToken -> VarIdent' a
VarIdent BNFC'Position
loc VarIdentToken
"refl") VSTokenType
vs_function [VSTokenModifier
vs_defaultLibrary]
, forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term' BNFC'Position -> [VSToken]
go [Term' BNFC'Position
x, Term' BNFC'Position
a] ]
IdJ BNFC'Position
loc Term' BNFC'Position
a Term' BNFC'Position
b Term' BNFC'Position
c Term' BNFC'Position
d Term' BNFC'Position
e Term' BNFC'Position
f -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken (forall a. a -> VarIdentToken -> VarIdent' a
VarIdent BNFC'Position
loc VarIdentToken
"J") VSTokenType
vs_function [VSTokenModifier
vs_defaultLibrary]
, forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term' BNFC'Position -> [VSToken]
go [Term' BNFC'Position
a, Term' BNFC'Position
b, Term' BNFC'Position
c, Term' BNFC'Position
d, Term' BNFC'Position
e, Term' BNFC'Position
f] ]
TypeAsc BNFC'Position
_loc Term' BNFC'Position
t Term' BNFC'Position
type_ -> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Term' BNFC'Position -> [VSToken]
go [Term' BNFC'Position
t, Term' BNFC'Position
type_]
RecOrDeprecated{} -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_regexp [VSTokenModifier
vs_deprecated]
TypeExtensionDeprecated{} -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_regexp [VSTokenModifier
vs_deprecated]
ASCII_TypeExtensionDeprecated{} -> forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken Term' BNFC'Position
term VSTokenType
vs_regexp [VSTokenModifier
vs_deprecated]
tokenizeRestriction :: Restriction -> [VSToken]
tokenizeRestriction :: Restriction' BNFC'Position -> [VSToken]
tokenizeRestriction (Restriction BNFC'Position
_loc Term' BNFC'Position
tope Term' BNFC'Position
term) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ Term' BNFC'Position -> [VSToken]
tokenizeTope Term' BNFC'Position
tope
, Term' BNFC'Position -> [VSToken]
tokenizeTerm Term' BNFC'Position
term ]
tokenizeRestriction (ASCII_Restriction BNFC'Position
_loc Term' BNFC'Position
tope Term' BNFC'Position
term) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ Term' BNFC'Position -> [VSToken]
tokenizeTope Term' BNFC'Position
tope
, Term' BNFC'Position -> [VSToken]
tokenizeTerm Term' BNFC'Position
term ]
tokenizeParamDecl :: ParamDecl -> [VSToken]
tokenizeParamDecl :: ParamDecl' BNFC'Position -> [VSToken]
tokenizeParamDecl = \case
ParamType BNFC'Position
_loc Term' BNFC'Position
type_ -> Term' BNFC'Position -> [VSToken]
tokenizeTerm Term' BNFC'Position
type_
ParamTermType BNFC'Position
_loc Term' BNFC'Position
pat Term' BNFC'Position
type_ -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ Term' BNFC'Position -> [VSToken]
tokenizeTerm Term' BNFC'Position
pat
, Term' BNFC'Position -> [VSToken]
tokenizeTerm Term' BNFC'Position
type_ ]
ParamTermShape BNFC'Position
_loc Term' BNFC'Position
pat Term' BNFC'Position
cube Term' BNFC'Position
tope -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ Term' BNFC'Position -> [VSToken]
tokenizeTerm Term' BNFC'Position
pat
, Term' BNFC'Position -> [VSToken]
tokenizeTerm Term' BNFC'Position
cube
, Term' BNFC'Position -> [VSToken]
tokenizeTope Term' BNFC'Position
tope
]
ParamTermTypeDeprecated BNFC'Position
_loc Pattern
pat Term' BNFC'Position
type_ -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ Pattern -> [VSToken]
tokenizePattern Pattern
pat
, Term' BNFC'Position -> [VSToken]
tokenizeTerm Term' BNFC'Position
type_ ]
ParamVarShapeDeprecated BNFC'Position
_loc Pattern
pat Term' BNFC'Position
cube Term' BNFC'Position
tope -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ Pattern -> [VSToken]
tokenizePattern Pattern
pat
, Term' BNFC'Position -> [VSToken]
tokenizeTerm Term' BNFC'Position
cube
, Term' BNFC'Position -> [VSToken]
tokenizeTope Term' BNFC'Position
tope
]
mkToken :: (HasPosition a, Print a) => a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken :: forall a.
(HasPosition a, Print a) =>
a -> VSTokenType -> [VSTokenModifier] -> [VSToken]
mkToken a
x VSTokenType
tokenType [VSTokenModifier]
tokenModifiers =
case forall a. HasPosition a => a -> BNFC'Position
hasPosition a
x of
BNFC'Position
Nothing -> []
Just (Int
line, Int
col) -> do
[ VSToken
{ startCharacter :: Int
startCharacter = Int
col forall a. Num a => a -> a -> a
- Int
1
, line :: Int
line = Int
line forall a. Num a => a -> a -> a
- Int
1
, length :: Int
length = forall (t :: * -> *) a. Foldable t => t a -> Int
Prelude.length (forall a. Print a => a -> String
printTree a
x)
, [VSTokenModifier]
VSTokenType
tokenModifiers :: [VSTokenModifier]
tokenType :: VSTokenType
tokenModifiers :: [VSTokenModifier]
tokenType :: VSTokenType
.. } ]