module Language.CNF.Parse.ParseDIMACS
( parseByteString
, parseFile
, CNF(..)
, Clause )
where
import Control.Monad
import Data.Array.Unboxed
import Data.ByteString.Lazy( ByteString )
import Prelude hiding (readFile, map)
import Text.Parsec( ParseError, SourceName )
import Text.Parsec.ByteString.Lazy
import Text.Parsec.Char
import Text.Parsec.Combinator
import Text.Parsec.Prim( many, try, unexpected, runParser )
import qualified Text.Parsec.Token as T
data CNF = CNF
{ numVars :: !Int
, numClauses :: !Int
, clauses :: ![Clause] } deriving Show
type Clause = UArray Int Int
parseFile :: FilePath -> IO (Either ParseError CNF)
parseFile = parseFromFile cnf
parseByteString :: SourceName -> ByteString -> Either ParseError CNF
parseByteString = runParser cnf ()
cnf :: Parser CNF
cnf = uncurry CNF `fmap` cnfHeader `ap` lexeme (many clause)
cnfHeader :: Parser (Int, Int)
cnfHeader = do
whiteSpace
char 'p' >> many1 space
symbol "cnf"
(,) `fmap` natural `ap` natural
clause :: Parser (UArray Int Int)
clause = do ints <- lexeme int `manyTill` try (symbol "0")
return $ listArray (0, length ints 1) ints
tp = T.makeTokenParser $ T.LanguageDef
{ T.commentStart = ""
, T.commentEnd = ""
, T.commentLine = "c"
, T.nestedComments = False
, T.identStart = unexpected "ParseDIMACS bug: shouldn't be parsing identifiers..."
, T.identLetter = unexpected "ParseDIMACS bug: shouldn't be parsing identifiers..."
, T.opStart = unexpected "ParseDIMACS bug: shouldn't be parsing operators..."
, T.opLetter = unexpected "ParseDIMACS bug: shouldn't be parsing operators..."
, T.reservedNames = ["p", "cnf"]
, T.reservedOpNames = []
, T.caseSensitive = True
}
natural :: Parser Int
natural = fromIntegral `fmap` T.natural tp
int :: Parser Int
int = fromIntegral `fmap` T.integer tp
symbol = T.symbol tp
whiteSpace = T.whiteSpace tp
lexeme = T.lexeme tp