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.
> {-# LANGUAGE OverloadedStrings #-}
> {-# LANGUAGE LambdaCase #-}
> module Main where
>
> import Control.Monad.IO.Class (liftIO)

View File

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

View File

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