{-# LANGUAGE CPP, DeriveDataTypeable #-}
module Language.JavaScript.Parser.Token
(
Token (..)
, CommentAnnotation (..)
, debugTokenString
) where
import Data.Data
import Language.JavaScript.Parser.SrcLocation
data
= TokenPosn String
| WhiteSpace TokenPosn String
|
deriving (CommentAnnotation -> CommentAnnotation -> Bool
(CommentAnnotation -> CommentAnnotation -> Bool)
-> (CommentAnnotation -> CommentAnnotation -> Bool)
-> Eq CommentAnnotation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CommentAnnotation -> CommentAnnotation -> Bool
== :: CommentAnnotation -> CommentAnnotation -> Bool
$c/= :: CommentAnnotation -> CommentAnnotation -> Bool
/= :: CommentAnnotation -> CommentAnnotation -> Bool
Eq, Int -> CommentAnnotation -> ShowS
[CommentAnnotation] -> ShowS
CommentAnnotation -> String
(Int -> CommentAnnotation -> ShowS)
-> (CommentAnnotation -> String)
-> ([CommentAnnotation] -> ShowS)
-> Show CommentAnnotation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CommentAnnotation -> ShowS
showsPrec :: Int -> CommentAnnotation -> ShowS
$cshow :: CommentAnnotation -> String
show :: CommentAnnotation -> String
$cshowList :: [CommentAnnotation] -> ShowS
showList :: [CommentAnnotation] -> ShowS
Show, Typeable, Typeable CommentAnnotation
Typeable CommentAnnotation =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CommentAnnotation
-> c CommentAnnotation)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CommentAnnotation)
-> (CommentAnnotation -> Constr)
-> (CommentAnnotation -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CommentAnnotation))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CommentAnnotation))
-> ((forall b. Data b => b -> b)
-> CommentAnnotation -> CommentAnnotation)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CommentAnnotation -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CommentAnnotation -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CommentAnnotation -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CommentAnnotation -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CommentAnnotation -> m CommentAnnotation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CommentAnnotation -> m CommentAnnotation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CommentAnnotation -> m CommentAnnotation)
-> Data CommentAnnotation
CommentAnnotation -> Constr
CommentAnnotation -> DataType
(forall b. Data b => b -> b)
-> CommentAnnotation -> CommentAnnotation
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CommentAnnotation -> u
forall u. (forall d. Data d => d -> u) -> CommentAnnotation -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CommentAnnotation -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CommentAnnotation -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CommentAnnotation -> m CommentAnnotation
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CommentAnnotation -> m CommentAnnotation
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CommentAnnotation
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CommentAnnotation -> c CommentAnnotation
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CommentAnnotation)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CommentAnnotation)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CommentAnnotation -> c CommentAnnotation
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CommentAnnotation -> c CommentAnnotation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CommentAnnotation
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CommentAnnotation
$ctoConstr :: CommentAnnotation -> Constr
toConstr :: CommentAnnotation -> Constr
$cdataTypeOf :: CommentAnnotation -> DataType
dataTypeOf :: CommentAnnotation -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CommentAnnotation)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CommentAnnotation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CommentAnnotation)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CommentAnnotation)
$cgmapT :: (forall b. Data b => b -> b)
-> CommentAnnotation -> CommentAnnotation
gmapT :: (forall b. Data b => b -> b)
-> CommentAnnotation -> CommentAnnotation
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CommentAnnotation -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CommentAnnotation -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CommentAnnotation -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CommentAnnotation -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> CommentAnnotation -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CommentAnnotation -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CommentAnnotation -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CommentAnnotation -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CommentAnnotation -> m CommentAnnotation
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CommentAnnotation -> m CommentAnnotation
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CommentAnnotation -> m CommentAnnotation
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CommentAnnotation -> m CommentAnnotation
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CommentAnnotation -> m CommentAnnotation
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CommentAnnotation -> m CommentAnnotation
Data, ReadPrec [CommentAnnotation]
ReadPrec CommentAnnotation
Int -> ReadS CommentAnnotation
ReadS [CommentAnnotation]
(Int -> ReadS CommentAnnotation)
-> ReadS [CommentAnnotation]
-> ReadPrec CommentAnnotation
-> ReadPrec [CommentAnnotation]
-> Read CommentAnnotation
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS CommentAnnotation
readsPrec :: Int -> ReadS CommentAnnotation
$creadList :: ReadS [CommentAnnotation]
readList :: ReadS [CommentAnnotation]
$creadPrec :: ReadPrec CommentAnnotation
readPrec :: ReadPrec CommentAnnotation
$creadListPrec :: ReadPrec [CommentAnnotation]
readListPrec :: ReadPrec [CommentAnnotation]
Read)
data Token
= { Token -> TokenPosn
tokenSpan :: !TokenPosn, Token -> String
tokenLiteral :: !String, :: ![CommentAnnotation] }
| WsToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| IdentifierToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| DecimalToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| HexIntegerToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| OctalToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| StringToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| RegExToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| AsyncToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| AwaitToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| BreakToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| CaseToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| CatchToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| ClassToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| ConstToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| LetToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| ContinueToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| DebuggerToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| DefaultToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| DeleteToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| DoToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| ElseToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| EnumToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| ExtendsToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| FalseToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| FinallyToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| ForToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| FunctionToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| FromToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| IfToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| InToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| InstanceofToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| NewToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| NullToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| OfToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| ReturnToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| StaticToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| SuperToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| SwitchToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| ThisToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| ThrowToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| TrueToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| TryToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| TypeofToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| VarToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| VoidToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| WhileToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| YieldToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| ImportToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| WithToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| ExportToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| FutureToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| GetToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| SetToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| AutoSemiToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| SemiColonToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| CommaToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| HookToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| ColonToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| OrToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| AndToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| BitwiseOrToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| BitwiseXorToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| BitwiseAndToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| StrictEqToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| EqToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| TimesAssignToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| DivideAssignToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| ModAssignToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| PlusAssignToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| MinusAssignToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| LshAssignToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| RshAssignToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| UrshAssignToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| AndAssignToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| XorAssignToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| OrAssignToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| SimpleAssignToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| StrictNeToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| NeToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| LshToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| LeToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| LtToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| UrshToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| RshToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| GeToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| GtToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| IncrementToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| DecrementToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| PlusToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| MinusToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| MulToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| DivToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| ModToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| NotToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| BitwiseNotToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| ArrowToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| SpreadToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| DotToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| LeftBracketToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| RightBracketToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| LeftCurlyToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| RightCurlyToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| LeftParenToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| RightParenToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| NoSubstitutionTemplateToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| TemplateHeadToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| TemplateMiddleToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| TemplateTailToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| AsToken { tokenSpan :: !TokenPosn, tokenLiteral :: !String, :: ![CommentAnnotation] }
| TailToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
| EOFToken { tokenSpan :: !TokenPosn, :: ![CommentAnnotation] }
deriving (Token -> Token -> Bool
(Token -> Token -> Bool) -> (Token -> Token -> Bool) -> Eq Token
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Token -> Token -> Bool
== :: Token -> Token -> Bool
$c/= :: Token -> Token -> Bool
/= :: Token -> Token -> Bool
Eq, Int -> Token -> ShowS
[Token] -> ShowS
Token -> String
(Int -> Token -> ShowS)
-> (Token -> String) -> ([Token] -> ShowS) -> Show Token
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Token -> ShowS
showsPrec :: Int -> Token -> ShowS
$cshow :: Token -> String
show :: Token -> String
$cshowList :: [Token] -> ShowS
showList :: [Token] -> ShowS
Show, Typeable)
debugTokenString :: Token -> String
debugTokenString :: Token -> String
debugTokenString = (Char -> Bool) -> ShowS
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
' ') ShowS -> (Token -> String) -> Token -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Token -> String
forall a. Show a => a -> String
show