mirror of
https://github.com/mrkkrp/megaparsec.git
synced 2024-12-28 18:54:34 +03:00
Improve new version of ‘Text.Megaparsec.Pos’
Documentation improvements. The commit also makes it compile with all supported GHC versions.
This commit is contained in:
parent
acbae63a21
commit
641114a442
@ -1,16 +1,17 @@
|
||||
-- |
|
||||
-- Module : Text.Megaparsec.Pos
|
||||
-- Copyright : © 2015–2016 Megaparsec contributors
|
||||
-- © 2007 Paolo Martini
|
||||
-- © 1999–2001 Daan Leijen
|
||||
-- License : FreeBSD
|
||||
--
|
||||
-- Maintainer : Mark Karpov <markkarpov@opmbx.org>
|
||||
-- Stability : experimental
|
||||
-- Portability : portable
|
||||
--
|
||||
-- Textual source position.
|
||||
-- Textual source position. The position includes name of file, line number,
|
||||
-- and column number. Stack of such positions can be used to support include
|
||||
-- files.
|
||||
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
|
||||
@ -31,20 +32,33 @@ module Text.Megaparsec.Pos
|
||||
where
|
||||
|
||||
import Control.Monad.Catch
|
||||
import Data.Data (Data)
|
||||
import Data.Semigroup
|
||||
import Data.Typeable (Typeable)
|
||||
import Unsafe.Coerce
|
||||
|
||||
#if !MIN_VERSION_base(4,8,0)
|
||||
import Control.Applicative ((<$>))
|
||||
import Data.Word (Word)
|
||||
#endif
|
||||
|
||||
----------------------------------------------------------------------------
|
||||
-- Pos
|
||||
|
||||
-- | Positive integer that is used to represent line number, column number,
|
||||
-- and similar things like indentation level.
|
||||
-- and similar things like indentation level. 'Semigroup' instance can be
|
||||
-- used to safely and purely add 'Pos'es together.
|
||||
|
||||
newtype Pos = Pos Word deriving (Show, Eq, Ord)
|
||||
newtype Pos = Pos Word
|
||||
deriving (Show, Eq, Ord, Data, Typeable)
|
||||
|
||||
-- | Construction of 'Pos' from 'Word'. Zero values will throw 'InvalidPos'.
|
||||
-- | Construction of 'Pos' from an instance of 'Integral'. The function
|
||||
-- throws 'InvalidPosException' when given non-positive argument. Note that
|
||||
-- the function is polymorphic with respect to 'MonadThrow' @m@, so you can
|
||||
-- get result inside of 'Maybe' or use the function in the context of parser
|
||||
-- monad.
|
||||
|
||||
mkPos :: (MonadThrow m, Integral a) => a -> m Pos
|
||||
mkPos :: (Integral a, MonadThrow m) => a -> m Pos
|
||||
mkPos x =
|
||||
if x < 1
|
||||
then throwM InvalidPosException
|
||||
@ -64,8 +78,8 @@ unsafePos x =
|
||||
-- | Extract 'Word' from 'Pos'.
|
||||
|
||||
unPos :: Pos -> Word
|
||||
unPos (Pos x) = x
|
||||
{-# INLINE unPos #-}
|
||||
unPos = unsafeCoerce
|
||||
{-# INLINE unPos #-}
|
||||
|
||||
instance Semigroup Pos where
|
||||
(Pos x) <> (Pos y) = Pos (x + y)
|
||||
@ -81,7 +95,8 @@ instance Read Pos where
|
||||
-- | The exception is thrown by 'mkPos' when its argument is not a positive
|
||||
-- number.
|
||||
|
||||
data InvalidPosException = InvalidPosException deriving (Eq, Show, Typeable)
|
||||
data InvalidPosException = InvalidPosException
|
||||
deriving (Eq, Show, Data, Typeable)
|
||||
|
||||
instance Exception InvalidPosException
|
||||
|
||||
@ -89,12 +104,14 @@ instance Exception InvalidPosException
|
||||
-- Source position
|
||||
|
||||
-- | The data type @SourcePos@ represents source positions. It contains the
|
||||
-- name of the source file, a line number and a column number.
|
||||
-- name of the source file, a line number, and a column number. Source line
|
||||
-- and column positions change intensively during parsing, so we need to
|
||||
-- make them strict to avoid memory leaks.
|
||||
|
||||
data SourcePos = SourcePos
|
||||
{ sourceName :: String -- ^ Name of source file
|
||||
, sourceLine :: !Pos -- ^ Line number
|
||||
, sourceColumn :: !Pos -- ^ Column number
|
||||
{ sourceName :: FilePath -- ^ Name of source file
|
||||
, sourceLine :: !Pos -- ^ Line number
|
||||
, sourceColumn :: !Pos -- ^ Column number
|
||||
} deriving (Show, Read, Eq, Ord)
|
||||
|
||||
-- | Construct initial position (line 1, column 1) given name of source
|
||||
@ -118,9 +135,8 @@ sourcePosPretty (SourcePos n l c)
|
||||
-- | Update a source position given a character. The first argument
|
||||
-- specifies tab width. If the character is a newline (\'\\n\') the line
|
||||
-- number is incremented by 1. If the character is a tab (\'\\t\') the
|
||||
-- column number is incremented to the nearest tab position, i.e. @column +
|
||||
-- width - ((column - 1) \`rem\` width)@. In all other cases, the column is
|
||||
-- incremented by 1.
|
||||
-- column number is incremented to the nearest tab position. In all other
|
||||
-- cases, the column is incremented by 1.
|
||||
|
||||
defaultUpdatePos
|
||||
:: Pos -- ^ Tab width
|
||||
|
Loading…
Reference in New Issue
Block a user