module Distribution.Simple.PreProcess.Unlit (unlit,plain) where
import Data.Char
import Data.List
data Classified = BirdTrack String | Blank String | Ordinary String
| Line !Int String | CPP String
| BeginCode | EndCode
| Error String | Comment String
plain :: String -> String -> String
plain _ hs = hs
classify :: String -> Classified
classify ('>':s) = BirdTrack s
classify ('#':s) = case tokens s of
(line:file:_) | all isDigit line
&& length file >= 2
&& head file == '"'
&& last file == '"'
-> Line (read line) (tail (init file))
_ -> CPP s
where tokens = unfoldr $ \str -> case lex str of
(t@(_:_), str'):_ -> Just (t, str')
_ -> Nothing
classify ('\\':s)
| "begin{code}" `isPrefixOf` s = BeginCode
| "end{code}" `isPrefixOf` s = EndCode
classify s | all isSpace s = Blank s
classify s = Ordinary s
unclassify :: Bool -> Classified -> String
unclassify _ (BirdTrack s) = ' ':s
unclassify _ (Blank s) = s
unclassify _ (Ordinary s) = s
unclassify _ (Line n file) = "# " ++ show n ++ " " ++ show file
unclassify _ (CPP s) = '#':s
unclassify True (Comment "") = " --"
unclassify True (Comment s) = " -- " ++ s
unclassify False (Comment "") = "--"
unclassify False (Comment s) = "-- " ++ s
unclassify _ _ = internalError
unlit :: FilePath -> String -> Either String String
unlit file input =
let (usesBirdTracks, classified) = classifyAndCheckForBirdTracks
. inlines
$ input
in either (Left . unlines . map (unclassify usesBirdTracks))
Right
. checkErrors
. reclassify
$ classified
where
classifyAndCheckForBirdTracks =
flip mapAccumL False $ \seenBirdTrack line ->
let classification = classify line
in (seenBirdTrack || isBirdTrack classification, classification)
isBirdTrack (BirdTrack _) = True
isBirdTrack _ = False
checkErrors ls = case [ e | Error e <- ls ] of
[] -> Left ls
(message:_) -> Right (f ++ ":" ++ show n ++ ": " ++ message)
where (f, n) = errorPos file 1 ls
errorPos f n [] = (f, n)
errorPos f n (Error _:_) = (f, n)
errorPos _ _ (Line n' f':ls) = errorPos f' n' ls
errorPos f n (_ :ls) = errorPos f (n+1) ls
reclassify :: [Classified] -> [Classified]
reclassify = blank
where
latex [] = []
latex (EndCode :ls) = Blank "" : comment ls
latex (BeginCode :_ ) = [Error "\\begin{code} in code section"]
latex (BirdTrack l:ls) = Ordinary ('>':l) : latex ls
latex ( l:ls) = l : latex ls
blank [] = []
blank (EndCode :_ ) = [Error "\\end{code} without \\begin{code}"]
blank (BeginCode :ls) = Blank "" : latex ls
blank (BirdTrack l:ls) = BirdTrack l : bird ls
blank (Ordinary l:ls) = Comment l : comment ls
blank ( l:ls) = l : blank ls
bird [] = []
bird (EndCode :_ ) = [Error "\\end{code} without \\begin{code}"]
bird (BeginCode :ls) = Blank "" : latex ls
bird (Blank l :ls) = Blank l : blank ls
bird (Ordinary _:_ ) = [Error "program line before comment line"]
bird ( l:ls) = l : bird ls
comment [] = []
comment (EndCode :_ ) = [Error "\\end{code} without \\begin{code}"]
comment (BeginCode :ls) = Blank "" : latex ls
comment (CPP l :ls) = CPP l : comment ls
comment (BirdTrack _:_ ) = [Error "comment line before program line"]
comment (Blank l:ls@(Ordinary _:_)) = Comment l : comment ls
comment (Blank l:ls) = Blank l : blank ls
comment (Line n f :ls) = Line n f : comment ls
comment (Ordinary l:ls) = Comment l : comment ls
comment (Comment _: _) = internalError
comment (Error _: _) = internalError
inlines :: String -> [String]
inlines xs = lines' xs id
where
lines' [] acc = [acc []]
lines' ('\^M':'\n':s) acc = acc [] : lines' s id
lines' ('\^M':s) acc = acc [] : lines' s id
lines' ('\n':s) acc = acc [] : lines' s id
lines' (c:s) acc = lines' s (acc . (c:))
internalError :: a
internalError = error "unlit: internal error"