Skip to content

Commit

Permalink
Probably need to redo everything on the parser to handle plurals
Browse files Browse the repository at this point in the history
  • Loading branch information
PPKFS committed Apr 2, 2024
1 parent 84a393b commit bbca9cd
Show file tree
Hide file tree
Showing 3 changed files with 17 additions and 9 deletions.
2 changes: 1 addition & 1 deletion run_no
Original file line number Diff line number Diff line change
@@ -1 +1 @@
523
524
21 changes: 13 additions & 8 deletions src/Yaifl/Game/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -213,26 +213,31 @@ parseArgumentType (Optionally a) t = do
parseArgumentType TakesObjectParameter t = tryFindingAnyObject t
parseArgumentType TakesThingParameter t = do
o <- tryFindingObject t
case fromAny <$> o of
case bimapF (mapM fromAny) fromAny o of
Left err -> pure $ Left err
Right Nothing -> pure $ Left "got room not thing"
Right (Just x) -> pure $ Right $ ThingParameter x
Right (Right (Just x)) -> pure $ Right $ ThingParameter x
Right (Left (Just ts)) -> pure $ Right $ PluralParameter (map ThingParameter ts)
_ -> pure $ Left "got room not thing"
parseArgumentType a t = pure $ Left $ "not implemented yet" <> show a <> " " <> t

tryFindingAnyObject ::
forall wm es.
WithListWriting wm
=> RuleEffects wm es
=> Text
-> Eff es (Either Text (NamedActionParameter wm))
tryFindingAnyObject t = do
o <- tryFindingObject t
pure $ ObjectParameter <$> o
case o of
Right (Left plurals) -> pure $ Right $ PluralParameter (map ObjectParameter plurals)
Right (Right o') -> pure $ Right $ ObjectParameter o'
Left err -> pure $ Left err

tryFindingObject ::
WithListWriting wm
=> RuleEffects wm es
=> Text
-> Eff es (Either Text (AnyObject wm))
-> Eff es (Either Text (Either [AnyObject wm] (AnyObject wm)))
tryFindingObject t = failHorriblyIfMissing $ do
pl <- getCurrentPlayer
playerLoc <- getLocation pl
Expand All @@ -245,15 +250,15 @@ findObjectsFrom ::
=> Text
-> [Thing wm]
-> Bool
-> Eff es (Either Text (AnyObject wm))
-> Eff es (Either Text (Either [AnyObject wm] (AnyObject wm)))
findObjectsFrom t allItems considerAmbiguity = do
let phraseSet = S.fromList . words $ t
let scores = zip (map (scoreParserMatch phraseSet) allItems) allItems
threshold <- use @Metadata #parserMatchThreshold
match <- filterM (\(f, _) -> f >>= \x -> pure (x > threshold)) scores
case match of
[] -> pure $ Left $ "I can't see anything called \"" <> t <> "\"."
[x] -> pure $ Right (toAny $ snd x)
[x] -> pure . Right . Right $ toAny (snd x)
xs -> if considerAmbiguity
then handleAmbiguity (map snd xs)
else pure $ Left "I still didn't know what you meant."
Expand All @@ -262,7 +267,7 @@ handleAmbiguity ::
WithListWriting wm
=> RuleEffects wm es
=> [Thing wm]
-> Eff es (Either Text (AnyObject wm))
-> Eff es (Either Text (Either [AnyObject wm] (AnyObject wm)))
handleAmbiguity ls = do
names <- mapM (sayText . view #name) ls
let phrase = case names of
Expand Down
3 changes: 3 additions & 0 deletions src/Yaifl/Model/Actions/Args.hs
Original file line number Diff line number Diff line change
Expand Up @@ -53,6 +53,7 @@ data NamedActionParameter wm =
| ObjectParameter (AnyObject wm)
| ThingParameter (Thing wm)
| ConstantParameter Text
| PluralParameter [NamedActionParameter wm]
deriving stock ( Generic)

instance Show (NamedActionParameter wm) where
Expand All @@ -63,6 +64,7 @@ instance Show (NamedActionParameter wm) where
ObjectParameter _ -> "object"
ConstantParameter t -> show t
ThingParameter _ -> "thing"
PluralParameter wm -> "Multiple " <> show wm <> "s"
deriving stock instance Eq (WMDirection wm) => Eq (NamedActionParameter wm)
deriving stock instance Ord (WMDirection wm) => Ord (NamedActionParameter wm)

Expand All @@ -74,6 +76,7 @@ type family ActionParameter wm (goesWith :: ActionParameterType) where
ActionParameter wm TakesThingParameter = Thing wm
ActionParameter wm TakesConstantParameter = Text
ActionParameter wm (TakesOneOf goesWith1 goesWith2) = Either (ActionParameter wm goesWith1) (ActionParameter wm goesWith2)
--ActionParameter wm (PluralParameter goesWith) = [ActionParameter wm goesWith]

class GoesWith (g :: ActionParameterType) where
goesWithA :: Proxy g -> ActionParameterType
Expand Down

0 comments on commit bbca9cd

Please sign in to comment.