Skip to content

Commit

Permalink
Fix "in which is/are" when dealing with plurals
Browse files Browse the repository at this point in the history
  • Loading branch information
PPKFS committed Dec 22, 2024
1 parent e6631c1 commit ba7b0d0
Show file tree
Hide file tree
Showing 6 changed files with 55 additions and 48 deletions.
2 changes: 1 addition & 1 deletion yaifl/run_no
Original file line number Diff line number Diff line change
@@ -1 +1 @@
686
699
15 changes: 13 additions & 2 deletions yaifl/src/Yaifl/Text/AdaptiveNarrative.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@ data AdaptiveNarrative wm = AdaptiveNarrative
--, adaptiveTextViewpoint :: NarrativeViewpoint
, tense :: Tense
, priorNamedObject :: Maybe (AnyObject wm)
, priorQuantity :: Int
} deriving stock (Generic)

blankAdaptiveNarrative :: AdaptiveNarrative wm
Expand All @@ -35,14 +36,23 @@ blankAdaptiveNarrative = AdaptiveNarrative
--, adaptiveTextViewpoint = FirstPersonPlural
, tense = Present
, priorNamedObject = Nothing
, priorQuantity = 0
}

regarding ::
State (AdaptiveNarrative wm) :> es
=> CanBeAny wm a
=> Maybe a
-> Eff es ()
regarding mbObj = #priorNamedObject .= (toAny <$> mbObj)
regarding mbObj = do
#priorNamedObject .= (toAny <$> mbObj)
#priorQuantity .= 1

regardingMany ::
State (AdaptiveNarrative wm) :> es
=> Eff es ()
regardingMany = do
#priorQuantity .= 2

