Skip to content

Commit

Permalink
Make attoparsec and parsec dependencies optional
Browse files Browse the repository at this point in the history
  • Loading branch information
typedrat committed Sep 5, 2018
1 parent bd421e5 commit 79f43b0
Show file tree
Hide file tree
Showing 6 changed files with 89 additions and 13 deletions.
25 changes: 20 additions & 5 deletions parsers.cabal
Expand Up @@ -44,6 +44,16 @@ flag binary
description:
You can disable the use of the `binary` package using `-f-binary`.

flag parsec
default: True
description:
You can disable the use of the `parsec` package using `-f-parsec`.

flag attoparsec
default: True
description:
You can disable the use of the `attoparsec` package using `-f-attoparsec`.

library
default-language: Haskell2010
exposed-modules:
Expand All @@ -68,28 +78,33 @@ library
charset >= 0.3 && < 1,
containers >= 0.4 && < 0.7,
semigroups >= 0.12 && < 1,
parsec >= 3.1 && < 3.2,
attoparsec >= 0.12.1.4 && < 0.14,
text >= 0.10 && < 1.3,
transformers >= 0.2 && < 0.6,
mtl >= 2.0.1 && < 2.3,
scientific >= 0.3 && < 0.4,
unordered-containers >= 0.2 && < 0.3

if flag(binary)
build-depends: binary >= 0.7.2 && < 1
build-depends: binary >= 0.7.2 && < 1
if flag(parsec)
build-depends: parsec >= 3.1 && < 3.2
if flag(attoparsec)
build-depends: attoparsec >= 0.12.1.4 && < 0.14

test-suite quickcheck
type: exitcode-stdio-1.0
main-is: QuickCheck.hs
default-language: Haskell2010
build-depends:
attoparsec,
base == 4.*,
bytestring,
parsec >= 3,
parsers,
QuickCheck,
quickcheck-instances
ghc-options: -Wall -threaded
hs-source-dirs: tests

if flag(parsec)
build-depends: parsec >= 3
if flag(attoparsec)
build-depends: attoparsec
12 changes: 11 additions & 1 deletion src/Text/Parser/Char.hs
Expand Up @@ -69,10 +69,16 @@ import Data.Monoid
#endif
import Data.Text
import qualified Text.ParserCombinators.ReadP as ReadP
import Text.Parser.Combinators

#ifdef MIN_VERSION_parsec
import qualified Text.Parsec as Parsec
#endif

#ifdef MIN_VERSION_attoparsec
import qualified Data.Attoparsec.Types as Att
import qualified Data.Attoparsec.Combinator as Att
import Text.Parser.Combinators
#endif

