{-# OPTIONS_GHC -Wall -fno-warn-orphans #-}
{-# LANGUAGE FlexibleInstances #-}
module ToySolver.FileFormat
( module ToySolver.FileFormat.Base
, WithFastParser (..)
) where
import qualified Data.PseudoBoolean as PBFile
import qualified Data.PseudoBoolean.Attoparsec as PBFileAttoparsec
import qualified Data.PseudoBoolean.Megaparsec as PBFileMegaparsec
import qualified Data.PseudoBoolean.ByteStringBuilder as PBFileBB
import ToySolver.FileFormat.Base
import ToySolver.FileFormat.CNF ()
import ToySolver.QUBO ()
import Text.Megaparsec.Error (errorBundlePretty)
instance FileFormat PBFile.Formula where
parse :: ByteString -> Either String Formula
parse ByteString
s =
case String -> ByteString -> Either ParseError Formula
PBFileMegaparsec.parseOPBByteString String
"-" ByteString
s of
Left ParseError
err -> String -> Either String Formula
forall a b. a -> Either a b
Left (ParseError -> String
forall s e.
(VisualStream s, TraversableStream s, ShowErrorComponent e) =>
ParseErrorBundle s e -> String
errorBundlePretty ParseError
err)
Right Formula
x -> Formula -> Either String Formula
forall a b. b -> Either a b
Right Formula
x
render :: Formula -> Builder
render Formula
x = Formula -> Builder
PBFileBB.opbBuilder Formula
x
instance FileFormat PBFile.SoftFormula where
parse :: ByteString -> Either String SoftFormula
parse ByteString
s =
case String -> ByteString -> Either ParseError SoftFormula
PBFileMegaparsec.parseWBOByteString String
"-" ByteString
s of
Left ParseError
err -> String -> Either String SoftFormula
forall a b. a -> Either a b
Left (ParseError -> String
forall s e.
(VisualStream s, TraversableStream s, ShowErrorComponent e) =>
ParseErrorBundle s e -> String
errorBundlePretty ParseError
err)
Right SoftFormula
x -> SoftFormula -> Either String SoftFormula
forall a b. b -> Either a b
Right SoftFormula
x
render :: SoftFormula -> Builder
render SoftFormula
x = SoftFormula -> Builder
PBFileBB.wboBuilder SoftFormula
x
newtype WithFastParser a
= WithFastParser
{ forall a. WithFastParser a -> a
unWithFastParser :: a
}
instance FileFormat (WithFastParser PBFile.Formula) where
parse :: ByteString -> Either String (WithFastParser Formula)
parse = (Formula -> WithFastParser Formula)
-> Either String Formula -> Either String (WithFastParser Formula)
forall a b. (a -> b) -> Either String a -> Either String b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Formula -> WithFastParser Formula
forall a. a -> WithFastParser a
WithFastParser (Either String Formula -> Either String (WithFastParser Formula))
-> (ByteString -> Either String Formula)
-> ByteString
-> Either String (WithFastParser Formula)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either String Formula
PBFileAttoparsec.parseOPBByteString
render :: WithFastParser Formula -> Builder
render (WithFastParser Formula
x) = Formula -> Builder
PBFileBB.opbBuilder Formula
x
instance FileFormat (WithFastParser PBFile.SoftFormula) where
parse :: ByteString -> Either String (WithFastParser SoftFormula)
parse = (SoftFormula -> WithFastParser SoftFormula)
-> Either String SoftFormula
-> Either String (WithFastParser SoftFormula)
forall a b. (a -> b) -> Either String a -> Either String b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SoftFormula -> WithFastParser SoftFormula
forall a. a -> WithFastParser a
WithFastParser (Either String SoftFormula
-> Either String (WithFastParser SoftFormula))
-> (ByteString -> Either String SoftFormula)
-> ByteString
-> Either String (WithFastParser SoftFormula)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either String SoftFormula
PBFileAttoparsec.parseWBOByteString
render :: WithFastParser SoftFormula -> Builder
render (WithFastParser SoftFormula
x) = SoftFormula -> Builder
PBFileBB.wboBuilder SoftFormula
x