module CHSLexer (CHSToken(..), lexCHS)
where
import Data.List ((\\))
import Data.Char (isDigit)
import Control.Monad (liftM)
import Numeric (readDec, readOct, readHex)
import Position (Position(..), Pos(posOf), incPos, retPos, tabPos)
import Errors (ErrorLvl(..), Error, makeError)
import UNames (NameSupply, Name, names)
import Idents (Ident, lexemeToIdent, identToLexeme)
import Lexers (Regexp, Lexer, Action, epsilon, char, (+>), lexaction,
lexactionErr, lexmeta, (>|<), (>||<), ctrlLexer, star, plus,
quest, alt, string, LexerState, execLexer)
import C2HSState (CST, raise, raiseError, nop, getNameSupply)
data CHSToken = CHSTokArrow Position
| CHSTokDArrow Position
| CHSTokDot Position
| CHSTokComma Position
| CHSTokEqual Position
| CHSTokMinus Position
| CHSTokStar Position
| CHSTokAmp Position
| CHSTokHat Position
| CHSTokLBrace Position
| CHSTokRBrace Position
| CHSTokLParen Position
| CHSTokRParen Position
| CHSTokEndHook Position
| CHSTokAs Position
| CHSTokCall Position
| CHSTokClass Position
| CHSTokContext Position
| CHSTokDerive Position
| CHSTokEnum Position
| CHSTokForeign Position
| CHSTokFun Position
| CHSTokGet Position
| CHSTokImport Position
| CHSTokLib Position
| CHSTokNewtype Position
| CHSTokPointer Position
| CHSTokPrefix Position
| CHSTokPure Position
| CHSTokQualif Position
| CHSTokSet Position
| CHSTokSizeof Position
| CHSTokStable Position
| CHSTokType Position
| CHSTok_2Case Position
| CHSTokUnsafe Position
| CHSTokWith Position
| CHSTokLock Position
| CHSTokNolock Position
| CHSTokString Position String
| CHSTokHSVerb Position String
| CHSTokIdent Position Ident
| CHSTokHaskell Position String
| CHSTokCPP Position String
| CHSTokLine Position
| CHSTokC Position String
| CHSTokCtrl Position Char
| CHSTokPragma Position
| CHSTokPragEnd Position
instance Pos CHSToken where
posOf :: CHSToken -> Position
posOf (CHSTokArrow Position
pos ) = Position
pos
posOf (CHSTokDArrow Position
pos ) = Position
pos
posOf (CHSTokDot Position
pos ) = Position
pos
posOf (CHSTokComma Position
pos ) = Position
pos
posOf (CHSTokEqual Position
pos ) = Position
pos
posOf (CHSTokMinus Position
pos ) = Position
pos
posOf (CHSTokStar Position
pos ) = Position
pos
posOf (CHSTokAmp Position
pos ) = Position
pos
posOf (CHSTokHat Position
pos ) = Position
pos
posOf (CHSTokLBrace Position
pos ) = Position
pos
posOf (CHSTokRBrace Position
pos ) = Position
pos
posOf (CHSTokLParen Position
pos ) = Position
pos
posOf (CHSTokRParen Position
pos ) = Position
pos
posOf (CHSTokEndHook Position
pos ) = Position
pos
posOf (CHSTokAs Position
pos ) = Position
pos
posOf (CHSTokCall Position
pos ) = Position
pos
posOf (CHSTokClass Position
pos ) = Position
pos
posOf (CHSTokContext Position
pos ) = Position
pos
posOf (CHSTokDerive Position
pos ) = Position
pos
posOf (CHSTokEnum Position
pos ) = Position
pos
posOf (CHSTokForeign Position
pos ) = Position
pos
posOf (CHSTokFun Position
pos ) = Position
pos
posOf (CHSTokGet Position
pos ) = Position
pos
posOf (CHSTokImport Position
pos ) = Position
pos
posOf (CHSTokLib Position
pos ) = Position
pos
posOf (CHSTokNewtype Position
pos ) = Position
pos
posOf (CHSTokPointer Position
pos ) = Position
pos
posOf (CHSTokPrefix Position
pos ) = Position
pos
posOf (CHSTokPure Position
pos ) = Position
pos
posOf (CHSTokQualif Position
pos ) = Position
pos
posOf (CHSTokSet Position
pos ) = Position
pos
posOf (CHSTokSizeof Position
pos ) = Position
pos
posOf (CHSTokStable Position
pos ) = Position
pos
posOf (CHSTokType Position
pos ) = Position
pos
posOf (CHSTok_2Case Position
pos ) = Position
pos
posOf (CHSTokUnsafe Position
pos ) = Position
pos
posOf (CHSTokWith Position
pos ) = Position
pos
posOf (CHSTokLock Position
pos ) = Position
pos
posOf (CHSTokNolock Position
pos ) = Position
pos
posOf (CHSTokString Position
pos String
_) = Position
pos
posOf (CHSTokHSVerb Position
pos String
_) = Position
pos
posOf (CHSTokIdent Position
pos Ident
_) = Position
pos
posOf (CHSTokHaskell Position
pos String
_) = Position
pos
posOf (CHSTokCPP Position
pos String
_) = Position
pos
posOf (CHSTokC Position
pos String
_) = Position
pos
posOf (CHSTokCtrl Position
pos Char
_) = Position
pos
posOf (CHSTokPragma Position
pos ) = Position
pos
posOf (CHSTokPragEnd Position
pos ) = Position
pos
instance Eq CHSToken where
(CHSTokArrow Position
_ ) == :: CHSToken -> CHSToken -> Bool
== (CHSTokArrow Position
_ ) = Bool
True
(CHSTokDArrow Position
_ ) == (CHSTokDArrow Position
_ ) = Bool
True
(CHSTokDot Position
_ ) == (CHSTokDot Position
_ ) = Bool
True
(CHSTokComma Position
_ ) == (CHSTokComma Position
_ ) = Bool
True
(CHSTokEqual Position
_ ) == (CHSTokEqual Position
_ ) = Bool
True
(CHSTokMinus Position
_ ) == (CHSTokMinus Position
_ ) = Bool
True
(CHSTokStar Position
_ ) == (CHSTokStar Position
_ ) = Bool
True
(CHSTokAmp Position
_ ) == (CHSTokAmp Position
_ ) = Bool
True
(CHSTokHat Position
_ ) == (CHSTokHat Position
_ ) = Bool
True
(CHSTokLBrace Position
_ ) == (CHSTokLBrace Position
_ ) = Bool
True
(CHSTokRBrace Position
_ ) == (CHSTokRBrace Position
_ ) = Bool
True
(CHSTokLParen Position
_ ) == (CHSTokLParen Position
_ ) = Bool
True
(CHSTokRParen Position
_ ) == (CHSTokRParen Position
_ ) = Bool
True
(CHSTokEndHook Position
_ ) == (CHSTokEndHook Position
_ ) = Bool
True
(CHSTokAs Position
_ ) == (CHSTokAs Position
_ ) = Bool
True
(CHSTokCall Position
_ ) == (CHSTokCall Position
_ ) = Bool
True
(CHSTokClass Position
_ ) == (CHSTokClass Position
_ ) = Bool
True
(CHSTokContext Position
_ ) == (CHSTokContext Position
_ ) = Bool
True
(CHSTokDerive Position
_ ) == (CHSTokDerive Position
_ ) = Bool
True
(CHSTokEnum Position
_ ) == (CHSTokEnum Position
_ ) = Bool
True
(CHSTokForeign Position
_ ) == (CHSTokForeign Position
_ ) = Bool
True
(CHSTokFun Position
_ ) == (CHSTokFun Position
_ ) = Bool
True
(CHSTokGet Position
_ ) == (CHSTokGet Position
_ ) = Bool
True
(CHSTokImport Position
_ ) == (CHSTokImport Position
_ ) = Bool
True
(CHSTokLib Position
_ ) == (CHSTokLib Position
_ ) = Bool
True
(CHSTokNewtype Position
_ ) == (CHSTokNewtype Position
_ ) = Bool
True
(CHSTokPointer Position
_ ) == (CHSTokPointer Position
_ ) = Bool
True
(CHSTokPrefix Position
_ ) == (CHSTokPrefix Position
_ ) = Bool
True
(CHSTokPure Position
_ ) == (CHSTokPure Position
_ ) = Bool
True
(CHSTokQualif Position
_ ) == (CHSTokQualif Position
_ ) = Bool
True
(CHSTokSet Position
_ ) == (CHSTokSet Position
_ ) = Bool
True
(CHSTokSizeof Position
_ ) == (CHSTokSizeof Position
_ ) = Bool
True
(CHSTokStable Position
_ ) == (CHSTokStable Position
_ ) = Bool
True
(CHSTokType Position
_ ) == (CHSTokType Position
_ ) = Bool
True
(CHSTok_2Case Position
_ ) == (CHSTok_2Case Position
_ ) = Bool
True
(CHSTokUnsafe Position
_ ) == (CHSTokUnsafe Position
_ ) = Bool
True
(CHSTokWith Position
_ ) == (CHSTokWith Position
_ ) = Bool
True
(CHSTokLock Position
_ ) == (CHSTokLock Position
_ ) = Bool
True
(CHSTokNolock Position
_ ) == (CHSTokNolock Position
_ ) = Bool
True
(CHSTokString Position
_ String
_) == (CHSTokString Position
_ String
_) = Bool
True
(CHSTokHSVerb Position
_ String
_) == (CHSTokHSVerb Position
_ String
_) = Bool
True
(CHSTokIdent Position
_ Ident
_) == (CHSTokIdent Position
_ Ident
_) = Bool
True
(CHSTokHaskell Position
_ String
_) == (CHSTokHaskell Position
_ String
_) = Bool
True
(CHSTokCPP Position
_ String
_) == (CHSTokCPP Position
_ String
_) = Bool
True
(CHSTokC Position
_ String
_) == (CHSTokC Position
_ String
_) = Bool
True
(CHSTokCtrl Position
_ Char
_) == (CHSTokCtrl Position
_ Char
_) = Bool
True
(CHSTokPragma Position
_ ) == (CHSTokPragma Position
_ ) = Bool
True
(CHSTokPragEnd Position
_ ) == (CHSTokPragEnd Position
_ ) = Bool
True
CHSToken
_ == CHSToken
_ = Bool
False
instance Show CHSToken where
showsPrec :: Int -> CHSToken -> ShowS
showsPrec Int
_ (CHSTokArrow Position
_ ) = String -> ShowS
showString String
"->"
showsPrec Int
_ (CHSTokDArrow Position
_ ) = String -> ShowS
showString String
"=>"
showsPrec Int
_ (CHSTokDot Position
_ ) = String -> ShowS
showString String
"."
showsPrec Int
_ (CHSTokComma Position
_ ) = String -> ShowS
showString String
","
showsPrec Int
_ (CHSTokEqual Position
_ ) = String -> ShowS
showString String
"="
showsPrec Int
_ (CHSTokMinus Position
_ ) = String -> ShowS
showString String
"-"
showsPrec Int
_ (CHSTokStar Position
_ ) = String -> ShowS
showString String
"*"
showsPrec Int
_ (CHSTokAmp Position
_ ) = String -> ShowS
showString String
"&"
showsPrec Int
_ (CHSTokHat Position
_ ) = String -> ShowS
showString String
"^"
showsPrec Int
_ (CHSTokLBrace Position
_ ) = String -> ShowS
showString String
"{"
showsPrec Int
_ (CHSTokRBrace Position
_ ) = String -> ShowS
showString String
"}"
showsPrec Int
_ (CHSTokLParen Position
_ ) = String -> ShowS
showString String
"("
showsPrec Int
_ (CHSTokRParen Position
_ ) = String -> ShowS
showString String
")"
showsPrec Int
_ (CHSTokEndHook Position
_ ) = String -> ShowS
showString String
"#}"
showsPrec Int
_ (CHSTokAs Position
_ ) = String -> ShowS
showString String
"as"
showsPrec Int
_ (CHSTokCall Position
_ ) = String -> ShowS
showString String
"call"
showsPrec Int
_ (CHSTokClass Position
_ ) = String -> ShowS
showString String
"class"
showsPrec Int
_ (CHSTokContext Position
_ ) = String -> ShowS
showString String
"context"
showsPrec Int
_ (CHSTokDerive Position
_ ) = String -> ShowS
showString String
"deriving"
showsPrec Int
_ (CHSTokEnum Position
_ ) = String -> ShowS
showString String
"enum"
showsPrec Int
_ (CHSTokForeign Position
_ ) = String -> ShowS
showString String
"foreign"
showsPrec Int
_ (CHSTokFun Position
_ ) = String -> ShowS
showString String
"fun"
showsPrec Int
_ (CHSTokGet Position
_ ) = String -> ShowS
showString String
"get"
showsPrec Int
_ (CHSTokImport Position
_ ) = String -> ShowS
showString String
"import"
showsPrec Int
_ (CHSTokLib Position
_ ) = String -> ShowS
showString String
"lib"
showsPrec Int
_ (CHSTokNewtype Position
_ ) = String -> ShowS
showString String
"newtype"
showsPrec Int
_ (CHSTokPointer Position
_ ) = String -> ShowS
showString String
"pointer"
showsPrec Int
_ (CHSTokPrefix Position
_ ) = String -> ShowS
showString String
"prefix"
showsPrec Int
_ (CHSTokPure Position
_ ) = String -> ShowS
showString String
"pure"
showsPrec Int
_ (CHSTokQualif Position
_ ) = String -> ShowS
showString String
"qualified"
showsPrec Int
_ (CHSTokSet Position
_ ) = String -> ShowS
showString String
"set"
showsPrec Int
_ (CHSTokSizeof Position
_ ) = String -> ShowS
showString String
"sizeof"
showsPrec Int
_ (CHSTokStable Position
_ ) = String -> ShowS
showString String
"stable"
showsPrec Int
_ (CHSTokType Position
_ ) = String -> ShowS
showString String
"type"
showsPrec Int
_ (CHSTok_2Case Position
_ ) = String -> ShowS
showString String
"underscoreToCase"
showsPrec Int
_ (CHSTokUnsafe Position
_ ) = String -> ShowS
showString String
"unsafe"
showsPrec Int
_ (CHSTokWith Position
_ ) = String -> ShowS
showString String
"with"
showsPrec Int
_ (CHSTokLock Position
_ ) = String -> ShowS
showString String
"lock"
showsPrec Int
_ (CHSTokNolock Position
_ ) = String -> ShowS
showString String
"nolock"
showsPrec Int
_ (CHSTokString Position
_ String
s) = String -> ShowS
showString (String
"\"" forall a. [a] -> [a] -> [a]
++ String
s forall a. [a] -> [a] -> [a]
++ String
"\"")
showsPrec Int
_ (CHSTokHSVerb Position
_ String
s) = String -> ShowS
showString (String
"`" forall a. [a] -> [a] -> [a]
++ String
s forall a. [a] -> [a] -> [a]
++ String
"'")
showsPrec Int
_ (CHSTokIdent Position
_ Ident
i) = (String -> ShowS
showString forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ident -> String
identToLexeme) Ident
i
showsPrec Int
_ (CHSTokHaskell Position
_ String
s) = String -> ShowS
showString String
s
showsPrec Int
_ (CHSTokCPP Position
_ String
s) = String -> ShowS
showString String
s
showsPrec Int
_ (CHSTokC Position
_ String
s) = String -> ShowS
showString String
s
showsPrec Int
_ (CHSTokCtrl Position
_ Char
c) = Char -> ShowS
showChar Char
c
showsPrec Int
_ (CHSTokPragma Position
_ ) = String -> ShowS
showString String
"{-# LANGUAGE"
showsPrec Int
_ (CHSTokPragEnd Position
_ ) = String -> ShowS
showString String
"#-}"
data CHSLexerState = CHSLS {
CHSLexerState -> Int
nestLvl :: Int,
CHSLexerState -> Bool
inHook :: Bool,
CHSLexerState -> [Name]
namesup :: [Name]
}
initialState :: CST s CHSLexerState
initialState :: forall s. CST s CHSLexerState
initialState = do
[Name]
namesup <- forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM NameSupply -> [Name]
names forall e s. PreCST e s NameSupply
getNameSupply
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ CHSLS {
nestLvl :: Int
nestLvl = Int
0,
inHook :: Bool
inHook = Bool
False,
namesup :: [Name]
namesup = [Name]
namesup
}
assertFinalState :: Position -> CHSLexerState -> CST s ()
assertFinalState :: forall s. Position -> CHSLexerState -> CST s ()
assertFinalState Position
pos CHSLS {nestLvl :: CHSLexerState -> Int
nestLvl = Int
nestLvl, inHook :: CHSLexerState -> Bool
inHook = Bool
inHook}
| Int
nestLvl forall a. Ord a => a -> a -> Bool
> Int
0 = forall e s. Position -> [String] -> PreCST e s ()
raiseError Position
pos [String
"Unexpected end of file!",
String
"Unclosed nested comment."]
| Bool
inHook = forall e s. Position -> [String] -> PreCST e s ()
raiseError Position
pos [String
"Unexpected end of file!",
String
"Unclosed binding hook."]
| Bool
otherwise = forall e s. PreCST e s ()
nop
type CHSLexer = Lexer CHSLexerState CHSToken
type CHSAction = Action CHSToken
type CHSRegexp = Regexp CHSLexerState CHSToken
infixl 3 `lexactionName`
lexactionName :: CHSRegexp
-> (String -> Position -> Name -> CHSToken)
-> CHSLexer
CHSRegexp
re lexactionName :: CHSRegexp -> (String -> Position -> Name -> CHSToken) -> CHSLexer
`lexactionName` String -> Position -> Name -> CHSToken
action = CHSRegexp
re forall s t. Regexp s t -> Meta s t -> Lexer s t
`lexmeta` forall {a} {a}.
String
-> Position
-> CHSLexerState
-> (Maybe (Either a CHSToken), Position, CHSLexerState, Maybe a)
action'
where
action' :: String
-> Position
-> CHSLexerState
-> (Maybe (Either a CHSToken), Position, CHSLexerState, Maybe a)
action' String
str Position
pos CHSLexerState
state = let Name
name:[Name]
ns = CHSLexerState -> [Name]
namesup CHSLexerState
state
in
(forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right (String -> Position -> Name -> CHSToken
action String
str Position
pos Name
name),
Position -> Int -> Position
incPos Position
pos (forall (t :: * -> *) a. Foldable t => t a -> Int
length String
str),
CHSLexerState
state {namesup :: [Name]
namesup = [Name]
ns},
forall a. Maybe a
Nothing)
chslexer :: CHSLexer
chslexer :: CHSLexer
chslexer = CHSLexer
pragma
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< CHSLexer
haskell
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< CHSLexer
nested
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< CHSLexer
ctrl
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< CHSLexer
hook
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< CHSLexer
cpp
pragma :: CHSLexer
pragma :: CHSLexer
pragma = forall s t. String -> Regexp s t
string String
"{-# LANGUAGE" forall s t. Regexp s t -> Meta s t -> Lexer s t
`lexmeta` \String
_ Position
pos CHSLexerState
s ->
(forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right (Position -> CHSToken
CHSTokPragma Position
pos), Position -> Int -> Position
incPos Position
pos Int
12, CHSLexerState
s, forall a. a -> Maybe a
Just CHSLexer
langLexer)
langLexer :: CHSLexer
langLexer :: CHSLexer
langLexer = CHSLexer
whitespace forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< CHSLexer
identOrKW forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< CHSLexer
symbol forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||<
(forall s t. String -> Regexp s t
string String
"#-}" forall s t. Regexp s t -> Meta s t -> Lexer s t
`lexmeta` \String
_ Position
pos CHSLexerState
s ->
(forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right (Position -> CHSToken
CHSTokPragEnd Position
pos), Position -> Int -> Position
incPos Position
pos Int
3, CHSLexerState
s, forall a. a -> Maybe a
Just CHSLexer
chslexer))
haskell :: CHSLexer
haskell :: CHSLexer
haskell = ( forall {s} {t}. Regexp s t
anyButSpecialforall s t. Regexp s t -> Regexp s t -> Regexp s t
`star` forall {s} {t}. Regexp s t
epsilon
forall s t. Regexp s t -> Regexp s t -> Regexp s t
>|< forall {s} {t}. Regexp s t
specialButQuotes
forall s t. Regexp s t -> Regexp s t -> Regexp s t
>|< forall s t. Char -> Regexp s t
char Char
'"' forall s t. Regexp s t -> Regexp s t -> Regexp s t
+> forall {s} {t}. Regexp s t
inhstrforall s t. Regexp s t -> Regexp s t -> Regexp s t
`star` forall s t. Char -> Regexp s t
char Char
'"'
forall s t. Regexp s t -> Regexp s t -> Regexp s t
>|< forall s t. String -> Regexp s t
string String
"'\"'"
forall s t. Regexp s t -> Regexp s t -> Regexp s t
>|< forall s t. String -> Regexp s t
string String
"--" forall s t. Regexp s t -> Regexp s t -> Regexp s t
+> forall {s} {t}. Regexp s t
anyButNLforall s t. Regexp s t -> Regexp s t -> Regexp s t
`star` forall {s} {t}. Regexp s t
epsilon
)
forall s t. Regexp s t -> Action t -> Lexer s t
`lexaction` CHSAction
copyVerbatim
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< forall s t. Char -> Regexp s t
char Char
'"'
forall s t. Regexp s t -> ActionErr t -> Lexer s t
`lexactionErr`
\String
_ Position
pos -> (forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ ErrorLvl -> Position -> [String] -> Error
makeError ErrorLvl
ErrorErr Position
pos
[String
"Lexical error!",
String
"Unclosed string."])
where
anyButSpecial :: Regexp s t
anyButSpecial = forall s t. String -> Regexp s t
alt (String
inlineSet forall a. Eq a => [a] -> [a] -> [a]
\\ String
specialSet)
specialButQuotes :: Regexp s t
specialButQuotes = forall s t. String -> Regexp s t
alt (String
specialSet forall a. Eq a => [a] -> [a] -> [a]
\\ [Char
'"'])
anyButNL :: Regexp s t
anyButNL = forall s t. String -> Regexp s t
alt (String
anySet forall a. Eq a => [a] -> [a] -> [a]
\\ [Char
'\n'])
inhstr :: Regexp s t
inhstr = forall {s} {t}. Regexp s t
instr forall s t. Regexp s t -> Regexp s t -> Regexp s t
>|< forall s t. Char -> Regexp s t
char Char
'\\' forall s t. Regexp s t -> Regexp s t -> Regexp s t
>|< forall s t. String -> Regexp s t
string String
"\\\"" forall s t. Regexp s t -> Regexp s t -> Regexp s t
>|< forall {s} {t}. Regexp s t
gap
gap :: Regexp s t
gap = forall s t. Char -> Regexp s t
char Char
'\\' forall s t. Regexp s t -> Regexp s t -> Regexp s t
+> forall s t. String -> Regexp s t
alt (Char
' 'forall a. a -> [a] -> [a]
:String
ctrlSet)forall s t. Regexp s t -> Regexp s t -> Regexp s t
`plus` forall s t. Char -> Regexp s t
char Char
'\\'
copyVerbatim :: CHSAction
copyVerbatim :: CHSAction
copyVerbatim String
cs Position
pos = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Position -> String -> CHSToken
CHSTokHaskell Position
pos String
cs
nested :: CHSLexer
nested :: CHSLexer
nested =
forall s t. String -> Regexp s t
string String
"{-"
forall s t. Regexp s t -> Meta s t -> Lexer s t
`lexmeta` forall {a}.
String
-> Position
-> CHSLexerState
-> (Maybe (Either a CHSToken), Position, CHSLexerState,
Maybe CHSLexer)
enterComment
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||<
forall s t. String -> Regexp s t
string String
"-}"
forall s t. Regexp s t -> Meta s t -> Lexer s t
`lexmeta` String
-> Position
-> CHSLexerState
-> (Maybe (Either Error CHSToken), Position, CHSLexerState,
Maybe CHSLexer)
leaveComment
where
enterComment :: String
-> Position
-> CHSLexerState
-> (Maybe (Either a CHSToken), Position, CHSLexerState,
Maybe CHSLexer)
enterComment String
cs Position
pos CHSLexerState
s =
(forall {a}. String -> Position -> Maybe (Either a CHSToken)
copyVerbatim' String
cs Position
pos,
Position -> Int -> Position
incPos Position
pos Int
2,
CHSLexerState
s {nestLvl :: Int
nestLvl = CHSLexerState -> Int
nestLvl CHSLexerState
s forall a. Num a => a -> a -> a
+ Int
1},
forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ CHSLexer
inNestedComment)
leaveComment :: String
-> Position
-> CHSLexerState
-> (Maybe (Either Error CHSToken), Position, CHSLexerState,
Maybe CHSLexer)
leaveComment String
cs Position
pos CHSLexerState
s =
case CHSLexerState -> Int
nestLvl CHSLexerState
s of
Int
0 -> (forall {b}. Position -> Maybe (Either Error b)
commentCloseErr Position
pos,
Position -> Int -> Position
incPos Position
pos Int
2,
CHSLexerState
s,
forall a. Maybe a
Nothing)
Int
1 -> (forall {a}. String -> Position -> Maybe (Either a CHSToken)
copyVerbatim' String
cs Position
pos,
Position -> Int -> Position
incPos Position
pos Int
2,
CHSLexerState
s {nestLvl :: Int
nestLvl = CHSLexerState -> Int
nestLvl CHSLexerState
s forall a. Num a => a -> a -> a
- Int
1},
forall a. a -> Maybe a
Just CHSLexer
chslexer)
Int
_ -> (forall {a}. String -> Position -> Maybe (Either a CHSToken)
copyVerbatim' String
cs Position
pos,
Position -> Int -> Position
incPos Position
pos Int
2,
CHSLexerState
s {nestLvl :: Int
nestLvl = CHSLexerState -> Int
nestLvl CHSLexerState
s forall a. Num a => a -> a -> a
- Int
1},
forall a. Maybe a
Nothing)
copyVerbatim' :: String -> Position -> Maybe (Either a CHSToken)
copyVerbatim' String
cs Position
pos = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right (Position -> String -> CHSToken
CHSTokHaskell Position
pos String
cs)
commentCloseErr :: Position -> Maybe (Either Error b)
commentCloseErr Position
pos =
forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left (ErrorLvl -> Position -> [String] -> Error
makeError ErrorLvl
ErrorErr Position
pos
[String
"Lexical error!",
String
"`-}' not preceded by a matching `{-'."])
inNestedComment :: CHSLexer
= CHSLexer
commentInterior
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< CHSLexer
nested
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< CHSLexer
ctrl
commentInterior :: CHSLexer
= ( forall {s} {t}. Regexp s t
anyButSpecialforall s t. Regexp s t -> Regexp s t -> Regexp s t
`star` forall {s} {t}. Regexp s t
epsilon
forall s t. Regexp s t -> Regexp s t -> Regexp s t
>|< forall {s} {t}. Regexp s t
special
)
forall s t. Regexp s t -> Action t -> Lexer s t
`lexaction` CHSAction
copyVerbatim
where
anyButSpecial :: Regexp s t
anyButSpecial = forall s t. String -> Regexp s t
alt (String
inlineSet forall a. Eq a => [a] -> [a] -> [a]
\\ String
commentSpecialSet)
special :: Regexp s t
special = forall s t. String -> Regexp s t
alt String
commentSpecialSet
ctrl :: CHSLexer
ctrl :: CHSLexer
ctrl =
forall s t. Char -> Regexp s t
char Char
'\n' forall s t. Regexp s t -> Meta s t -> Lexer s t
`lexmeta` forall {c} {a} {a}.
String
-> Position
-> c
-> (Maybe (Either a CHSToken), Position, c, Maybe a)
newline
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< forall s t. Char -> Regexp s t
char Char
'\r' forall s t. Regexp s t -> Meta s t -> Lexer s t
`lexmeta` forall {c} {a} {a}.
String
-> Position
-> c
-> (Maybe (Either a CHSToken), Position, c, Maybe a)
newline
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< forall s t. Char -> Regexp s t
char Char
'\v' forall s t. Regexp s t -> Meta s t -> Lexer s t
`lexmeta` forall {c} {a} {a}.
String
-> Position
-> c
-> (Maybe (Either a CHSToken), Position, c, Maybe a)
newline
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< forall s t. Char -> Regexp s t
char Char
'\f' forall s t. Regexp s t -> Meta s t -> Lexer s t
`lexmeta` forall {c} {a} {a}.
String
-> Position
-> c
-> (Maybe (Either a CHSToken), Position, c, Maybe a)
formfeed
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< forall s t. Char -> Regexp s t
char Char
'\t' forall s t. Regexp s t -> Meta s t -> Lexer s t
`lexmeta` forall {c} {a} {a}.
String
-> Position
-> c
-> (Maybe (Either a CHSToken), Position, c, Maybe a)
tab
where
newline :: String
-> Position
-> c
-> (Maybe (Either a CHSToken), Position, c, Maybe a)
newline [Char
c] Position
pos = forall {b} {c} {a} {a}.
Position
-> Char -> b -> c -> (Maybe (Either a CHSToken), b, c, Maybe a)
ctrlResult Position
pos Char
c (Position -> Position
retPos Position
pos)
formfeed :: String
-> Position
-> c
-> (Maybe (Either a CHSToken), Position, c, Maybe a)
formfeed [Char
c] Position
pos = forall {b} {c} {a} {a}.
Position
-> Char -> b -> c -> (Maybe (Either a CHSToken), b, c, Maybe a)
ctrlResult Position
pos Char
c (Position -> Int -> Position
incPos Position
pos Int
1)
tab :: String
-> Position
-> c
-> (Maybe (Either a CHSToken), Position, c, Maybe a)
tab [Char
c] Position
pos = forall {b} {c} {a} {a}.
Position
-> Char -> b -> c -> (Maybe (Either a CHSToken), b, c, Maybe a)
ctrlResult Position
pos Char
c (Position -> Position
tabPos Position
pos)
ctrlResult :: Position
-> Char -> b -> c -> (Maybe (Either a CHSToken), b, c, Maybe a)
ctrlResult Position
pos Char
c b
pos' c
s =
(forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right (Position -> Char -> CHSToken
CHSTokCtrl Position
pos Char
c), b
pos', c
s, forall a. Maybe a
Nothing)
hook :: CHSLexer
hook :: CHSLexer
hook = forall s t. String -> Regexp s t
string String
"{#"
forall s t. Regexp s t -> Meta s t -> Lexer s t
`lexmeta` \String
_ Position
pos CHSLexerState
s -> (forall a. Maybe a
Nothing, Position -> Int -> Position
incPos Position
pos Int
2, CHSLexerState
s, forall a. a -> Maybe a
Just CHSLexer
bhLexer)
cpp :: CHSLexer
cpp :: CHSLexer
cpp = CHSLexer
directive
where
directive :: CHSLexer
directive =
forall s t. String -> Regexp s t
string String
"\n#" forall s t. Regexp s t -> Regexp s t -> Regexp s t
+> forall s t. String -> Regexp s t
alt (Char
'\t'forall a. a -> [a] -> [a]
:String
inlineSet)forall s t. Regexp s t -> Regexp s t -> Regexp s t
`star` forall {s} {t}. Regexp s t
epsilon
forall s t. Regexp s t -> Meta s t -> Lexer s t
`lexmeta`
\(Char
_:Char
_:String
dir) Position
pos CHSLexerState
s ->
case String
dir of
[Char
'c'] ->
(forall a. Maybe a
Nothing, Position -> Position
retPos Position
pos, CHSLexerState
s, forall a. a -> Maybe a
Just CHSLexer
cLexer)
Char
'c':Char
sp:String
_ | Char
sp forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
" \t" ->
(forall a. Maybe a
Nothing, Position -> Position
retPos Position
pos, CHSLexerState
s, forall a. a -> Maybe a
Just CHSLexer
cLexer)
Char
' ':line :: String
line@(Char
n:String
_) | Char -> Bool
isDigit Char
n ->
let pos' :: Position
pos' = String -> Position -> Position
adjustPosByCLinePragma String
line Position
pos
in (forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right (Position -> CHSToken
CHSTokLine Position
pos'), Position
pos', CHSLexerState
s, forall a. Maybe a
Nothing)
String
_ ->
(forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right (Position -> String -> CHSToken
CHSTokCPP Position
pos String
dir),
Position -> Position
retPos Position
pos, CHSLexerState
s, forall a. Maybe a
Nothing)
adjustPosByCLinePragma :: String -> Position -> Position
adjustPosByCLinePragma :: String -> Position -> Position
adjustPosByCLinePragma String
str (Position String
fname Int
_ Int
_) =
(String -> Int -> Int -> Position
Position String
fname' Int
row' Int
0)
where
str' :: String
str' = ShowS
dropWhite String
str
(String
rowStr, String
str'') = forall a. (a -> Bool) -> [a] -> ([a], [a])
span Char -> Bool
isDigit String
str'
row' :: Int
row' = forall a. Read a => String -> a
read String
rowStr
str''' :: String
str''' = ShowS
dropWhite String
str''
fnameStr :: String
fnameStr = forall a. (a -> Bool) -> [a] -> [a]
takeWhile (forall a. Eq a => a -> a -> Bool
/= Char
'"') forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> [a]
drop Int
1 forall a b. (a -> b) -> a -> b
$ String
str'''
fname' :: String
fname' | forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
str''' Bool -> Bool -> Bool
|| forall a. [a] -> a
head String
str''' forall a. Eq a => a -> a -> Bool
/= Char
'"' = String
fname
| String
fnameStr forall a. Eq a => a -> a -> Bool
== String
fname = String
fname
| Bool
otherwise = String
fnameStr
dropWhite :: ShowS
dropWhite = forall a. (a -> Bool) -> [a] -> [a]
dropWhile (\Char
c -> Char
c forall a. Eq a => a -> a -> Bool
== Char
' ' Bool -> Bool -> Bool
|| Char
c forall a. Eq a => a -> a -> Bool
== Char
'\t')
bhLexer :: CHSLexer
bhLexer :: CHSLexer
bhLexer = CHSLexer
identOrKW
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< CHSLexer
symbol
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< CHSLexer
strlit
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< CHSLexer
hsverb
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< CHSLexer
whitespace
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< CHSLexer
endOfHook
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< forall s t. String -> Regexp s t
string String
"--" forall s t. Regexp s t -> Regexp s t -> Regexp s t
+> forall {s} {t}. Regexp s t
anyButNLforall s t. Regexp s t -> Regexp s t -> Regexp s t
`star` forall s t. Char -> Regexp s t
char Char
'\n'
forall s t. Regexp s t -> Meta s t -> Lexer s t
`lexmeta` \String
_ Position
pos CHSLexerState
s -> (forall a. Maybe a
Nothing, Position -> Position
retPos Position
pos, CHSLexerState
s, forall a. Maybe a
Nothing)
where
anyButNL :: Regexp s t
anyButNL = forall s t. String -> Regexp s t
alt (String
anySet forall a. Eq a => [a] -> [a] -> [a]
\\ [Char
'\n'])
endOfHook :: CHSLexer
endOfHook = forall s t. String -> Regexp s t
string String
"#}"
forall s t. Regexp s t -> Meta s t -> Lexer s t
`lexmeta`
\String
_ Position
pos CHSLexerState
s -> (forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right (Position -> CHSToken
CHSTokEndHook Position
pos),
Position -> Int -> Position
incPos Position
pos Int
2, CHSLexerState
s, forall a. a -> Maybe a
Just CHSLexer
chslexer)
cLexer :: CHSLexer
cLexer :: CHSLexer
cLexer = forall {s}. Lexer s CHSToken
inlineC
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< CHSLexer
ctrl
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< forall s t. String -> Regexp s t
string String
"\n#endc"
forall s t. Regexp s t -> Meta s t -> Lexer s t
`lexmeta`
\String
_ Position
pos CHSLexerState
s -> (forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right (Position -> Char -> CHSToken
CHSTokCtrl Position
pos Char
'\n'), Position -> Position
retPos Position
pos, CHSLexerState
s,
forall a. a -> Maybe a
Just CHSLexer
chslexer)
where
inlineC :: Lexer s CHSToken
inlineC = forall s t. String -> Regexp s t
alt String
inlineSet forall s t. Regexp s t -> Action t -> Lexer s t
`lexaction` CHSAction
copyVerbatimC
copyVerbatimC :: CHSAction
copyVerbatimC :: CHSAction
copyVerbatimC String
cs Position
pos = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Position -> String -> CHSToken
CHSTokC Position
pos String
cs
whitespace :: CHSLexer
whitespace :: CHSLexer
whitespace = (forall s t. Char -> Regexp s t
char Char
' ' forall s t. Regexp s t -> Action t -> Lexer s t
`lexaction` \String
_ Position
_ -> forall a. Maybe a
Nothing)
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< forall s t. Lexer s t
ctrlLexer
identOrKW :: CHSLexer
identOrKW :: CHSLexer
identOrKW =
(forall {s} {t}. Regexp s t
letter forall s t. Regexp s t -> Regexp s t -> Regexp s t
+> (forall {s} {t}. Regexp s t
letter forall s t. Regexp s t -> Regexp s t -> Regexp s t
>|< forall {s} {t}. Regexp s t
digit forall s t. Regexp s t -> Regexp s t -> Regexp s t
>|< forall s t. Char -> Regexp s t
char Char
'\'')forall s t. Regexp s t -> Regexp s t -> Regexp s t
`star` forall {s} {t}. Regexp s t
epsilon
CHSRegexp -> (String -> Position -> Name -> CHSToken) -> CHSLexer
`lexactionName` \String
cs Position
pos Name
name -> (Position -> String -> Name -> CHSToken
idkwtok forall a b. (a -> b) -> a -> b
$!Position
pos) String
cs Name
name)
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||<
(forall s t. Char -> Regexp s t
char Char
'\'' forall s t. Regexp s t -> Regexp s t -> Regexp s t
+> forall {s} {t}. Regexp s t
letter forall s t. Regexp s t -> Regexp s t -> Regexp s t
+> (forall {s} {t}. Regexp s t
letter forall s t. Regexp s t -> Regexp s t -> Regexp s t
>|< forall {s} {t}. Regexp s t
digit)forall s t. Regexp s t -> Regexp s t -> Regexp s t
`star` forall s t. Char -> Regexp s t
char Char
'\''
CHSRegexp -> (String -> Position -> Name -> CHSToken) -> CHSLexer
`lexactionName` \String
cs Position
pos Name
name -> (Position -> String -> Name -> CHSToken
mkid forall a b. (a -> b) -> a -> b
$!Position
pos) String
cs Name
name)
where
idkwtok :: Position -> String -> Name -> CHSToken
idkwtok Position
pos String
"as" Name
_ = Position -> CHSToken
CHSTokAs Position
pos
idkwtok Position
pos String
"call" Name
_ = Position -> CHSToken
CHSTokCall Position
pos
idkwtok Position
pos String
"class" Name
_ = Position -> CHSToken
CHSTokClass Position
pos
idkwtok Position
pos String
"context" Name
_ = Position -> CHSToken
CHSTokContext Position
pos
idkwtok Position
pos String
"deriving" Name
_ = Position -> CHSToken
CHSTokDerive Position
pos
idkwtok Position
pos String
"enum" Name
_ = Position -> CHSToken
CHSTokEnum Position
pos
idkwtok Position
pos String
"foreign" Name
_ = Position -> CHSToken
CHSTokForeign Position
pos
idkwtok Position
pos String
"fun" Name
_ = Position -> CHSToken
CHSTokFun Position
pos
idkwtok Position
pos String
"get" Name
_ = Position -> CHSToken
CHSTokGet Position
pos
idkwtok Position
pos String
"import" Name
_ = Position -> CHSToken
CHSTokImport Position
pos
idkwtok Position
pos String
"lib" Name
_ = Position -> CHSToken
CHSTokLib Position
pos
idkwtok Position
pos String
"newtype" Name
_ = Position -> CHSToken
CHSTokNewtype Position
pos
idkwtok Position
pos String
"pointer" Name
_ = Position -> CHSToken
CHSTokPointer Position
pos
idkwtok Position
pos String
"prefix" Name
_ = Position -> CHSToken
CHSTokPrefix Position
pos
idkwtok Position
pos String
"pure" Name
_ = Position -> CHSToken
CHSTokPure Position
pos
idkwtok Position
pos String
"qualified" Name
_ = Position -> CHSToken
CHSTokQualif Position
pos
idkwtok Position
pos String
"set" Name
_ = Position -> CHSToken
CHSTokSet Position
pos
idkwtok Position
pos String
"sizeof" Name
_ = Position -> CHSToken
CHSTokSizeof Position
pos
idkwtok Position
pos String
"stable" Name
_ = Position -> CHSToken
CHSTokStable Position
pos
idkwtok Position
pos String
"type" Name
_ = Position -> CHSToken
CHSTokType Position
pos
idkwtok Position
pos String
"underscoreToCase" Name
_ = Position -> CHSToken
CHSTok_2Case Position
pos
idkwtok Position
pos String
"unsafe" Name
_ = Position -> CHSToken
CHSTokUnsafe Position
pos
idkwtok Position
pos String
"with" Name
_ = Position -> CHSToken
CHSTokWith Position
pos
idkwtok Position
pos String
"lock" Name
_ = Position -> CHSToken
CHSTokLock Position
pos
idkwtok Position
pos String
"nolock" Name
_ = Position -> CHSToken
CHSTokNolock Position
pos
idkwtok Position
pos String
cs Name
name = Position -> String -> Name -> CHSToken
mkid Position
pos String
cs Name
name
mkid :: Position -> String -> Name -> CHSToken
mkid Position
pos String
cs Name
name = Position -> Ident -> CHSToken
CHSTokIdent Position
pos (Position -> String -> Name -> Ident
lexemeToIdent Position
pos String
cs Name
name)
symbol :: CHSLexer
symbol :: CHSLexer
symbol = forall {t} {s}. String -> (Position -> t) -> Lexer s t
sym String
"->" Position -> CHSToken
CHSTokArrow
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< forall {t} {s}. String -> (Position -> t) -> Lexer s t
sym String
"=>" Position -> CHSToken
CHSTokDArrow
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< forall {t} {s}. String -> (Position -> t) -> Lexer s t
sym String
"." Position -> CHSToken
CHSTokDot
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< forall {t} {s}. String -> (Position -> t) -> Lexer s t
sym String
"," Position -> CHSToken
CHSTokComma
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< forall {t} {s}. String -> (Position -> t) -> Lexer s t
sym String
"=" Position -> CHSToken
CHSTokEqual
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< forall {t} {s}. String -> (Position -> t) -> Lexer s t
sym String
"-" Position -> CHSToken
CHSTokMinus
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< forall {t} {s}. String -> (Position -> t) -> Lexer s t
sym String
"*" Position -> CHSToken
CHSTokStar
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< forall {t} {s}. String -> (Position -> t) -> Lexer s t
sym String
"&" Position -> CHSToken
CHSTokAmp
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< forall {t} {s}. String -> (Position -> t) -> Lexer s t
sym String
"^" Position -> CHSToken
CHSTokHat
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< forall {t} {s}. String -> (Position -> t) -> Lexer s t
sym String
"{" Position -> CHSToken
CHSTokLBrace
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< forall {t} {s}. String -> (Position -> t) -> Lexer s t
sym String
"}" Position -> CHSToken
CHSTokRBrace
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< forall {t} {s}. String -> (Position -> t) -> Lexer s t
sym String
"(" Position -> CHSToken
CHSTokLParen
forall s t. Lexer s t -> Lexer s t -> Lexer s t
>||< forall {t} {s}. String -> (Position -> t) -> Lexer s t
sym String
")" Position -> CHSToken
CHSTokRParen
where
sym :: String -> (Position -> t) -> Lexer s t
sym String
cs Position -> t
con = forall s t. String -> Regexp s t
string String
cs forall s t. Regexp s t -> Action t -> Lexer s t
`lexaction` \String
_ Position
pos -> forall a. a -> Maybe a
Just (Position -> t
con Position
pos)
strlit :: CHSLexer
strlit :: CHSLexer
strlit = forall s t. Char -> Regexp s t
char Char
'"' forall s t. Regexp s t -> Regexp s t -> Regexp s t
+> (forall {s} {t}. Regexp s t
instr forall s t. Regexp s t -> Regexp s t -> Regexp s t
>|< forall s t. Char -> Regexp s t
char Char
'\\')forall s t. Regexp s t -> Regexp s t -> Regexp s t
`star` forall s t. Char -> Regexp s t
char Char
'"'
forall s t. Regexp s t -> Action t -> Lexer s t
`lexaction` \String
cs Position
pos -> forall a. a -> Maybe a
Just (Position -> String -> CHSToken
CHSTokString Position
pos (forall a. [a] -> [a]
init forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
tail forall a b. (a -> b) -> a -> b
$ String
cs))
hsverb :: CHSLexer
hsverb :: CHSLexer
hsverb = forall s t. Char -> Regexp s t
char Char
'`' forall s t. Regexp s t -> Regexp s t -> Regexp s t
+> forall {s} {t}. Regexp s t
inhsverbforall s t. Regexp s t -> Regexp s t -> Regexp s t
`star` forall s t. Char -> Regexp s t
char Char
'\''
forall s t. Regexp s t -> Action t -> Lexer s t
`lexaction` \String
cs Position
pos -> forall a. a -> Maybe a
Just (Position -> String -> CHSToken
CHSTokHSVerb Position
pos (forall a. [a] -> [a]
init forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
tail forall a b. (a -> b) -> a -> b
$ String
cs))
letter, digit, instr, inchar, inhsverb :: Regexp s t
letter :: forall {s} {t}. Regexp s t
letter = forall s t. String -> Regexp s t
alt [Char
'a'..Char
'z'] forall s t. Regexp s t -> Regexp s t -> Regexp s t
>|< forall s t. String -> Regexp s t
alt [Char
'A'..Char
'Z'] forall s t. Regexp s t -> Regexp s t -> Regexp s t
>|< forall s t. Char -> Regexp s t
char Char
'_'
digit :: forall {s} {t}. Regexp s t
digit = forall s t. String -> Regexp s t
alt [Char
'0'..Char
'9']
instr :: forall {s} {t}. Regexp s t
instr = forall s t. String -> Regexp s t
alt ([Char
' '..Char
'\127'] forall a. Eq a => [a] -> [a] -> [a]
\\ String
"\"\\")
inchar :: forall {s} {t}. Regexp s t
inchar = forall s t. String -> Regexp s t
alt ([Char
' '..Char
'\127'] forall a. Eq a => [a] -> [a] -> [a]
\\ String
"\'")
inhsverb :: forall {s} {t}. Regexp s t
inhsverb = forall s t. String -> Regexp s t
alt ([Char
' '..Char
'\127'] forall a. Eq a => [a] -> [a] -> [a]
\\ String
"\'")
anySet, inlineSet, specialSet, commentSpecialSet, ctrlSet :: [Char]
anySet :: String
anySet = [Char
'\0'..Char
'\255']
inlineSet :: String
inlineSet = String
anySet forall a. Eq a => [a] -> [a] -> [a]
\\ String
ctrlSet
specialSet :: String
specialSet = [Char
'{', Char
'-', Char
'"', Char
'\'']
= [Char
'{', Char
'-']
ctrlSet :: String
ctrlSet = [Char
'\n', Char
'\f', Char
'\r', Char
'\t', Char
'\v']
lexCHS :: String -> Position -> CST s [CHSToken]
lexCHS :: forall s. String -> Position -> CST s [CHSToken]
lexCHS String
cs Position
pos =
do
CHSLexerState
state <- forall s. CST s CHSLexerState
initialState
let ([CHSToken]
ts, LexerState CHSLexerState
lstate, [Error]
errs) = forall s t.
Lexer s t -> LexerState s -> ([t], LexerState s, [Error])
execLexer CHSLexer
chslexer (String
cs, Position
pos, CHSLexerState
state)
(String
_, Position
pos', CHSLexerState
state') = LexerState CHSLexerState
lstate
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall e s. Error -> PreCST e s ()
raise [Error]
errs
forall s. Position -> CHSLexerState -> CST s ()
assertFinalState Position
pos' CHSLexerState
state'
forall (m :: * -> *) a. Monad m => a -> m a
return [CHSToken]
ts