module Hlex
(
Grammar
, TokenSyntax(..)
, Lexer
, LexException(..)
, hlex
) where
import Text.Regex.TDFA ((=~))
data LexException = LexException
Int
Int
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 TokenSyntax token
= Skip
String
| Tokenize
String
(String -> token)
| JustToken
String
token
type InternalToken token = (String, Maybe (String -> token))
type Grammar token = [TokenSyntax token]
type Lexer token = String -> Either LexException [token]
tokenizerToInternalToken :: TokenSyntax a -> InternalToken a
tokenizerToInternalToken :: forall a. TokenSyntax a -> InternalToken a
tokenizerToInternalToken (Skip String
regex) = (String
regex, forall a. Maybe a
Nothing)
tokenizerToInternalToken (Tokenize String
regex String -> a
toToken) = (String
regex, forall a. a -> Maybe a
Just String -> a
toToken)
tokenizerToInternalToken (JustToken String
regex a
token) = (String
regex, forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ \String
_ -> a
token)
hlex :: Grammar token -> Lexer token
hlex :: forall token. Grammar token -> Lexer token
hlex = forall token. Int -> Int -> [InternalToken token] -> Lexer token
lexInternal Int
1 Int
1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall a. TokenSyntax a -> InternalToken a
tokenizerToInternalToken
lexInternal :: Int -> Int -> [InternalToken token] -> Lexer token
lexInternal :: forall token. Int -> Int -> [InternalToken token] -> Lexer token
lexInternal Int
_ Int
_ [InternalToken token]
_ String
"" = forall a b. b -> Either a b
Right []
lexInternal Int
row Int
col ((String
regex, Maybe (String -> token)
t):[InternalToken token]
grammar) String
program = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
matchedText
then forall token. Int -> Int -> [InternalToken token] -> Lexer token
lexInternal Int
row Int
col [InternalToken token]
grammar String
program
else do
[token]
before <- Either LexException [token]
parsedBefore
[token]
after <- Either LexException [token]
parsedAfter
case Maybe (String -> token)
t of
Maybe (String -> token)
Nothing -> forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ [token]
before forall a. [a] -> [a] -> [a]
++ [token]
after
Just String -> token
tk -> forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ [token]
before forall a. [a] -> [a] -> [a]
++ String -> token
tk String
matchedText forall a. a -> [a] -> [a]
: [token]
after
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
=~ String
regex :: (String, String, String)
(Int
afterRow, Int
afterCol) = Int -> Int -> String -> (Int, Int)
getLastCharPos Int
row Int
col (String
beforeProgram forall a. [a] -> [a] -> [a]
++ String
matchedText)
parsedBefore :: Either LexException [token]
parsedBefore = forall token. Int -> Int -> [InternalToken token] -> Lexer token
lexInternal Int
row Int
col [InternalToken token]
grammar String
beforeProgram
parsedAfter :: Either LexException [token]
parsedAfter = forall token. Int -> Int -> [InternalToken token] -> Lexer token
lexInternal Int
afterRow Int
afterCol ((String
regex, Maybe (String -> token)
t)forall a. a -> [a] -> [a]
:[InternalToken token]
grammar) String
afterProgram
lexInternal Int
row Int
col [InternalToken token]
_ String
invalidString = forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ Int -> Int -> String -> LexException
LexException 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