Skip to content

Commit

Permalink
Allow ‘megaparsec-6.4.0’
Browse files Browse the repository at this point in the history
  • Loading branch information
mrkkrp committed Dec 31, 2017
1 parent 48d3856 commit 29824d1
Show file tree
Hide file tree
Showing 4 changed files with 22 additions and 7 deletions.
4 changes: 4 additions & 0 deletions CHANGELOG.md
@@ -1,3 +1,7 @@
## Modern URI 0.1.2.1

* Allow Megaparsec 6.4.0.

## Modern URI 0.1.2.0

* Fixed handling of `+` in query strings. Now `+` is parsed as space and
Expand Down
16 changes: 10 additions & 6 deletions Text/URI/Parser/ByteString.hs
Expand Up @@ -9,17 +9,17 @@
--
-- URI parser for string 'ByteString', an internal module.

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}

module Text.URI.Parser.ByteString
( parserBs )
where

import Control.Applicative
import Control.Monad
import Control.Monad.Catch (MonadThrow (..))
import Data.ByteString (ByteString)
Expand All @@ -38,6 +38,10 @@ import qualified Data.Set as E
import qualified Data.Text.Encoding as TE
import qualified Text.Megaparsec.Byte.Lexer as L

#if !MIN_VERSION_megaparsec(6,4,0)
import Control.Applicative (empty)
#endif

-- | This parser can be used to parse 'URI' from strict 'ByteString'.
-- Remember to use a concrete non-polymorphic parser type for efficiency.
--
Expand Down
6 changes: 5 additions & 1 deletion Text/URI/Parser/Text.hs
Expand Up @@ -9,6 +9,7 @@
--
-- URI parser for strict 'Text', an internal module.

{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
Expand All @@ -20,7 +21,6 @@ module Text.URI.Parser.Text
, parser )
where

import Control.Applicative
import Control.Monad
import Control.Monad.Catch (MonadThrow (..))
import Data.Maybe (isJust, catMaybes)
Expand All @@ -35,6 +35,10 @@ import qualified Data.List.NonEmpty as NE
import qualified Data.Text.Encoding as TE
import qualified Text.Megaparsec.Char.Lexer as L

#if !MIN_VERSION_megaparsec(6,4,0)
import Control.Applicative (empty)
#endif

-- | Construct a 'URI' from 'Text'. The input you pass to 'mkURI' must be a
-- valid URI as per RFC 3986, that is, its components should be
-- percent-encoded where necessary. In case of parse failure
Expand Down
3 changes: 3 additions & 0 deletions stack.yaml
@@ -1,3 +1,6 @@
resolver: lts-10.0
packages:
- '.'
extra-deps:
- megaparsec-6.4.0
- parser-combinators-0.4.0

0 comments on commit 29824d1

Please sign in to comment.