Skip to content

Commit

Permalink
Documentation corrections and improvements
Browse files Browse the repository at this point in the history
  • Loading branch information
mrkkrp committed Jul 25, 2017
1 parent 7cbab7c commit a745b27
Show file tree
Hide file tree
Showing 7 changed files with 46 additions and 35 deletions.
31 changes: 16 additions & 15 deletions Text/Megaparsec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,9 +38,10 @@
--
-- Megaparsec is capable of a lot. Apart from this standard functionality
-- you can parse permutation phrases with "Text.Megaparsec.Perm",
-- expressions with "Text.Megaparsec.Expr", and even entire languages with
-- "Text.Megaparsec.Char.Lexer". These modules should be imported explicitly
-- along with the modules mentioned above.
-- expressions with "Text.Megaparsec.Expr", do lexing with
-- "Text.Megaparsec.Char.Lexer" and "Text.Megaparsec.Byte.Lexer". These
-- modules should be imported explicitly along with the modules mentioned
-- above.

{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
Expand Down Expand Up @@ -144,11 +145,11 @@ import Control.Applicative
----------------------------------------------------------------------------
-- Data types

-- | This is the Megaparsec's state, it's parametrized over stream type @s@.
-- | This is the Megaparsec's state parametrized over stream type @s@.

data State s = State
{ stateInput :: s
-- ^ Current input (already processed input is removed from the stream)
-- ^ The rest of input to process
, statePos :: NonEmpty SourcePos
-- ^ Current position (column + line number) with support for include files
, stateTokensProcessed :: {-# UNPACK #-} !Int
Expand Down Expand Up @@ -252,13 +253,13 @@ refreshLastHint (Hints (_:xs)) Nothing = Hints xs
refreshLastHint (Hints (_:xs)) (Just m) = Hints (E.singleton m : xs)
{-# INLINE refreshLastHint #-}

-- | @Parsec@ is a non-transformer variant of the more general 'ParsecT'
-- | 'Parsec' is a non-transformer variant of the more general 'ParsecT'
-- monad transformer.

type Parsec e s = ParsecT e s Identity

-- | @ParsecT e s m a@ is a parser with custom data component of error @e@,
-- stream type @s@, underlying monad @m@ and return type @a@.
-- | @'ParsecT' e s m a@ is a parser with custom data component of error
-- @e@, stream type @s@, underlying monad @m@ and return type @a@.

newtype ParsecT e s m a = ParsecT
{ unParser
Expand Down Expand Up @@ -452,7 +453,7 @@ parse = runParser
-- The function is supposed to be useful for lightweight parsing, where
-- error messages (and thus file name) are not important and entire input
-- should be parsed. For example, it can be used when parsing of a single
-- number according to specification of its format is desired.
-- number according to a specification of its format is desired.

parseMaybe :: (Ord e, Stream s) => Parsec e s a -> s -> Maybe a
parseMaybe p s =
Expand Down Expand Up @@ -577,7 +578,7 @@ initialState name s = State
-- | Type class describing monads that implement the full set of primitive
-- parsers.
--
-- Note carefully that the following primitives are “fast” and should be
-- __Note carefully__ that the following primitives are “fast” and should be
-- taken advantage of as much as possible if your aim is a fast parser:
-- 'tokens', 'takeWhileP', 'takeWhile1P', and 'takeP'.

Expand Down Expand Up @@ -641,7 +642,7 @@ class (Stream s, A.Alternative m, MonadPlus m)
-- >>> parseTest (try (string "let") <|> string "lexical") "lexical"
-- "lexical"
--
-- @try@ also improves error messages in case of overlapping alternatives,
-- 'try' also improves error messages in case of overlapping alternatives,
-- because Megaparsec's hint system can be used:
--
-- >>> parseTest (try (string "let") <|> string "lexical") "le"
Expand Down Expand Up @@ -1249,16 +1250,16 @@ infix 0 <?>
(<?>) = flip label
{-# INLINE (<?>) #-}

-- | The parser @unexpected item@ fails with an error message telling about
-- unexpected item @item@ without consuming any input.
-- | The parser @'unexpected' item@ fails with an error message telling
-- about unexpected item @item@ without consuming any input.
--
-- > unexpected item = failure (pure item) Set.empty

unexpected :: MonadParsec e s m => ErrorItem (Token s) -> m a
unexpected item = failure (pure item) E.empty
{-# INLINE unexpected #-}

-- | Return both the result of a parse and the list of tokens that were
-- | Return both the result of a parse and a chunk of input that was
-- consumed during parsing. This relies on the change of the
-- 'stateTokensProcessed' value to evaluate how many tokens were consumed.
-- If you mess with it manually in the argument parser, prepare for
Expand Down Expand Up @@ -1292,7 +1293,7 @@ match p = do
region :: MonadParsec e s m
=> (ParseError (Token s) e -> ParseError (Token s) e)
-- ^ How to process 'ParseError's
-> m a -- ^ The “region” that processing applies to
-> m a -- ^ The “region” that the processing applies to
-> m a
region f m = do
r <- observing m
Expand Down
17 changes: 11 additions & 6 deletions Text/Megaparsec/Byte/Lexer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,10 @@
--
-- Stripped-down version of "Text.Megaparsec.Char.Lexer" for streams of
-- bytes.
--
-- This module is intended to be imported qualified:
--
-- > import qualified Text.Megaparsec.Byte.Lexer as L

{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
Expand Down Expand Up @@ -194,7 +198,7 @@ data SP = SP !Integer {-# UNPACK #-} !Int

-- | Parse a floating point number without sign. There are differences
-- between the syntax for floating point literals described in the Haskell
-- report and what this function accepts. In particular, it does not quire
-- report and what this function accepts. In particular, it does not require
-- fractional part and accepts inputs like @\"3\"@ returning @3.0@.
--
-- This is a simple short-cut defined as:
Expand All @@ -208,10 +212,11 @@ float :: (MonadParsec e s m, Token s ~ Word8, RealFloat a) => m a
float = Sci.toRealFloat <$> scientific <?> "floating point number"
{-# INLINEABLE float #-}

-- | @'signed' space p@ parser parses an optional sign, then if there is a
-- sign it will consume optional white space (using @space@ parser), then it
-- runs parser @p@ which should return a number. Sign of the number is
-- changed according to previously parsed sign.
-- | @'signed' space p@ parser parses an optional sign character (“+” or
-- “-”), then if there is a sign it consumes optional white space (using
-- @space@ parser), then it runs parser @p@ which should return a number.
-- Sign of the number is changed according to the previously parsed sign
-- character.
--
-- For example, to parse signed integer you can write:
--
Expand All @@ -225,7 +230,7 @@ signed :: (MonadParsec e s m, Token s ~ Word8, Num a)
-> m a -- ^ Parser for signed numbers
signed spc p = ($) <$> option id (C.lexeme spc sign) <*> p
where
sign = (char 43 *> return id) <|> (char 45 *> return negate)
sign = (id <$ char 43) <|> (negate <$ char 45)
{-# INLINEABLE signed #-}

----------------------------------------------------------------------------
Expand Down
16 changes: 10 additions & 6 deletions Text/Megaparsec/Char/Lexer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -380,6 +380,9 @@ lineFold sc action =
-- string literals:
--
-- > stringLiteral = char '"' >> manyTill L.charLiteral (char '"')
--
-- __Performance note__: the parser is not particularly efficient at the
-- moment.

charLiteral :: (MonadParsec e s m, Token s ~ Char) => m Char
charLiteral = label "literal character" $ do
Expand Down Expand Up @@ -502,7 +505,7 @@ data SP = SP !Integer {-# UNPACK #-} !Int

-- | Parse a floating point number without sign. There are differences
-- between the syntax for floating point literals described in the Haskell
-- report and what this function accepts. In particular, it does not quire
-- report and what this function accepts. In particular, it does not require
-- fractional part and accepts inputs like @\"3\"@ returning @3.0@.
--
-- This is a simple short-cut defined as:
Expand All @@ -519,10 +522,11 @@ float :: (MonadParsec e s m, Token s ~ Char, RealFloat a) => m a
float = Sci.toRealFloat <$> scientific <?> "floating point number"
{-# INLINEABLE float #-}

-- | @'signed' space p@ parser parses an optional sign, then if there is a
-- sign it will consume optional white space (using @space@ parser), then it
-- runs parser @p@ which should return a number. Sign of the number is
-- changed according to previously parsed sign.
-- | @'signed' space p@ parser parses an optional sign character (“+” or
-- “-”), then if there is a sign it consumes optional white space (using
-- @space@ parser), then it runs parser @p@ which should return a number.
-- Sign of the number is changed according to the previously parsed sign
-- character.
--
-- For example, to parse signed integer you can write:
--
Expand All @@ -536,5 +540,5 @@ signed :: (MonadParsec e s m, Token s ~ Char, Num a)
-> m a -- ^ Parser for signed numbers
signed spc p = ($) <$> option id (lexeme spc sign) <*> p
where
sign = (C.char '+' *> return id) <|> (C.char '-' *> return negate)
sign = (id <$ C.char '+') <|> (negate <$ C.char '-')
{-# INLINEABLE signed #-}
4 changes: 2 additions & 2 deletions Text/Megaparsec/Error.hs
Original file line number Diff line number Diff line change
Expand Up @@ -103,8 +103,8 @@ instance NFData a => NFData (ErrorFancy a) where
rnf (ErrorIndentation ord ref act) = ord `seq` rnf ref `seq` rnf act
rnf (ErrorCustom a) = rnf a

-- | 'ParseError' representsparse errors. The data type is parametrized
-- over the token type @t@ and the custom data @e@.
-- | @'ParseError' t e@ represents a parse error parametrized over the token
-- type @t@ and the custom data @e@.
--
-- Note that the stack of source positions contains current position as its
-- head, and the rest of positions allows to track full sequence of include
Expand Down
6 changes: 3 additions & 3 deletions Text/Megaparsec/Error/Builder.hs
Original file line number Diff line number Diff line change
Expand Up @@ -94,16 +94,16 @@ instance Ord e => Monoid (EF e) where

-- | Assemble a 'ParseError' from source position and @'ET' t@ value. To
-- create source position, two helpers are available: 'posI' and 'posN'.
-- @'ET' t@ is a monoid and can be built from primitives provided by this
-- module, see below.
-- @'ET' t@ is a monoid and can be assembled by combining primitives
-- provided by this module, see below.

err
:: NonEmpty SourcePos -- ^ 'ParseError' position
-> ET t -- ^ Error components
-> ParseError t e -- ^ Resulting 'ParseError'
err pos (ET us ps) = TrivialError pos us ps

-- | Much like 'err', but constructs a “fancy” 'ParseError'.
-- | Like 'err', but constructs a “fancy” 'ParseError'.

errFancy
:: NonEmpty SourcePos -- ^ 'ParseError' position
Expand Down
2 changes: 1 addition & 1 deletion Text/Megaparsec/Pos.hs
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,7 @@ import GHC.Generics
newtype Pos = Pos Int
deriving (Show, Eq, Ord, Data, Typeable, NFData)

-- | Construction of 'Pos' from 'Word'. The function throws
-- | Construction of 'Pos' from 'Int'. The function throws
-- 'InvalidPosException' when given a non-positive argument.
--
-- @since 6.0.0
Expand Down
5 changes: 3 additions & 2 deletions Text/Megaparsec/Stream.hs
Original file line number Diff line number Diff line change
Expand Up @@ -116,7 +116,7 @@ class (Ord (Token s), Ord (Tokens s)) => Stream s where
{-# INLINE positionAtN #-}

-- | Advance position given a single token. The returned position is the
-- position right after the token, or position where the token ends.
-- position right after the token, or the position where the token ends.

advance1
:: Proxy s -- ^ 'Proxy' clarifying the type of stream
Expand All @@ -126,7 +126,8 @@ class (Ord (Token s), Ord (Tokens s)) => Stream s where
-> SourcePos -- ^ Advanced position

-- | Advance position given a chunk of stream. The returned position is
-- the position right after the chunk, or position where the chunk ends.
-- the position right after the chunk, or the position where the chunk
-- ends.

advanceN
:: Proxy s -- ^ 'Proxy' clarifying the type of stream
Expand Down

0 comments on commit a745b27

Please sign in to comment.