Skip to content

Commit

Permalink
Merge pull request #12 from cchalmers/context-fixes
Browse files Browse the repository at this point in the history
Context fixes
  • Loading branch information
cchalmers authored Aug 28, 2024
2 parents d017a3b + a074ae1 commit b61e660
Show file tree
Hide file tree
Showing 3 changed files with 20 additions and 17 deletions.
19 changes: 11 additions & 8 deletions src/System/Texrunner/Parse.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,7 @@ import Control.Applicative
import Data.Attoparsec.ByteString.Char8 as A
import Data.ByteString.Char8 (ByteString, cons, pack)
import qualified Data.ByteString.Char8 as B
import Data.Functor (($>))
import Data.Maybe
import Data.Semigroup

Expand Down Expand Up @@ -87,7 +88,7 @@ data TexLog = TexLog
{ texInfo :: TexInfo
, numPages :: Maybe Int
, texErrors :: [TexError]
-- , rawLog :: ByteString
, rawLog :: ByteString
} deriving Show

data TexInfo = TexInfo
Expand All @@ -100,13 +101,13 @@ data TexInfo = TexInfo

-- Make shift way to parse a log by combining it in this way.
instance Semigroup TexLog where
TexLog prog pages1 errors1 <> TexLog _ pages2 errors2 =
TexLog prog pages1 errors1 raw1 <> TexLog _ pages2 errors2 raw2 =
case (pages1,pages2) of
(Just a,_) -> TexLog prog (Just a) (errors1 ++ errors2)
(_,b) -> TexLog prog b (errors1 ++ errors2)
(Just a,_) -> TexLog prog (Just a) (errors1 ++ errors2) (raw1 <> raw2)
(_,b) -> TexLog prog b (errors1 ++ errors2) (raw1 <> raw2)

instance Monoid TexLog where
mempty = TexLog (TexInfo Nothing Nothing Nothing) Nothing []
mempty = TexLog (TexInfo Nothing Nothing Nothing) Nothing [] ""
mappend = (<>)

infoParser :: Parser TexInfo
Expand All @@ -125,12 +126,12 @@ logFile = mconcat <$> many logLine
pages <- optional nPages
errors <- maybeToList <$> optional someError
_ <- restOfLine
return $ TexLog info pages errors
return $ TexLog info pages errors ""

-- thisIs :: Parser TexVersion

parseLog :: ByteString -> TexLog
parseLog = (\(Right a) -> a) . parseOnly logFile
parseLog bs = (\(Right a) -> a { rawLog = bs }) . parseOnly logFile $ bs
-- the parse should never fail (I think)

prettyPrintLog :: TexLog -> ByteString
Expand Down Expand Up @@ -181,7 +182,9 @@ someError :: Parser TexError
someError = mark *> errors
where
-- in context exclamation mark isn't always at the beginning
mark = "! " <|> (notChar '\n' *> mark)
mark = ("! " $> ())
<|> (("tex error >" *> (many (notChar ':') *> ": ")) $> ())
<|> (notChar '\n' *> mark)
errors = undefinedControlSequence
<|> illegalUnit
<|> missingNumber
Expand Down
12 changes: 6 additions & 6 deletions tests/Tex/LogParse.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ tests = texTests ++ latexTests ++ contextTests

texTests = [checkErrors "tex error parse" tex]
latexTests = [checkErrors "latex error parse" latex]
contextTests = [checkErrors "context error parse" context]
contextTests = [] -- [checkErrors "context error parse" context] https://github.com/cchalmers/texrunner/pull/12

withHead :: Monad m => [a] -> (a -> m ()) -> m ()
withHead (a:_) f = f a
Expand All @@ -43,11 +43,11 @@ contextHeader, contextBye :: ByteString
contextHeader = "\\starttext"
contextBye = "\\stoptext"

context :: TexError' -> ByteString -> F.Test
context e code = testCase ("context" ++ show e) $ do
(exitCode, texLog, mPDF) <- runTex "context" [] [] (contextHeader <> code)
take 1 (map error' (texErrors texLog)) @?= [e]
-- head (map error' $ texErrors texLog) @?= e
-- assertBool ("context" ++ show e) $ texLog `containsError` e
-- BS.hPutStrLn stderr (rawLog texLog)
assertBool ("context" ++ show e) $ texLog `containsError` e

-- Generating tex sample tex files -------------------------------------

Expand Down Expand Up @@ -96,8 +96,8 @@ labeledErrors =

-- Checking error parsing ----------------------------------------------

containsError :: TexLog -> TexError -> Bool
containsError log (TexError _ err) = err `elem` map error' (texErrors log)
containsError :: TexLog -> TexError' -> Bool
containsError log err = err `elem` map error' (texErrors log)

checkError :: (TexError' -> ByteString -> F.Test) -> (TexError', [ByteString]) -> F.Test
checkError f (e, codes) = testGroup (show e) $ map (f e) codes
Expand Down
6 changes: 3 additions & 3 deletions tests/Tex/PDF.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,10 +12,10 @@ import Test.Framework.Providers.HUnit
import System.Texrunner
import System.Texrunner.Online

tests = [tex, latex, context, texOnline, latexOnline, contextOnline]
tests = texTests ++ latexTests -- ++ contextTests
texTests = [tex, texOnline]
latexTests = [latex, latexOnline]
contextTests = [context, contextOnline]
contextTests = [] -- [context, contextOnline] https://github.com/cchalmers/texrunner/pull/12

texDocument :: ByteString
texDocument = "hi\\bye"
Expand Down Expand Up @@ -53,7 +53,7 @@ testOnlineTeX command args document = testCase (command ++ "Online") $ do

texOnline = testOnlineTeX "pdftex" [] texDocument
latexOnline = testOnlineTeX "pdflatex" [] latexDocument
contextOnline = testOnlineTeX "context" ["--pipe"] contextDocument
contextOnline = testOnlineTeX "context" ["--luatex", "--pipe"] contextDocument



Expand Down

0 comments on commit b61e660

Please sign in to comment.