ItemAux.hs revision d046de48e620a7233d0dc2a687fc84b82c089887
649fdc0d0502d62d160c150684356fef2c273484Eugen Kuksamodule ItemAux where
649fdc0d0502d62d160c150684356fef2c273484Eugen Kuksa
649fdc0d0502d62d160c150684356fef2c273484Eugen Kuksaimport Id(Token())
649fdc0d0502d62d160c150684356fef2c273484Eugen Kuksaimport Lexer
649fdc0d0502d62d160c150684356fef2c273484Eugen Kuksaimport Token
649fdc0d0502d62d160c150684356fef2c273484Eugen Kuksaimport Parsec
649fdc0d0502d62d160c150684356fef2c273484Eugen Kuksaimport ParseType
649fdc0d0502d62d160c150684356fef2c273484Eugen Kuksaimport LocalEnv
import Term
pluralKeyword s = makeToken (string s <++> option "" (string "s"))
optSemi = bind (\ x y -> (x, y)) (option Nothing (fmap Just semi)) ann
dot = toKey [dotChar] <|> toKey middleDotStr <?> "dot"
bar = toKey [barChar]
equal = toKey equalStr
isStartKeyword s = s `elem` [dotChar]:middleDotStr:casl_reserved_words
lookAheadItemKeyword :: Ast -> Parser Ast
lookAheadItemKeyword ast =
do { c <- lookAhead (many (oneOf (['0'..'9'] ++ "'" ++ caslLetters))
<|> many (oneOf signChars))
; if isStartKeyword c then return ast else unexpected c
}
itemAux :: (Ast -> Token -> Parser Ast) -> Ast -> Token -> Parser Ast
itemAux itemParser ast key =
do { ast' <- itemParser ast key
; (m, an) <- optSemi
; let ast'' = if null an then ast' else addAn ast' an
in case m of Nothing -> return ast''
Just key' -> try (lookAheadItemKeyword ast'')
<|> itemAux itemParser ast'' key'
}