-- | @oneOf cs@ succeeds if the current character is in the supplied
-- list of characters @cs@. Returns the parsed character. See also
Expand Down Expand Up @@ -339,17 +345,21 @@ instance (CharParsing m, MonadPlus m) => CharParsing (IdentityT m) where
text = lift . text
{-# INLINE text #-}

#ifdef MIN_VERSION_parsec
instance Parsec.Stream s m Char => CharParsing (Parsec.ParsecT s u m) where
satisfy = Parsec.satisfy
char = Parsec.char
notChar c = Parsec.satisfy (/= c)
anyChar = Parsec.anyChar
string = Parsec.string
#endif

#ifdef MIN_VERSION_attoparsec
instance Att.Chunk t => CharParsing (Att.Parser t) where
satisfy p = fmap e2c $ Att.satisfyElem $ p . e2c
where e2c = Att.chunkElemToChar (undefined :: t)
{-# INLINE satisfy #-}
#endif

instance CharParsing ReadP.ReadP where
satisfy = ReadP.satisfy
Expand Down
11 changes: 11 additions & 0 deletions src/Text/Parser/Combinators.hs
Expand Up @@ -80,9 +80,16 @@ import Data.Orphans ()
#endif
import Data.Traversable (sequenceA)
#endif

#ifdef MIN_VERSION_parsec
import qualified Text.Parsec as Parsec
#endif

#ifdef MIN_VERSION_attoparsec
import qualified Data.Attoparsec.Types as Att
import qualified Data.Attoparsec.Combinator as Att
#endif

import qualified Text.ParserCombinators.ReadP as ReadP

#ifdef MIN_VERSION_binary
Expand Down Expand Up @@ -419,6 +426,7 @@ instance (Parsing m, Monad m) => Parsing (IdentityT m) where
notFollowedBy (IdentityT m) = IdentityT $ notFollowedBy m
{-# INLINE notFollowedBy #-}

#ifdef MIN_VERSION_parsec
instance (Parsec.Stream s m t, Show t) => Parsing (Parsec.ParsecT s u m) where
try = Parsec.try
(<?>) = (Parsec.<?>)
Expand All @@ -427,7 +435,9 @@ instance (Parsec.Stream s m t, Show t) => Parsing (Parsec.ParsecT s u m) where
unexpected = Parsec.unexpected
eof = Parsec.eof
notFollowedBy = Parsec.notFollowedBy
#endif

#ifdef MIN_VERSION_attoparsec
instance Att.Chunk t => Parsing (Att.Parser t) where
try = Att.try
(<?>) = (Att.<?>)
Expand All @@ -436,6 +446,7 @@ instance Att.Chunk t => Parsing (Att.Parser t) where
unexpected = fail
eof = Att.endOfInput
notFollowedBy p = optional p >>= maybe (pure ()) (unexpected . show)
#endif

#ifdef MIN_VERSION_binary
instance Parsing B.Get where
Expand Down
16 changes: 13 additions & 3 deletions src/Text/Parser/LookAhead.hs
Expand Up @@ -36,15 +36,21 @@ import Control.Monad.Trans.RWS.Lazy as Lazy
import Control.Monad.Trans.RWS.Strict as Strict
import Control.Monad.Trans.Reader
import Control.Monad.Trans.Identity
import qualified Data.Attoparsec.Types as Att
import qualified Data.Attoparsec.Combinator as Att
#if __GLASGOW_HASKELL__ < 710
import Data.Monoid
#endif
import qualified Text.ParserCombinators.ReadP as ReadP
import qualified Text.Parsec as Parsec
import Text.Parser.Combinators

#ifdef MIN_VERSION_parsec
import qualified Text.Parsec as Parsec
#endif

#ifdef MIN_VERSION_attoparsec
import qualified Data.Attoparsec.Types as Att
import qualified Data.Attoparsec.Combinator as Att
#endif

#ifdef MIN_VERSION_binary
import qualified Data.Binary.Get as B
#endif
Expand Down Expand Up @@ -86,11 +92,15 @@ instance (LookAheadParsing m, Monad m) => LookAheadParsing (IdentityT m) where
lookAhead = IdentityT . lookAhead . runIdentityT
{-# INLINE lookAhead #-}

#ifdef MIN_VERSION_parsec
instance (Parsec.Stream s m t, Show t) => LookAheadParsing (Parsec.ParsecT s u m) where
lookAhead = Parsec.lookAhead
#endif

#ifdef MIN_VERSION_attoparsec
instance Att.Chunk i => LookAheadParsing (Att.Parser i) where
lookAhead = Att.lookAhead
#endif

#ifdef MIN_VERSION_binary
instance LookAheadParsing B.Get where
Expand Down
14 changes: 12 additions & 2 deletions src/Text/Parser/Token.hs
Expand Up @@ -113,12 +113,18 @@ import Data.String
import Data.Text hiding (empty,zip,foldl',take,map,length,splitAt,null,transpose)
import Numeric (showIntAtBase)
import qualified Text.ParserCombinators.ReadP as ReadP
import qualified Text.Parsec as Parsec
import qualified Data.Attoparsec.Types as Att
import Text.Parser.Char
import Text.Parser.Combinators
import Text.Parser.Token.Highlight

#ifdef MIN_VERSION_parsec
import qualified Text.Parsec as Parsec
#endif

#ifdef MIN_VERSION_attoparsec
import qualified Data.Attoparsec.Types as Att
#endif

-- | Skip zero or more bytes worth of white space. More complex parsers are
-- free to consider comments as white space.
whiteSpace :: TokenParsing m => m ()
Expand Down Expand Up @@ -925,8 +931,12 @@ instance TokenParsing m => TokenParsing (Unlined m) where
highlight h (Unlined m) = Unlined (highlight h m)
{-# INLINE highlight #-}

#ifdef MIN_VERSION_parsec
instance Parsec.Stream s m Char => TokenParsing (Parsec.ParsecT s u m)
#endif

#ifdef MIN_VERSION_attoparsec
instance Att.Chunk t => TokenParsing (Att.Parser t)
#endif

instance TokenParsing ReadP.ReadP
24 changes: 22 additions & 2 deletions tests/QuickCheck.hs
Expand Up @@ -9,7 +9,9 @@ module Main

import Control.Applicative

#ifdef MIN_VERSION_attoparsec
import Data.Attoparsec.Text (parseOnly)
#endif
import Data.String

#if MIN_VERSION_base(4,7,0)
Expand All @@ -19,7 +21,9 @@ import Data.Either
import Test.QuickCheck
import Test.QuickCheck.Instances ()

#ifdef MIN_VERSION_parsec
import Text.Parsec.Prim as P (parse)
#endif
import Text.Parser.Char
import Text.Parser.Combinators
import Text.ParserCombinators.ReadP (readP_to_S)
Expand All @@ -38,15 +42,31 @@ data TestParser a = TestParser String (P a -> String -> Either String a)

instance Show (TestParser a) where show (TestParser n _) = n

pAtto, pParsec, pReadP :: TestParser a
#ifdef MIN_VERSION_attoparsec
pAtto :: TestParser a
pAtto = TestParser "attoparsec" $ \(P p) -> parseOnly p . fromString
#endif

#ifdef MIN_VERSION_parsec
pParsec :: TestParser a
pParsec = TestParser "parsec" $ \(P p) -> either (Left . show) Right . parse p "test input"
#endif

pReadP :: TestParser a
pReadP = TestParser "ReadP" $ \(P p) s -> case readP_to_S p s of
[] -> Left "parseFailed"
(a,_):_ -> Right a

instance Arbitrary (TestParser a) where
arbitrary = elements [pReadP, pAtto, pParsec]
arbitrary = elements ps
where
ps = [pReadP]
#ifdef MIN_VERSION_attoparsec
++ [pAtto]
#endif
#ifdef MIN_VERSION_parsec
++ [pParsec]
#endif

-- -------------------------------------------------------------------------- --
-- Main
Expand Down

0 comments on commit 79f43b0

Please sign in to comment.