Replace Parser.manyNE with NonEmpty.some

This commit is contained in:
Eugen Wissner 2020-01-12 07:19:28 +01:00
parent dd8f312cb3
commit 6d951491be
4 changed files with 5 additions and 8 deletions

View File

@ -12,7 +12,6 @@ We have written a small tutorial to help you (and ourselves) understand the grap
Since this file is a literate haskell file, we start by importing some dependencies. Since this file is a literate haskell file, we start by importing some dependencies.
> {-# LANGUAGE OverloadedStrings #-} > {-# LANGUAGE OverloadedStrings #-}
> {-# LANGUAGE LambdaCase #-}
> module Main where > module Main where
> >
> import Control.Monad.IO.Class (liftIO) > import Control.Monad.IO.Class (liftIO)

View File

@ -30,6 +30,7 @@ dependencies:
- base >= 4.7 && < 5 - base >= 4.7 && < 5
- containers - containers
- megaparsec - megaparsec
- parser-combinators
- text - text
- transformers - transformers
- unordered-containers - unordered-containers

View File

@ -7,7 +7,7 @@ module Language.GraphQL.AST.Parser
) where ) where
import Control.Applicative (Alternative(..), optional) import Control.Applicative (Alternative(..), optional)
import Data.List.NonEmpty (NonEmpty(..)) import qualified Control.Applicative.Combinators.NonEmpty as NonEmpty
import Language.GraphQL.AST import Language.GraphQL.AST
import qualified Language.GraphQL.AST.Document as Document import qualified Language.GraphQL.AST.Document as Document
import Language.GraphQL.AST.Lexer import Language.GraphQL.AST.Lexer
@ -17,7 +17,7 @@ import Text.Megaparsec (lookAhead, option, try, (<?>))
document :: Parser Document.Document document :: Parser Document.Document
document = unicodeBOM document = unicodeBOM
>> spaceConsumer >> spaceConsumer
>> lexeme (manyNE $ Document.ExecutableDefinition <$> definition) >> lexeme (NonEmpty.some $ Document.ExecutableDefinition <$> definition)
definition :: Parser ExecutableDefinition definition :: Parser ExecutableDefinition
definition = DefinitionOperation <$> operationDefinition definition = DefinitionOperation <$> operationDefinition
@ -44,7 +44,7 @@ operationType = Query <$ symbol "query"
-- * SelectionSet -- * SelectionSet
selectionSet :: Parser SelectionSet selectionSet :: Parser SelectionSet
selectionSet = braces $ manyNE selection selectionSet = braces $ NonEmpty.some selection
selectionSetOpt :: Parser SelectionSetOpt selectionSetOpt :: Parser SelectionSetOpt
selectionSetOpt = braces $ some selection selectionSetOpt = braces $ some selection
@ -186,6 +186,3 @@ but :: Parser a -> Parser ()
but pn = False <$ lookAhead pn <|> pure True >>= \case but pn = False <$ lookAhead pn <|> pure True >>= \case
False -> empty False -> empty
True -> pure () True -> pure ()
manyNE :: Alternative f => f a -> f (NonEmpty a)
manyNE p = (:|) <$> p <*> many p

View File

@ -1,4 +1,4 @@
resolver: lts-14.19 resolver: lts-14.20
packages: packages:
- . - .