summaryrefslogtreecommitdiff
path: root/source
diff options
context:
space:
mode:
Diffstat (limited to 'source')
-rw-r--r--source/Api.hs2
-rw-r--r--source/Syntax/Adapt.hs12
-rw-r--r--source/Syntax/Concrete/Keywords.hs4
-rw-r--r--source/Syntax/Token.hs60
4 files changed, 48 insertions, 30 deletions
diff --git a/source/Api.hs b/source/Api.hs
index 421a8eb..95d5c8c 100644
--- a/source/Api.hs
+++ b/source/Api.hs
@@ -94,7 +94,7 @@ findAndReadFile path = do
homeDir <- getHomeDirectory
currentDir <- getCurrentDirectory
userLib <- (?? (homeDir </> "formalizations")) <$> lookupEnv "NAPROCHE_LIB"
- srcLib <- (?? (homeDir </> "code/zf/library")) <$> lookupEnv "NAPROCHE_SCR_LIB"
+ srcLib <- (?? (homeDir </> "code/naproche-zf/library")) <$> lookupEnv "NAPROCHE_SCR_LIB"
existsCurrent <- doesFileExist (currentDir </> path)
existsUserLib <- doesFileExist (userLib </> path)
diff --git a/source/Syntax/Adapt.hs b/source/Syntax/Adapt.hs
index b1237d2..3a8b3d6 100644
--- a/source/Syntax/Adapt.hs
+++ b/source/Syntax/Adapt.hs
@@ -26,10 +26,14 @@ scanChunk ltoks =
let toks = unLocated <$> ltoks
matchOrErr re env pos = match re toks ?? error ("could not find lexical pattern in " <> env <> " at " <> sourcePosPretty pos)
in case ltoks of
- Located pos (BeginEnv "definition") : _ -> matchOrErr definition "definition" pos
- Located pos (BeginEnv "abbreviation") : _ -> matchOrErr abbreviation "abbreviation" pos
- Located pos (BeginEnv "struct") :_ -> matchOrErr struct "struct definition" pos
- Located pos (BeginEnv "inductive") :_ -> matchOrErr inductive "inductive definition" pos
+ Located{startPos = pos, unLocated = BeginEnv "definition"} : _ ->
+ matchOrErr definition "definition" (pos)
+ Located{startPos = pos, unLocated = BeginEnv "abbreviation"} : _ ->
+ matchOrErr abbreviation "abbreviation" pos
+ Located{startPos = pos, unLocated = (BeginEnv "struct")} :_ ->
+ matchOrErr struct "struct definition" pos
+ Located{startPos = pos, unLocated = (BeginEnv "inductive")} :_ ->
+ matchOrErr inductive "inductive definition" pos
_ -> []
adaptChunks :: [[Located Token]] -> Lexicon -> Lexicon
diff --git a/source/Syntax/Concrete/Keywords.hs b/source/Syntax/Concrete/Keywords.hs
index e0f577e..135cdac 100644
--- a/source/Syntax/Concrete/Keywords.hs
+++ b/source/Syntax/Concrete/Keywords.hs
@@ -203,7 +203,7 @@ _haveIntro = _thus <|> _particularly <|> _have
_colon :: Prod r Text (Located Token) SourcePos
_colon = symbol ":" ? ":"
_pipe :: Prod r Text (Located Token) SourcePos
-_pipe = symbol "|" <|> command "mid" ? "\\mid"
+_pipe = (optional (command "middle") *> symbol "|") <|> command "mid" ? "\\mid"
_comma :: Prod r Text (Located Token) SourcePos
_comma = symbol "," ? ","
_commaAnd :: Prod r Text (Located Token) SourcePos
@@ -219,4 +219,4 @@ _eq = symbol "=" ? "="
_in :: Prod r Text (Located Token) SourcePos
_in = symbol "∈" <|> command "in" ? "\\in"
_subseteq :: Prod r Text (Located Token) SourcePos
-_subseteq = command "subseteq" ? ":"
+_subseteq = command "subseteq" ? "\\subseteq"
diff --git a/source/Syntax/Token.hs b/source/Syntax/Token.hs
index 1d13693..cb3f4cb 100644
--- a/source/Syntax/Token.hs
+++ b/source/Syntax/Token.hs
@@ -164,8 +164,17 @@ instance Pretty Token where
data Located a = Located
{ startPos :: !SourcePos
, unLocated :: !a
+ , postWhitespace :: Whitespace
} deriving (Show)
+data Whitespace = NoSpace | Space deriving (Show)
+
+collapseWhitespace :: [Whitespace] -> Whitespace
+collapseWhitespace = \case
+ Space : _ -> Space
+ NoSpace : ws -> collapseWhitespace ws
+ [] -> NoSpace
+
instance Eq a => Eq (Located a) where (==) = (==) `on` unLocated
instance Ord a => Ord (Located a) where compare = compare `on` unLocated
@@ -178,32 +187,32 @@ toks = whitespace *> goNormal id <* eof
r <- optional tok
case r of
Nothing -> pure (f [])
- Just t@(Located _ (BeginEnv "math")) -> goMath (f . (t:))
- Just t@(Located _ (BeginEnv "align*")) -> goMath (f . (t:))
+ Just t@Located{unLocated = BeginEnv "math"} -> goMath (f . (t:))
+ Just t@Located{unLocated = BeginEnv "align*"} -> goMath (f . (t:))
Just t -> goNormal (f . (t:))
goText f = do
r <- optional textToken
case r of
Nothing -> pure (f [])
- Just t@(Located _ (BeginEnv "math")) -> goMathInText (f . (t:))
- Just t@(Located _ (EndEnv "text")) -> goMath (f . (t:))
- Just t@(Located _ (EndEnv "explanation")) -> goMath (f . (t:))
+ Just t@Located{unLocated = BeginEnv "math"} -> goMathInText (f . (t:))
+ Just t@Located{unLocated = EndEnv "text"} -> goMath (f . (t:))
+ Just t@Located{unLocated = EndEnv "explanation"} -> goMath (f . (t:))
Just t -> goText (f . (t:))
goMath f = do
r <- optional mathToken
case r of
Nothing -> pure (f [])
- Just t@(Located _ (EndEnv "math")) -> goNormal (f . (t:))
- Just t@(Located _ (EndEnv "align*")) -> goNormal (f . (t:))
- Just t@(Located _ (BeginEnv "text")) -> goText (f . (t:))
- Just t@(Located _ (BeginEnv "explanation")) -> goText (f . (t:))
+ Just t@Located{unLocated = EndEnv "math"} -> goNormal (f . (t:))
+ Just t@Located{unLocated = EndEnv "align*"} -> goNormal (f . (t:))
+ Just t@Located{unLocated = BeginEnv "text"} -> goText (f . (t:))
+ Just t@Located{unLocated = BeginEnv "explanation"} -> goText (f . (t:))
Just t -> goMath (f . (t:))
goMathInText f = do
r <- optional mathToken
case r of
Nothing -> pure (f [])
- Just t@(Located _ (EndEnv "math")) -> goText (f . (t:))
- Just t@(Located _ (BeginEnv "text")) -> goText (f . (t:))
+ Just t@(Located{unLocated = EndEnv "math"}) -> goText (f . (t:))
+ Just t@(Located{unLocated = BeginEnv "text"}) -> goText (f . (t:))
Just t -> goMathInText (f . (t:))
{-# INLINE toks #-}
@@ -219,7 +228,7 @@ mathToken =
beginText :: Lexer (Located Token)
beginText = lexeme do
- Char.string "\\text{"
+ Char.string "\\text{" <|> Char.string "\\textbox{"
setTextMode
pure (BeginEnv "text")
@@ -240,14 +249,14 @@ textToken = word <|> symbol <|> begin <|> end <|> textEnd <|> mathBegin <|> alig
setMathMode
pure (EndEnv "text")
- opening' = lexeme (brace <|> group <|> paren <|> bracket)
+ opening' = lexeme (group <|> optional (Char.string "\\left") *> (brace <|> paren <|> bracket))
where
brace = VisibleBraceL <$ lexeme (Char.string "\\{")
group = InvisibleBraceL <$ lexeme (Char.char '{') <* modify' incrNesting
paren = ParenL <$ lexeme (Char.char '(')
bracket = BracketL <$ lexeme (Char.char '[')
- closing' = lexeme (brace <|> group <|> paren <|> bracket)
+ closing' = lexeme (group <|> optional (Char.string "\\right") *> (brace <|> paren <|> bracket))
where
brace = VisibleBraceR <$ lexeme (Char.string "\\}")
group = InvisibleBraceR <$ lexeme (Char.char '}') <* modify' decrNesting
@@ -408,7 +417,7 @@ end = lexeme do
-- | Parses an opening delimiter.
opening :: Lexer (Located Token)
-opening = lexeme (paren <|> brace <|> group <|> bracket)
+opening = lexeme (group <|> optional (Char.string "\\left") *> (paren <|> brace <|> bracket))
where
brace = VisibleBraceL <$ lexeme (Char.string "\\{")
group = InvisibleBraceL <$ lexeme (Char.char '{')
@@ -417,7 +426,7 @@ opening = lexeme (paren <|> brace <|> group <|> bracket)
-- | Parses a closing delimiter.
closing :: Lexer (Located Token)
-closing = lexeme (paren <|> brace <|> group <|> bracket)
+closing = lexeme (group <|> optional (Char.string "\\right") *> (paren <|> brace <|> bracket))
where
brace = VisibleBraceR <$ lexeme (Char.string "\\}")
group = InvisibleBraceR <$ lexeme (Char.char '}')
@@ -430,12 +439,17 @@ lexeme :: Lexer a -> Lexer (Located a)
lexeme p = do
start <- getSourcePos
t <- p
- whitespace
- pure (Located start t)
+ w <- whitespace
+ pure (Located start t w)
-space :: Lexer ()
-space = void (Char.char ' ' <|> Char.char '\n' <|> Char.char '\r')
- <|> void (Char.string "\\ " <|> Char.string "\\\\" <|> Char.string "\\!" <|> Char.string "\\," <|> Char.string "\\:" <|> Char.string "\\;" <|> Char.string "\\;")
+space :: Lexer Whitespace
+space = Space <$ (Char.char ' ' <|> Char.char '\n' <|> Char.char '\r')
+ <|> Space <$ (Char.string "\\ " <|> Char.string "\\\\" <|> Char.string "\\!" <|> Char.string "\\," <|> Char.string "\\:" <|> Char.string "\\;" <|> Char.string "\\;")
-whitespace :: Lexer ()
-whitespace = Lexer.space (void (some space)) (Lexer.skipLineComment "%") empty
+whitespace :: Lexer Whitespace
+whitespace = do
+ ws <- many (spaces <|> comment)
+ pure (collapseWhitespace ws)
+ where
+ spaces = collapseWhitespace <$> some space
+ comment = NoSpace <$ Lexer.skipLineComment "%"