module Data.Makefile.Parse.Internal where
import Control.Applicative ((<|>))
import Control.Monad (void)
import Data.Attoparsec.ByteString
import Data.Makefile
import qualified Data.Attoparsec.ByteString.Char8 as Atto
import qualified Data.ByteString as B
parseMakefile :: IO (Either String Makefile)
parseMakefile = Atto.parseOnly makefile <$> B.readFile "Makefile"
parseAsMakefile :: FilePath -> IO (Either String Makefile)
parseAsMakefile f = Atto.parseOnly makefile <$> B.readFile f
makefile :: Parser Makefile
makefile = Makefile <$> many' entry
entry :: Parser Entry
entry = do
void $ many' emptyLine
assignment <|> rule
assignment :: Parser Entry
assignment = do v1 <- lazyVar <|> immVar
v2 <- toLineEnd1
return $ Assignment v1 v2
rule :: Parser Entry
rule = do t <- target
ds <- many' dependency
nextLine
cs <- many' command
return $ Rule t ds cs
command :: Parser Command
command = do _ <- many' emptyLine
_ <- Atto.char8 '\t'
c <- Command <$> toLineEnd1
nextLine
return c
target :: Parser Target
target = do t <- Target <$> Atto.takeWhile (/= ':')
_ <- Atto.char8 ':'
return t
dependency :: Parser Dependency
dependency = Atto.takeWhile isSpaceChar
>> Dependency <$> Atto.takeWhile1 (`notElem` [' ', '\n', '#'])
lazyVar :: Parser B.ByteString
lazyVar = do
v1 <- Atto.takeWhile1 (`notElem` ['=', '\n', '#'])
_ <- Atto.char8 '='
return v1
immVar :: Parser B.ByteString
immVar = do
v1 <- Atto.takeWhile1 (`notElem` [':', '\n', '#'])
_ <- Atto.string ":="
return v1
comment :: Parser B.ByteString
comment = Atto.char8 '#' >> Atto.takeWhile (/= '\n')
nextLine :: Parser ()
nextLine = void $ Atto.takeWhile (/= '\n') >> Atto.char8 '\n'
emptyLine :: Parser ()
emptyLine = Atto.takeWhile (`elem` ['\t', ' '])
>> many' comment
>> Atto.char8 '\n'
>> return ()
isSpaceChar :: Char -> Bool
isSpaceChar c = c == ' '
toLineEnd1 :: Parser B.ByteString
toLineEnd1 = Atto.takeWhile1 (`notElem` ['\n', '#'])