module Text.ParserCombinators.UU.BasicInstances(
Error (..),
Str (..),
Insertion (..),
LineCol (..),
LineColPos (..),
Parser,
ParserTrafo,
IsLocationUpdatedBy,
createStr,
show_expecting,
pSatisfy,
pRangeInsert,
pRange,
pSymInsert,
pSym,
pToken,
pTokenCost,
pMunch,
pMunchL
) where
import Text.ParserCombinators.UU.Core
import Data.Maybe
import Data.Word
import qualified Data.ListLike as LL
data Error pos = Inserted String pos Strings
| Deleted String pos Strings
| Replaced String String pos Strings
| DeletedAtEnd String
instance (Show pos) => Show (Error pos) where
show (Inserted s pos expecting) = "-- Inserted " ++ s ++ show_expecting pos expecting
show (Deleted t pos expecting) = "-- Deleted " ++ t ++ show_expecting pos expecting
show (Replaced old new pos expecting) = "-- Replaced " ++ old ++ " by "++ new ++ show_expecting pos expecting
show (DeletedAtEnd t) = "-- The token " ++ t ++ " was not consumed by the parsing process."
show_expecting :: Show pos => pos -> [String] -> String
show_expecting pos [a] = " at position " ++ show pos ++ " expecting " ++ a
show_expecting pos (a:as) = " at position " ++ show pos ++
" expecting one of [" ++ a ++ concat (map (", " ++) as) ++ "]"
show_expecting pos [] = " expecting nothing"
data Str a s loc = Str {
input :: s,
msgs :: [Error loc],
pos :: loc,
deleteOk :: !Bool
}
type Parser a = forall loc state . (IsLocationUpdatedBy loc Char, LL.ListLike state Char) => P (Str Char state loc) a
type ParserTrafo a b = forall loc state . (IsLocationUpdatedBy loc Char, LL.ListLike state Char) => P (Str Char state loc) a -> P (Str Char state loc) b
createStr :: LL.ListLike s a => loc -> s -> Str a s loc
createStr beginpos ls = Str ls [] beginpos True
instance IsLocationUpdatedBy Int Char where
advance pos _ = pos + 1
instance IsLocationUpdatedBy Int Word8 where
advance pos _ = pos + 1
data LineCol = LineCol !Int !Int deriving Show
instance IsLocationUpdatedBy LineCol Char where
advance (LineCol line pos) c = case c of
'\n' -> LineCol (line+1) 0
'\t' -> LineCol line ( pos + 8 (pos1) `mod` 8)
_ -> LineCol line (pos + 1)
data LineColPos = LineColPos !Int !Int !Int deriving Show
instance IsLocationUpdatedBy LineColPos Char where
advance (LineColPos line pos abs) c = case c of
'\n' -> LineColPos (line+1) 0 (abs + 1)
'\t' -> LineColPos line (pos + 8 (pos1) `mod` 8) (abs + 1)
_ -> LineColPos line (pos + 1) (abs + 1)
instance IsLocationUpdatedBy loc a => IsLocationUpdatedBy loc [a] where
advance = foldl advance
instance (Show a, LL.ListLike s a) => Eof (Str a s loc) where
eof (Str i _ _ _ ) = LL.null i
deleteAtEnd (Str s msgs pos ok ) | LL.null s = Nothing
| otherwise = Just (5, Str (LL.tail s) (msgs ++ [DeletedAtEnd (show (LL.head s))]) pos ok)
instance StoresErrors (Str a s loc) (Error loc) where
getErrors (Str inp msgs pos ok ) = (msgs, Str inp [] pos ok)
instance HasPosition (Str a s loc) loc where
getPos (Str inp msgs pos ok ) = pos
data Insertion a = Insertion String a Cost
pSatisfy :: forall loc state a .((Show a, loc `IsLocationUpdatedBy` a, LL.ListLike state a) => (a -> Bool) -> (Insertion a) -> P (Str a state loc) a)
pSatisfy p (Insertion msg a cost) = pSymExt splitState (Succ (Zero)) Nothing
where splitState :: forall r. ((a -> (Str a state loc) -> Steps r) -> (Str a state loc) -> Steps r)
splitState k (Str tts msgs pos del_ok)
= show_attempt ("Try Predicate: " ++ msg ++ " at position " ++ show pos ++ "\n") (
let ins exp = (cost, k a (Str tts (msgs ++ [Inserted (show a) pos exp]) pos False))
in if LL.null tts
then Fail [msg] [ins]
else let t = LL.head tts
ts = LL.tail tts
del exp = (4, splitState k (Str ts (msgs ++ [Deleted (show t) pos exp]) (advance pos t) True ))
in if p t
then show_symbol ("Accepting symbol: " ++ show t ++ " at position: " ++ show pos ++"\n")
(Step 1 (k t (Str ts msgs (advance pos t) True)))
else Fail [msg] (ins: if del_ok then [del] else [])
)
pRangeInsert :: (Ord a, Show a, IsLocationUpdatedBy loc a, LL.ListLike state a) => (a, a) -> Insertion a -> P (Str a state loc) a
pRangeInsert (low, high) = pSatisfy (\ t -> low <= t && t <= high)
pRange :: (Ord a, Show a, IsLocationUpdatedBy loc a, LL.ListLike state a) => (a, a) -> P (Str a state loc) a
pRange lh@(low, high) = pRangeInsert lh (Insertion (show low ++ ".." ++ show high) low 5)
pSymInsert :: (Eq a,Show a, IsLocationUpdatedBy loc a, LL.ListLike state a) => a -> Insertion a -> P (Str a state loc) a
pSymInsert t = pSatisfy (==t)
pSym :: (Eq a,Show a, IsLocationUpdatedBy loc a, LL.ListLike state a) => a -> P (Str a state loc) a
pSym t = pSymInsert t (Insertion (show t) t 5)
pMunchL :: forall loc state a .((Show a, loc `IsLocationUpdatedBy` a, LL.ListLike state a) => (a -> Bool) -> String -> P (Str a state loc) [a])
pMunchL p msg = pSymExt splitState Zero Nothing
where splitState :: forall r. (([a] -> (Str a state loc) -> Steps r) -> (Str a state loc) -> Steps r)
splitState k inp@(Str tts msgs pos del_ok)
= show_attempt ("Try Munch: " ++ msg ++ "\n") (
let (fmunch, rest) = LL.span p tts
munched = LL.toList fmunch
l = length munched
in if l > 0 then show_munch ("Accepting munch: " ++ msg ++ " " ++ show munched ++ show pos ++ "\n")
(Step l (k munched (Str rest msgs (advance pos munched) (l>0 || del_ok))))
else show_munch ("Accepting munch: " ++ msg ++ " as emtty munch " ++ show pos ++ "\n") (k [] inp)
)
pMunch :: forall loc state a .((Show a, loc `IsLocationUpdatedBy` a, LL.ListLike state a) => (a -> Bool) -> P (Str a state loc) [a])
pMunch p = pMunchL p ""
pTokenCost :: forall loc state a .((Show a, Eq a, loc `IsLocationUpdatedBy` a, LL.ListLike state a) => [a] -> Int -> P (Str a state loc) [a])
pTokenCost as cost =
if null as then error "Module: BasicInstances, function: pTokenCost; call with empty token"
else pSymExt splitState (nat_length as) Nothing
where tas :: state
tas = LL.fromList as
nat_length [] = Zero
nat_length (_:as) = Succ (nat_length as)
l = length as
msg = show as
splitState :: forall r. (([a] -> (Str a state loc) -> Steps r) -> (Str a state loc) -> Steps r)
splitState k inp@(Str tts msgs pos del_ok)
= show_attempt ("Try Token: " ++ show as ++ "\n") (
if LL.isPrefixOf tas tts
then show_tokens ("Accepting token: " ++ show as ++"\n")
(Step l (k as (Str (LL.drop l tts) msgs (advance pos as) True)))
else let ins exp = (cost, k as (Str tts (msgs ++ [Inserted msg pos exp]) pos False))
in if LL.null tts
then Fail [msg] [ins]
else let t = LL.head tts
ts = LL.tail tts
del exp = (5, splitState k
(Str ts (msgs ++ [Deleted (show t) pos exp])
(advance pos t) True))
in Fail [msg] (ins: if del_ok then [del] else [])
)
pToken :: forall loc state a .((Show a, Eq a, loc `IsLocationUpdatedBy` a, LL.ListLike state a) => [a] -> P (Str a state loc) [a])
pToken as = pTokenCost as 10
show_tokens :: String -> b -> b
show_tokens m v = v
show_munch :: String -> b -> b
show_munch m v = v
show_symbol :: String -> b -> b
show_symbol m v = v
show_attempt m v = v