{-# LANGUAGE RankNTypes #-}
module Text.MMark.Parser.Internal
(
BParser
, runBParser
, isNakedAllowed
, refLevel
, subEnv
, registerReference
, IParser
, runIParser
, disallowEmpty
, isEmptyAllowed
, disallowLinks
, isLinksAllowed
, disallowImages
, isImagesAllowed
, getLastChar
, lastChar
, lookupReference
, Isp (..)
, CharType (..)
, Defs
, MMarkErr (..) )
where
import Control.Monad.State.Strict
import Data.Bifunctor
import Data.Function ((&))
import Data.HashMap.Strict (HashMap)
import Data.Ratio ((%))
import Data.Text (Text)
import Data.Text.Metrics (damerauLevenshteinNorm)
import Lens.Micro (Lens', (^.), (.~), set, over)
import Lens.Micro.Extras (view)
import Text.MMark.Parser.Internal.Type
import Text.Megaparsec hiding (State)
import Text.URI (URI)
import qualified Data.HashMap.Strict as HM
import qualified Data.List.NonEmpty as NE
import qualified Text.Megaparsec as M
type BParser a = ParsecT MMarkErr Text (State BlockState) a
runBParser
:: BParser a
-> FilePath
-> Text
-> Either (ParseErrorBundle Text MMarkErr) (a, Defs)
runBParser p file input =
case runState (snd <$> runParserT' p st) initialBlockState of
(Left bundle, _) -> Left bundle
(Right x, st') -> Right (x, st' ^. bstDefs)
where
st = mkInitialState file input 0
isNakedAllowed :: BParser Bool
isNakedAllowed = gets (^. bstAllowNaked)
refLevel :: BParser Pos
refLevel = gets (^. bstRefLevel)
subEnv
:: Bool
-> Pos
-> BParser a
-> BParser a
subEnv allowNaked rlevel =
locally bstAllowNaked allowNaked .
locally bstRefLevel rlevel
registerReference
:: Text
-> (URI, Maybe Text)
-> BParser Bool
registerReference = registerGeneric referenceDefs
registerGeneric
:: Lens' Defs (HashMap DefLabel a)
-> Text
-> a
-> BParser Bool
registerGeneric l name a = do
let dlabel = mkDefLabel name
defs <- gets (^. bstDefs . l)
if HM.member dlabel defs
then return True
else do
modify' $ over (bstDefs . l) (HM.insert dlabel a)
return False
type IParser a = StateT InlineState (Parsec MMarkErr Text) a
runIParser
:: Defs
-> IParser a
-> Isp
-> Either (ParseError Text MMarkErr) a
runIParser _ _ (IspError err) = Left err
runIParser defs p (IspSpan offset input) =
first (NE.head . bundleErrors) (snd (runParser' (evalStateT p ist) pst))
where
ist = initialInlineState & istDefs .~ defs
pst = mkInitialState "" input offset
disallowEmpty :: IParser a -> IParser a
disallowEmpty = locally istAllowEmpty False
isEmptyAllowed :: IParser Bool
isEmptyAllowed = gets (view istAllowEmpty)
disallowLinks :: IParser a -> IParser a
disallowLinks = locally istAllowLinks False
isLinksAllowed :: IParser Bool
isLinksAllowed = gets (view istAllowLinks)
disallowImages :: IParser a -> IParser a
disallowImages = locally istAllowImages False
isImagesAllowed :: IParser Bool
isImagesAllowed = gets (view istAllowImages)
getLastChar :: IParser CharType
getLastChar = gets (view istLastChar)
lastChar :: CharType -> IParser ()
lastChar = modify' . set istLastChar
{-# INLINE lastChar #-}
lookupReference
:: Text
-> IParser (Either [Text] (URI, Maybe Text))
lookupReference = lookupGeneric referenceDefs
lookupGeneric
:: Lens' Defs (HashMap DefLabel a)
-> Text
-> IParser (Either [Text] a)
lookupGeneric l name = do
let dlabel = mkDefLabel name
defs <- gets (view (istDefs . l))
case HM.lookup dlabel defs of
Nothing -> return . Left $ closeNames dlabel (HM.keys defs)
Just x -> return (Right x)
closeNames :: DefLabel -> [DefLabel] -> [Text]
closeNames r'
= filter (\x -> damerauLevenshteinNorm r x >= (2 % 3))
. map unDefLabel
where
r = unDefLabel r'
mkInitialState
:: FilePath
-> Text
-> Int
-> M.State Text e
mkInitialState file input offset = M.State
{ stateInput = input
, stateOffset = offset
, statePosState = PosState
{ pstateInput = input
, pstateOffset = offset
, pstateSourcePos = initialPos file
, pstateTabWidth = mkPos 4
, pstateLinePrefix = ""
}
, stateParseErrors = []
}
locally :: MonadState s m => Lens' s a -> a -> m b -> m b
locally l x m = do
y <- gets (^. l)
modify' (set l x)
r <- m
modify' (set l y)
return r