module Hlex
(
Grammar
, GrammarRule(..)
, Lexer
, LexException(..)
, hlex
) where
import Text.Regex.TDFA ((=~))
import Data.Maybe (maybeToList)
data LexException
= UnmatchedException
Int
Int
String
| MatchedException
Int
Int
String
String
deriving(ReadPrec [LexException]
ReadPrec LexException
Int -> ReadS LexException
ReadS [LexException]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LexException]
$creadListPrec :: ReadPrec [LexException]
readPrec :: ReadPrec LexException
$creadPrec :: ReadPrec LexException
readList :: ReadS [LexException]
$creadList :: ReadS [LexException]
readsPrec :: Int -> ReadS LexException
$creadsPrec :: Int -> ReadS LexException
Read, Int -> LexException -> ShowS
[LexException] -> ShowS
LexException -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LexException] -> ShowS
$cshowList :: [LexException] -> ShowS
show :: LexException -> String
$cshow :: LexException -> String
showsPrec :: Int -> LexException -> ShowS
$cshowsPrec :: Int -> LexException -> ShowS
Show, LexException -> LexException -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LexException -> LexException -> Bool
$c/= :: LexException -> LexException -> Bool
== :: LexException -> LexException -> Bool
$c== :: LexException -> LexException -> Bool
Eq)
data GrammarRule token
= Skip
String
| Tokenize
String
(String -> token)
| JustToken
String
token
| Error
String
String
type Grammar token = [GrammarRule token]
type Lexer token = String -> Either LexException [token]
hlex :: Grammar token -> Lexer token
hlex :: forall token. Grammar token -> Lexer token
hlex = forall token. Int -> Int -> Grammar token -> Lexer token
hlex' Int
1 Int
1
hlex' :: Int -> Int -> Grammar token -> Lexer token
hlex' :: forall token. Int -> Int -> Grammar token -> Lexer token
hlex' Int
_ Int
_ Grammar token
_ [] = forall a b. b -> Either a b
Right []
hlex' Int
row Int
col tzss :: Grammar token
tzss@(GrammarRule token
tz:Grammar token
tzs) String
program =
if forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
matchedText
then forall token. Int -> Int -> Grammar token -> Lexer token
hlex' Int
row Int
col Grammar token
tzs String
program
else case GrammarRule token
tz of
Error String
_ String
errMessage -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Int -> Int -> String -> String -> LexException
MatchedException (Int -> Int -> String -> (Int, Int)
getLastCharPos Int
row Int
col String
beforeProgram) String
matchedText String
errMessage
Skip String
_ -> Maybe token -> Either LexException [token]
lexCont forall a. Maybe a
Nothing
Tokenize String
_ String -> token
f -> Maybe token -> Either LexException [token]
lexCont forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ String -> token
f String
matchedText
JustToken String
_ token
token -> Maybe token -> Either LexException [token]
lexCont forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just token
token
where
(String
beforeProgram, String
matchedText, String
afterProgram) = String
program forall source source1 target.
(RegexMaker Regex CompOption ExecOption source,
RegexContext Regex source1 target) =>
source1 -> source -> target
=~ forall token. GrammarRule token -> String
getRegex GrammarRule token
tz :: (String, String, String)
lexCont :: Maybe token -> Either LexException [token]
lexCont Maybe token
t = do
[token]
before <- forall token. Int -> Int -> Grammar token -> Lexer token
hlex' Int
row Int
col Grammar token
tzs String
beforeProgram
[token]
after <- forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall token. Int -> Int -> Grammar token -> Lexer token
hlex' (Int -> Int -> String -> (Int, Int)
getLastCharPos Int
row Int
col (String
beforeProgram forall a. [a] -> [a] -> [a]
++ String
matchedText)) Grammar token
tzss String
afterProgram
forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ [token]
before forall a. [a] -> [a] -> [a]
++ forall a. Maybe a -> [a]
maybeToList Maybe token
t forall a. [a] -> [a] -> [a]
++ [token]
after
hlex' Int
row Int
col Grammar token
_ String
invalidString = forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ Int -> Int -> String -> LexException
UnmatchedException Int
row Int
col String
invalidString
getLastCharPos :: Int -> Int -> String -> (Int, Int)
getLastCharPos :: Int -> Int -> String -> (Int, Int)
getLastCharPos Int
startRow Int
startCol String
x = (Int
startRow forall a. Num a => a -> a -> a
+ Int
addRow, Int
addCol forall a. Num a => a -> a -> a
+ if Int
addRow forall a. Eq a => a -> a -> Bool
== Int
0 then Int
startCol else Int
1)
where
ls :: [String]
ls = String -> [String]
lines String
x
addRow :: Int
addRow = forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
ls forall a. Num a => a -> a -> a
- Int
1
addCol :: Int
addCol = forall (t :: * -> *) a. Foldable t => t a -> Int
length forall a b. (a -> b) -> a -> b
$ forall a. [a] -> a
last [String]
ls
getRegex :: GrammarRule token -> String
getRegex :: forall token. GrammarRule token -> String
getRegex (Skip String
regex) = String
regex
getRegex (Tokenize String
regex String -> token
_) = String
regex
getRegex (JustToken String
regex token
_) = String
regex
getRegex (Error String
regex String
_) = String
regex