Reduce dependency requirements to what is in sid (#939)

This make it easier to build the package on debian unstable, which is
the first step towards an official package.
This commit is contained in:
Stephen Paul Weber 2019-05-05 09:54:14 -05:00 committed by Gabriel Gonzalez
parent a929d4e0bb
commit 2fc7f79959
4 changed files with 56 additions and 8 deletions

View File

@ -402,7 +402,7 @@ Library
filepath >= 1.4 && < 1.5 ,
haskeline >= 0.7.2.1 && < 0.8 ,
lens-family-core >= 1.0.0 && < 1.3 ,
megaparsec >= 7.0.0 && < 7.1 ,
megaparsec >= 6.5.0 && < 7.1 ,
memory >= 0.14 && < 0.15,
mtl >= 2.2.1 && < 2.3 ,
optparse-applicative >= 0.14.0.0 && < 0.15,
@ -415,7 +415,7 @@ Library
template-haskell < 2.15,
text >= 0.11.1.0 && < 1.3 ,
transformers >= 0.2.0.0 && < 0.6 ,
transformers-compat >= 0.6.4 && < 0.7 ,
transformers-compat >= 0.6.2 && < 0.7 ,
unordered-containers >= 0.1.3.0 && < 0.3 ,
uri-encode < 1.6 ,
vector >= 0.11.0.0 && < 0.13

View File

@ -1,4 +1,5 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
-- | This module contains Dhall's parsing logic
@ -42,13 +43,21 @@ exprA = completeExpression
-- | A parsing error
data ParseError = ParseError
#if MIN_VERSION_megaparsec(7, 0, 0)
{ unwrap :: Text.Megaparsec.ParseErrorBundle Text Void
#else
{ unwrap :: Text.Megaparsec.ParseError Char Void
#endif
, input :: Text
}
instance Show ParseError where
show (ParseError {..}) =
#if MIN_VERSION_megaparsec(7, 0, 0)
"\n\ESC[1;31mError\ESC[0m: Invalid input\n\n" <> Text.Megaparsec.errorBundlePretty unwrap
#else
"\n\ESC[1;31mError\ESC[0m: Invalid input\n\n" <> Text.Megaparsec.parseErrorPretty unwrap
#endif
instance Exception ParseError

View File

@ -34,6 +34,9 @@ import qualified Dhall.Pretty
import qualified Dhall.Util
import qualified Dhall.Set
import qualified Text.Megaparsec
#if !MIN_VERSION_megaparsec(7, 0, 0)
import qualified Text.Megaparsec.Char as Text.Megaparsec (satisfy)
#endif
import qualified Text.Megaparsec.Char
import qualified Text.Parser.Char
import qualified Text.Parser.Combinators
@ -233,7 +236,11 @@ instance Text.Parser.Char.CharParsing Parser where
notChar = Text.Megaparsec.Char.char
#if MIN_VERSION_megaparsec(7, 0, 0)
anyChar = Text.Megaparsec.anySingle
#else
anyChar = Text.Megaparsec.Char.anyChar
#endif
string = fmap Data.Text.unpack . Text.Megaparsec.Char.string . fromString

View File

@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedLists #-}
@ -27,16 +28,47 @@ import qualified Data.Sequence
import qualified Data.Text
import qualified Data.Text.Encoding
import qualified Text.Megaparsec
#if !MIN_VERSION_megaparsec(7, 0, 0)
import qualified Text.Megaparsec.Char as Text.Megaparsec
#endif
import qualified Text.Parser.Char
import Dhall.Parser.Combinators
import Dhall.Parser.Token
getSourcePos :: Text.Megaparsec.MonadParsec e s m =>
m Text.Megaparsec.SourcePos
getSourcePos =
#if MIN_VERSION_megaparsec(7, 0, 0)
Text.Megaparsec.getSourcePos
#else
Text.Megaparsec.getPosition
#endif
{-# INLINE getSourcePos #-}
getOffset :: Text.Megaparsec.MonadParsec e s m => m Int
#if MIN_VERSION_megaparsec(7, 0, 0)
getOffset = Text.Megaparsec.stateOffset <$> Text.Megaparsec.getParserState
#else
getOffset = Text.Megaparsec.stateTokensProcessed <$> Text.Megaparsec.getParserState
#endif
{-# INLINE getOffset #-}
setOffset :: Text.Megaparsec.MonadParsec e s m => Int -> m ()
#if MIN_VERSION_megaparsec(7, 0, 0)
setOffset o = Text.Megaparsec.updateParserState $ \(Text.Megaparsec.State s _ pst) ->
Text.Megaparsec.State s o pst
#else
setOffset o = Text.Megaparsec.updateParserState $ \(Text.Megaparsec.State s p _ stw) ->
Text.Megaparsec.State s p o stw
#endif
{-# INLINE setOffset #-}
noted :: Parser (Expr Src a) -> Parser (Expr Src a)
noted parser = do
before <- Text.Megaparsec.getSourcePos
before <- getSourcePos
(tokens, e) <- Text.Megaparsec.match parser
after <- Text.Megaparsec.getSourcePos
after <- getSourcePos
let src = Src before after tokens
case e of
Note src _ | laxSrcEq src src -> return e
@ -240,10 +272,10 @@ completeExpression embedded = completeExpression_
<|> alternative38
where
alternative00 = do
n <- Text.Megaparsec.getOffset
n <- getOffset
a <- try doubleLiteral
b <- if isInfinite a
then Text.Megaparsec.setOffset n *> fail "double out of bounds"
then setOffset n *> fail "double out of bounds"
else return a
return (DoubleLit b)
@ -390,7 +422,7 @@ completeExpression embedded = completeExpression_
) && c /= '$'
unescapedCharacterSlow = do
_ <- Text.Megaparsec.single '$'
_ <- Text.Parser.Char.char '$'
return (Chunks [] "$")
escapedCharacter = do