module Logic.Judge.Formula.Parser
(
Parseable(..)
, parse
, formula
, modality
, justification
, quantifier
, named
, marked
, identifier
, boolean
, comments
, Operator
, expression
, ambiguity
) where
import Prelude hiding (length)
import "base" Data.List (tails, sortBy, groupBy)
import "base" Data.Function (on)
import "base" Data.Maybe (catMaybes, listToMaybe)
import "base" Data.Char (isAlphaNum, isUpper)
import "base" Control.Applicative ((<|>), (<*), (*>), liftA2)
import "text" Data.Text (Text, pack, unpack, empty, length)
import "attoparsec" Data.Attoparsec.Combinator ((<?>))
import qualified "attoparsec" Data.Attoparsec.Combinator as P (lookAhead)
import qualified "attoparsec" Data.Attoparsec.Text as P
import qualified Logic.Judge.Formula.Datastructure as F
class Parseable a where
parser :: P.Parser a
parserEmbedded :: P.Parser a
parserEmbedded = parser
instance Parseable f => Parseable [f] where
parser = comments *> P.many1 (parser <* comments)
instance Parseable F.Classical where
parser = fail "proposition has no extension"
instance Parseable F.Modality where
parser = modality
instance Parseable F.Quantifier where
parser = quantifier
instance Parseable F.Justification where
parser = justification
parserEmbedded = parser <* (spaced $ P.char ':')
instance Parseable e => Parseable (F.Formula e) where
parser = formula parserEmbedded
instance Parseable f => Parseable (F.Marked f) where
parser = marked parser
instance Parseable e => Parseable (F.Ambiguous (F.Term e)) where
parser = F.Ambiguous <$> ambiguity
[ F.Formula <$> parser
, F.Extension <$> parser
, F.MarkedFormula <$> parser ]
parse :: (Monad m, Parseable a) => Text -> m a
parse = either fail return . P.parseOnly (parser <* P.endOfInput)
compose, composeReverse :: P.Parser [a -> a] -> P.Parser (a -> a)
compose = fmap $ foldr (.) id
composeReverse = fmap $ foldl (flip (.)) id
data Operator a = Infix Associativity (P.Parser (a -> a -> a))
| Prefix (P.Parser (a -> a))
| Postfix (P.Parser (a -> a))
data Associativity = L | R
expression :: [[ Operator a ]] ->
P.Parser a
-> P.Parser a
expression buckets base = spaced $ foldl buildUpon (spaced base) buckets' where
buckets' = zip buckets (map concat . tail . tails $ buckets)
buildUpon tighterParser (current, pending) =
let infixL = spaced $ P.choice [ p | Infix L p <- current ]
infixR = spaced $ P.choice [ p | Infix R p <- current ]
postfix = spaced $ P.choice [ p | Postfix p <- current ]
prefix = spaced $ P.choice [ p | Prefix p <- current ]
prefixLooser = spaced $ P.choice [ p | Prefix p <- pending ]
postfixes = composeReverse $ P.many' postfix
prefixesLooser = compose $ P.many' prefixLooser
prefixes = compose $ (:)
<$> prefix
<*> P.many' (prefixLooser <|> prefix)
<|> return []
continueL x = do f <- infixL
g <- prefixesLooser
y <- tighterParser
continueL (x `f` g y) <|> return (x `f` g y)
continueR x = do f <- infixR
g <- prefixesLooser
y' <- tighterParser
y <- continueR y' <|> return y'
return $ x `f` g y
in do f <- prefixes
x <- tighterParser
g <- postfixes
let y = g (f x) in continueL y <|> continueR y <|> return y
ambiguity :: [P.Parser a] -> P.Parser [a]
ambiguity options = do
(n, results) <- longestParses =<< consider options
P.take n
return results
where
whatIf :: P.Parser a -> P.Parser (Maybe (Text, a))
whatIf p = P.option Nothing (Just <$> P.lookAhead (P.match p))
consider :: [P.Parser a] -> P.Parser [(Text, a)]
consider = fmap catMaybes . sequence . map whatIf
longestParses :: [(Text, a)] -> P.Parser (Int, [a])
longestParses =
maybe (fail "failed at ambiguity") return .
fmap (\xs -> (fst $ head xs, map snd xs)) .
listToMaybe .
groupBy ((==) `on` fst) .
reverse .
sortBy (compare `on` fst) .
map (\(x, y) -> (length x, y))
formula :: P.Parser ext -> P.Parser (F.Formula ext)
formula extension = expression operators base
where
operators =
[ [ Prefix (oneOf ['~','¬'] >> return F.Negation) ]
, [ Infix L (oneOf ['&','∧'] >> return F.Conjunction) ]
, [ Infix L (oneOf ['|','∨'] >> return F.Disjunction) ]
, [ Infix L (oneOf ['^','⊻'] >> return F.XDisjunction) ]
, [ Infix R (oneOf' ["->", "→"] >> return F.Implication) ]
, [ Infix R (oneOf' ["<-", "←"] >> return (flip F.Implication)) ]
, [ Infix R (oneOf' ["<->", "↔"] >> return F.BiImplication) ]
]
base = (F.Extend <$> extension <*> (optPrefixed <*> base) )
<|> (F.Constant <$> boolean)
<|> (F.Variable <$> identifier)
<|> (P.char '(' *> formula extension <* P.char ')')
<?> "formula term"
optPrefixed =
compose . P.many' . P.choice $
[ p | bucket <- operators, Prefix p <- bucket ]
modality :: P.Parser F.Modality
modality = (oneOf' ["[]","□"] >> return F.Necessary)
<|> (oneOf' ["<>","◇"] >> return F.Possible)
quantifier :: P.Parser F.Quantifier
quantifier = quantor <*> identifier <* P.char '.'
where
quantor = (oneOf' ["\\A","∀"] >> return F.Universal)
<|> (oneOf' ["\\E","∃"] >> return F.Existential)
justification :: P.Parser F.Justification
justification = expression operators base
where
operators =
[ [ Prefix (oneOf ['!'] >> return (F.ProofChecker)) ]
, [ Infix L (oneOf ['+'] >> return (F.Sum)) ]
, [ Infix L (oneOf ['*','⋅','·'] >> return (F.Application)) ]
]
base = (toAtom <$> identifier)
<|> (P.char '(' *> justification <* P.char ')')
<?> "justification term"
toAtom s | isUpper (head s) = F.ProofVariable s
| otherwise = F.ProofConstant s
oneOf :: [Char] -> P.Parser Char
oneOf c = P.satisfy (`elem` c)
oneOf' :: [String] -> P.Parser String
oneOf' s = fmap unpack $ P.choice (map (P.string . pack) s)
spaced :: P.Parser a -> P.Parser a
spaced p = P.skipSpace *> p <* P.skipSpace
identifier :: P.Parser String
identifier = liftA2 (:) P.letter (unpack <$> P.takeWhile (\x -> isAlphaNum x || x == '\''))
<?> "identifier"
boolean :: P.Parser Bool
boolean = (oneOf "⊥0" >> return False) <|> (oneOf "⊤1" >> return True)
<?> "boolean"
named :: P.Parser x -> P.Parser (String, x)
named p = (,)
<$> (identifier <* (spaced $ P.char '='))
<*> p
marked :: P.Parser formula -> P.Parser (F.Marked formula)
marked p = F.Marked <$> P.option [] marks <*> p where
marks = (spaced $ P.char '[')
*> P.sepBy' identifier (spaced $ P.char ',') <*
(spaced $ P.char ']')
comments :: P.Parser ()
comments =
P.skipSpace *> P.skipMany (
P.char '#' *> P.manyTill P.anyChar P.endOfLine <* P.skipSpace
)