Skip to content

Commit

Permalink
set the correct behaviour with the "..." construction
Browse files Browse the repository at this point in the history
  • Loading branch information
Kerl13 committed Mar 31, 2016
1 parent 2b4b743 commit ee5f5d8
Show file tree
Hide file tree
Showing 3 changed files with 28 additions and 19 deletions.
39 changes: 24 additions & 15 deletions lexer.x
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,8 @@
module Lexer where
import qualified Data.Map as M
import qualified Data.Set as S
import Data.Word
import Codec.Binary.UTF8.String (encode)
}

%wrapper "basic"
Expand Down Expand Up @@ -57,12 +59,11 @@ tokens :-
"_|_" { cst FALSUM }
"|--" { cst TURNSTILE }
"|==" { cst TTURNSTILE }
. { \s -> RAW s }

{
data Token =
RAW String
| LETTER Char
| LETTER Char | LETTERS_ String -- Temporary token
| NUM Int
| LDEL String
| RDEL String
Expand Down Expand Up @@ -152,7 +153,7 @@ check_kw s = case M.lookup s kws of
else if S.member s std_fun then
STDFUN s
else
RAW s
LETTERS_ s

sym1 = M.fromList [
("+", ADD), ("-", SUB), ("*", MUL), ("\\", BSLASH), ("/", SLASH),
Expand All @@ -161,20 +162,28 @@ sym1 = M.fromList [

check_sym1 s = case M.lookup s sym1 of
Just tok -> tok
Nothing -> RAW s
Nothing -> error ("'" ++ s ++ "' is supposed to be recognised")

alphabet = S.fromList $ ['a'..'z'] ++ ['A'..'Z']

unraw :: [Token] -> [Token]
unraw [] = []
unraw ((RAW (c:cs)):ts) =
if S.member c alphabet then
(LETTER c):(unraw ((RAW cs):ts))
else
(RAW [c]):(unraw ((RAW cs):ts))
unraw ((RAW ""):ts) = unraw ts
unraw (t:ts) = t:(unraw ts)

get_tokens = unraw . alexScanTokens
split :: String -> Either String (String, String, String)
split s = case span ((/=) '"') s of
(_, "") -> Left s
(a, _:t) ->
case span ((/=) '"') t of
(_, "") -> error "Unterminated string"
(b, _:c) -> Right (a, b, c)

get_tokens_ :: String -> [Token]
get_tokens_ s = case split s of
Left s -> alexScanTokens s
Right (prev, str, next) ->
(alexScanTokens prev) ++ [RAW str] ++ (get_tokens_ next)

get_tokens :: String -> [Token]
get_tokens = unletters . get_tokens_
where unletters [] = []
unletters ((LETTERS_ s):toks) = (map LETTER s) ++ (unletters toks)
unletters (tok:toks) = tok:(unletters toks)
}

6 changes: 3 additions & 3 deletions main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ import TeXWriter (writeTeX)
endl :: String -> String
endl = (flip (++)) "\n"

f :: String -> String
f = endl . writeTeX . parseAscii . get_tokens
run :: String -> String
run = endl . writeTeX . parseAscii . get_tokens

main = interact f
main = interact run
2 changes: 1 addition & 1 deletion texwriter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -152,7 +152,7 @@ writeSimpleExpr (BinaryApp BRoot e1 e2) =
cmdarg ("sqrt[" ++ writeSimpleExpr e1 ++ "]") $ writeSimpleExpr e2
writeSimpleExpr (BinaryApp BStackRel e1 e2) =
cmdarg2 "stackrel" (writeSimpleExpr e1) (writeSimpleExpr e2)
writeSimpleExpr (Raw s) = s
writeSimpleExpr (Raw s) = cmdarg "textrm" s

-- Writes a simple expression after removing the delimiters at the embracing
-- delimiters if present
Expand Down

0 comments on commit ee5f5d8

Please sign in to comment.