regardingNothing ::
State (AdaptiveNarrative wm) :> es
Expand Down Expand Up @@ -124,9 +134,10 @@ getPersonageOfObject ::
=> Eff es VerbPersonage
getPersonageOfObject = do
o <- getMentioned
q <- use @(AdaptiveNarrative wm) #priorQuantity
case o of
Nothing -> pure ThirdPersonSingular
Just someObj -> do
ifM (isPlayer someObj)
(use @(AdaptiveNarrative wm) #narrativeViewpoint)
(pure $ if someObj ^. #namePlurality == PluralNamed then ThirdPersonPlural else ThirdPersonSingular)
(pure $ if someObj ^. #namePlurality == PluralNamed || q > 1 then ThirdPersonPlural else ThirdPersonSingular)
10 changes: 9 additions & 1 deletion yaifl/src/Yaifl/Text/ListWriter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,7 @@ import Yaifl.Text.Say

import qualified Data.EnumSet as ES
import qualified Data.Text as T
import Breadcrumbs

type WithListWriting wm = (
WithPrintingNameOfSomething wm
Expand Down Expand Up @@ -247,6 +248,10 @@ writeListR = do
let adjustedList = if fromStart then coalesceList contents else contents
when prefacingWithIsAre $ do
a <- getMentionedThing
case listToMaybe adjustedList of
Nothing -> pass
Just (SingleObject o) -> regarding (Just o)
Just _ -> regardingMany
sayTellResponse V a
if withNewlines
then tell ":\n"
Expand Down Expand Up @@ -386,6 +391,8 @@ writeAfterEntry _numberOfItem itemMember = do
else
pure False
when (recurseFlag && asEnglishSentence) $ whenJust (viaNonEmpty head nonConcealedThings) $ \thing1 -> do
-- apparently we need to do this, because we want to say (on which ARE plurals) based on the first element of the list
-- not on the plurality of the thing(s) doing the containing.
regarding (Just thing1)
sayTellResponse V thingWrittenAbout
saySpace
Expand Down Expand Up @@ -536,7 +543,8 @@ listWriterResponsesImpl = \case
-- "[regarding list writer internals][are] nothing" (W) TODO
W -> constResponse "is nothing"
-- "[regarding list writer internals][are]" (V) TODO
V -> constResponse "is"
V -> Response $ \_o -> do
[sayingTell|#{are}|]
Y -> constResponse "nothing"
x -> constResponse $ "need to do response " <> show x <> " "

Expand Down
2 changes: 2 additions & 0 deletions yaifl/test/Yaifl/Test/Chapter3/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ import Yaifl.Test.Chapter3.StarryVoid
import Yaifl.Test.Chapter3.UpAndUp
import Yaifl.Test.Chapter3.Verbosity
import Yaifl.Test.Chapter3.TheUnbuttonedElevatorAffair
import Yaifl.Test.Chapter3.DisenchantmentBay
import qualified Data.Map as M
import Yaifl (PlainWorldModel, Game)
import Yaifl.Test.Chapter3.FirstNameBasis
Expand All @@ -35,4 +36,5 @@ spec _allTenses = M.fromList
, c3Harness ex11 -- First Name Basis
, c3Harness ex12 -- Midsummer Day
, c3Harness ex13 -- Tamed
, c3Harness ex14 -- Disenchantment Bay
]
73 changes: 29 additions & 44 deletions yaifl/test/Yaifl/Test/Chapter3/DisenchantmentBay.hs
Original file line number Diff line number Diff line change
@@ -1,66 +1,51 @@
module Yaifl.Test.Chapter3.Tamed where
module Yaifl.Test.Chapter3.DisenchantmentBay where

import Yaifl.Prelude
import Yaifl.Game.EffectHandlers

import Yaifl (PlainWorldModel)
import Yaifl.Model.Metadata

import Yaifl.Game.Create.Object
import Yaifl.Model.Query
import Yaifl.Text.SayQQ
import Yaifl.Text.AdaptiveNarrative
import Yaifl.Text.DynamicText
import Yaifl.Text.Say
import Yaifl.Game.EffectHandlers
import Yaifl.Game.ObjectSpecifics
import Yaifl.Model.Kinds.Device
import Yaifl.Model.Kinds.Person
import Yaifl.Model.Kinds (NamePlurality (..))
import Yaifl.Model.Kinds.Container
import Yaifl.Model.Kinds.Openable
import Yaifl.Model.Actions.Args
import Yaifl.Model.Kinds (ThingPortable(..))
import Yaifl.Game.Create
import Yaifl.Model.Rules (parseAction)
import Yaifl.Model.Kinds.Supporter
import Yaifl.Model.Metadata
import Yaifl.Test.Common
import Yaifl.Model.Kinds.Object

ex14 :: (Text, [Text], Game PlainWorldModel ())
ex14 = ("Disenchantment Bay", disenchantmentBayTestMeWith, disenchantmentBayWorld)

tamedWorld :: Game PlainWorldModel ()
tamedWorld = do
disenchantmentBayWorld :: Game PlainWorldModel ()
disenchantmentBayWorld = do
setTitle "Disenchantment Bay"
tcr <- addRoom "The Center Ring" ! done
_tc <- addRoom "The Cabin" ! #description
[wrappedText|The front of the small cabin is entirely occupied with navigational instruments,
a radar display, and radios for calling back to shore. Along each side runs a bench with faded blue
vinyl cushions, which can be lifted to reveal the storage space underneath. A glass case against the
wall contains several fishing rods.

tc <- addContainer "cage"
! #enterable Enterable
Scratched windows offer a view of the surrounding bay, and there is a door south to the deck.
A sign taped to one wall announces the menu of tours offered by the Yakutat Charter Boat Company.|]

gc <- addContainer "glass case"
! #openable Openable
! #opacity Transparent
! #opened Closed
! done
l <- addAnimal "lion"
! #location tc
_fr <- addThing "collection of fishing rods"
! #location (inThe gc)
! done
ped <- addSupporter "pedestal"
b <- addSupporter "bench"
! #enterable Enterable
! done
p <- getPlayer
p `isNowOn` ped
everyTurn [whenIn tc] $ do
r <- uniformRIO @Bool
if r then
[saying|The lion eyes you with obvious discontent.|]
else [saying|Though the lion does not move, you are aware that it is watching you closely.|]
tmb <- addContainer "magician's booth"
! #initialAppearance "Off to one side is a magician's booth, used in disappearing acts. The exterior is covered with painted gilt stars."
! #enterable Enterable
! #openable NotOpenable
! #modify (#objectData % #portability .~ FixedInPlace)
! done
tsv <- addRoom "Starry Vastness"
! done
tsv `isInsideFrom` tcr

insteadOf (ActionRule #entering) [theObject tmb] $ \_ -> do
Nothing <$ parseAction normalAction [] "in"
addThing "blue vinyl cushions"
! #modify (#namePlurality .= PluralNamed)
! #location (onThe b)
! done
pass

tamedTestMeWith :: [Text]
tamedTestMeWith = ["get in cage", "open cage", "get in cage", "z", "close cage", "out", "open cage", "get on pedestal",
"get off", "look", "enter booth", "out"]
disenchantmentBayTestMeWith :: [Text]
disenchantmentBayTestMeWith = ["examine case", "get rods", "open case", "get rods", "sit on bench", "take cushions", "get up"]
1 change: 1 addition & 0 deletions yaifl/yaifl.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -199,6 +199,7 @@ test-suite yaifl-test
other-modules:
Yaifl.Test.Chapter3.Bic
Yaifl.Test.Chapter3.Common
Yaifl.Test.Chapter3.DisenchantmentBay
Yaifl.Test.Chapter3.FirstNameBasis
Yaifl.Test.Chapter3.MidsummerDay
Yaifl.Test.Chapter3.PortRoyal
Expand Down

0 comments on commit ba7b0d0

Please sign in to comment.