{-# OPTIONS_GHC -Wall -fno-warn-orphans #-}
{-# LANGUAGE FlexibleInstances #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  ToySolver.FileFormat
-- Copyright   :  (c) Masahiro Sakai 2018
-- License     :  BSD-style
--
-- Maintainer  :  masahiro.sakai@gmail.com
-- Stability   :  provisional
-- Portability :  non-portable
--
-----------------------------------------------------------------------------
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 () -- importing instances
import ToySolver.QUBO () -- importing instances
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 -> forall a b. a -> Either a b
Left (forall s e.
(VisualStream s, TraversableStream s, ShowErrorComponent e) =>
ParseErrorBundle s e -> String
errorBundlePretty ParseError
err)
      Right Formula
x -> 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 -> forall a b. a -> Either a b
Left (forall s e.
(VisualStream s, TraversableStream s, ShowErrorComponent e) =>
ParseErrorBundle s e -> String
errorBundlePretty ParseError
err)
      Right SoftFormula
x -> forall a b. b -> Either a b
Right SoftFormula
x
  render :: SoftFormula -> Builder
render SoftFormula
x = SoftFormula -> Builder
PBFileBB.wboBuilder SoftFormula
x

-- | Wrapper type for parsing opb/wbo files using attoparsec-based parser instead of megaparsec-based one.
newtype WithFastParser a
  = WithFastParser
  { forall a. WithFastParser a -> a
unWithFastParser :: a
  }

instance FileFormat (WithFastParser PBFile.Formula) where
  parse :: ByteString -> Either String (WithFastParser Formula)
parse = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> WithFastParser a
WithFastParser 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 = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> WithFastParser a
WithFastParser 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