{-# LANGUAGE MultiParamTypeClasses #-} {- Spatial Reference Frames An implementation of Thora Tenbrink, 2011. Reference frames of space and time in language, Journal of Pragmatics 43:704-722. The code is a simulation, providing an executable model to produce valid descriptions from situations. It will evolve into an ontology of spatial reference, specifying the conceptualizations in terms of roles. Contributions of the approach: - distinguishes external and internal relationships - represents absolute reference frames consistently with intrinsic and relative frames - includes dynamic situations - separates roles (such as providing a perspective) from properties and affordances (such as having an intrinsic orientation) - distinguishes spatial and discourse roles and abstracts these from concrete linguistic expressions - maps to existing approaches: Levinson 1996/2003 Herrmann 1990 Retz-Schmidt 1988 Pederson 2003 Talmy 2000 Grabowski 1999 Bohnemeyer? (nicht geprüft), Frank 1998. Formalization approach: - entities only exist in situations they always have a position and can have an orientation and/or motion - box, room, wall, town, country, place: -o -m - chair, queue, river: +o -m - ball, wheel: -o +m - person, mouse, car: +o +m - 2 kinds of cognitive roles filled by entities in a situation discourse roles: speaker, addressee, participant (corresponding to grammatical first, second, third person) spatial roles: locatum, relatum, perspective (optionally with origin) To Do: - try 3 step role filling as mappings (from empty to filled situations to discourse roles to spatial roles) - or reversed? start with sentence slots, fill them by spatial roles, then by entities - or generate possible combinations of roles and situations? - deal with names vs nouns - produce multiple sentences to capture alternatives like encounter, directional, etc.? - rethink 13 and 18, introduce inverse orientation (rather than inverse perspective, which is wrong) - check: which roles are actually used in computations! - test with 1d cases - extend to 3d - tie to DOLCE / GUM - extend to multiple fillers per role - test with other languages (c) Werner Kuhn Last modified: 9 Mar 2011 (WK) -} module SpatialReference where -- positions as individual raster cells type Position = (Int, Int) outside = (-9,-9) -- dummy value, never accessed -- footprints as sets of positions type Footprint = [Position] -- directions as free (!) unit vectors type Direction = (Int, Int) -- meaningful direction terms to use in the code none, forward, backward, right, left:: Direction none = (0,0) forward = (0,1) backward = (0,-1) right = (1,0) left = (-1,0) invert :: Direction -> Direction invert (0,0) = (0,0) invert (0,1) = (0,-1) invert (1,0) = (-1,0) invert (-1,0) = (1,0) -- the direction from a position to another fromTo :: Position -> Position -> Direction fromTo p1 p2 = (signum (fst p2 - fst p1), signum (snd p2 - snd p1)) -- the first direction seen from the second relativeTo :: Direction -> Direction -> Direction relativeTo d1 d2 = (snd d2 * fst d1 - fst d2 * snd d1, fst d2 * fst d1 + snd d2 * snd d1) -- the view taken of a situation data View = Field | Object deriving Eq ---------------------------------------------------------------------- -- entities -- position, orientation, motion defined in the local (situation) system data Entity = Entity { noun :: String, position :: Position, footprint :: Footprint, orientation :: Direction, motion :: Direction} deriving (Eq, Show) box75 = Entity {noun = "box ", position = (7,5), footprint = [(7,5)], orientation = none, motion = none} box73 = Entity {noun = "box ", position = (7,3), footprint = [(7,3)], orientation = none, motion = none} box65 = Entity {noun = "box ", position = (6,5), footprint = [(6,5)], orientation = none, motion = none} box95 = Entity {noun = "box ", position = (9,5), footprint = [(9,5)], orientation = none, motion = none} person55 = Entity {noun = "person ", position = (5,5), footprint = [(5,5)], orientation = right, motion = none} person75 = Entity {noun = "person ", position = (7,5), footprint = [(7,5)], orientation = right, motion = none} person73 = Entity {noun = "person ", position = (7,3), footprint = [(7,3)], orientation = right, motion = none} chair55 = Entity {noun = "chair ", position = (5,5), footprint = [(5,5)], orientation = right, motion = none} external = Entity {noun = "person ", position = outside, footprint = [outside], orientation = right, motion = none} ball75 = Entity {noun = "ball ", position = (7,5), footprint = [(7,5)], orientation = none, motion = none} wall105 = Entity {noun = "wall ", position = (10,5), footprint = [(10,4), (10,5), (10,6)], orientation = none, motion = none} car5565 = Entity {noun = "car ", position = (5,5), footprint = [(5,5), (6,5)], orientation = right, motion = none} room6575 = Entity {noun = "room ", position = (6,5), footprint = [(6,5), (7,5)], orientation = none, motion = none} country6575 = Entity {noun = "country ", position = (6,5), footprint = [(6,5), (7,5)], orientation = forward, motion = none} town75 = Entity {noun = "town ", position = (7,5), footprint = [(7,5)], orientation = none, motion = none} wheel93 = Entity {noun = "wheel ", position = (9,3), footprint = [(9,3)], orientation = forward, motion = forward} river7595 = Entity {noun = "river ", position = (7,5), footprint = [(7,5),(8,5),(9,5)], orientation = right, motion = none} peter95 = Entity {noun = "peter ", position = (9,5), footprint = [(9,5)], orientation = none, motion = none} mary75 = Entity {noun = "mary ", position = (7,5), footprint = [(7,5)], orientation = none, motion = none} queue7595 = Entity {noun = "queue ", position = (7,5), footprint = [(7,5),(8,5),(9,5)], orientation = right, motion = none} ---------------------------------------------------------------------- -- situations -- fill spatial and discourse roles with entities and their aspects -- examples are taken from COSIT 2011 submission and numbered accordingly -- note that s1 to s13 (and possibly later) do NOT need the knowledge about the origin to compute the direction - what follows from this? -- participants are only the relevant entities that have no other role data Situation = Situation {locatum :: !Entity, relatum :: !Entity, perspective :: !Direction, origin :: Position, speaker :: !Entity, addressee :: !Entity, participants :: [Entity]} deriving (Eq, Show) s1 = Situation {locatum = box75, relatum = person55, perspective = orientation person55, origin = position person55, speaker = person55, addressee = external, participants = []} -- locatum = participant, relatum = speaker, origin = speaker 311 s2 = Situation {locatum = box75, relatum = person55, perspective = orientation person55, origin = position person55, speaker = external, addressee = person55, participants = []} -- locatum = participant, relatum = addressee, origin = addressee 322 s3 = Situation {locatum = box75, relatum = chair55, perspective = orientation chair55, origin = position chair55, speaker = external, addressee = external, participants = []} -- relatum = participant, origin = participant 333 s4 = Situation {locatum = person75, relatum = person55, perspective = orientation person55, origin = position person55, speaker = person75, addressee = person55, participants = []} -- locatum = speaker, relatum = addressee 122 s5 = Situation {locatum = person75, relatum = person55, perspective = orientation person55, origin = position person55, speaker = person55, addressee = person75, participants = []} -- locatum = addressee, relatum = speaker 211 s6 = Situation {locatum = box73, relatum = ball75, perspective = orientation person55, origin = position person55, speaker = person55, addressee = external, participants = []} -- relatum = participant, origin = speaker 331 s7 = Situation {locatum = box73, relatum = ball75, perspective = orientation person55, origin = position person55, speaker = person75, addressee = person55, participants = []} -- relatum = participant, origin = addressee 332 s8 = Situation {locatum = box73, relatum = ball75, perspective = orientation chair55, origin = position chair55, speaker = external, addressee = external, participants = []} -- origin = participant 333 s9 = Situation {locatum = person73, relatum = ball75, perspective = orientation person55, origin = position person55, speaker = person73, addressee = person55, participants = []} -- locatum = speaker, relatum = participant, origin = addressee 132 s10 = Situation {locatum = person73, relatum = ball75, perspective = orientation person55, origin = position person55, speaker = person55, addressee = person73, participants = []} -- locatum = addressee, relatum = participant, origin = speaker 231 s11 = Situation {locatum = box73, relatum = person75, perspective = orientation person55, origin = position person55, speaker = person75, addressee = person55, participants = []} -- locatum = participant, relatum = speaker, origin = addressee 312 s12 = Situation {locatum = box73, relatum = person75, perspective = orientation person55, origin = position person55, speaker = person55, addressee = person75, participants = []} -- locatum = participant, relatum = addressee, origin = speaker 321 s13a = Situation {locatum = box65, relatum = ball75, perspective = invert (orientation person55), origin = position person55, speaker = person55, addressee = external, participants = []} -- locatum = participant, relatum = participant, origin = speaker 331 s13b = Situation {locatum = box95, relatum = ball75, perspective = orientation person55, origin = position person55, speaker = person55, addressee = external, participants = []} -- locatum = participant, relatum = participant, origin = speaker 331 s14 = Situation {locatum = box95, relatum = ball75, perspective = none, origin = outside, speaker = external, addressee = external, participants = []} -- locatum = participant, relatum = participant 330 --s15 = Situation {locatum = box95, relatum = ball2wall, perspective = none, origin = position ball75, speaker = external, addressee = external, participants = [wall105]} -- locatum = participant, relatum = participant 330 s16 = Situation {locatum = box75, relatum = car5565, perspective = orientation car5565, origin = position car5565, speaker = external, addressee = external, participants = []} -- locatum = participant, relatum = participant, origin = participant 333 s17 = Situation {locatum = box65, relatum = car5565, perspective = orientation car5565, origin = position car5565, speaker = external, addressee = external, participants = []} -- locatum = participant, relatum = participant, origin = participant 333 s18 = Situation {locatum = box75, relatum = room6575, perspective = invert (orientation person55), origin = position person55, speaker = person55, addressee = external, participants = []} -- locatum = participant, relatum = participant, origin = speaker 331 s20 = Situation {locatum = town75, relatum = country6575, perspective = none, origin = outside, speaker = external, addressee = external, participants = []} -- locatum = participant, relatum = participant 330 -- s22 is a 3d case, not treated s23 = Situation {locatum = box95, relatum = ball75, perspective = motion wheel93, origin = outside, speaker = external, addressee = external, participants = []} -- locatum = participant, relatum = participant, origin = participant 333 s24 = Situation {locatum = box95, relatum = ball75, perspective = orientation river7595, origin = position ball75, speaker = external, addressee = external, participants = []} s25 = Situation {locatum = peter95, relatum = mary75, perspective = orientation queue7595, origin = position mary75, speaker = external, addressee = external, participants = []} ---------------------------------------------------------------------- -- analysis -- functions to analyze situations -- the direction from relatum to locatum direction :: Situation -> Direction direction s = fromTo (position (relatum s)) (position (locatum s)) -- the direction seen from the perspective relativeDirection :: Situation -> Direction relativeDirection s = if (absolute s) || (direction s == none) then direction s else (relativeTo (direction s) (perspective s)) -- the labels for reference frames absolute, intrinsic, internal, static :: Situation -> Bool absolute s = (perspective s == none) intrinsic s = (perspective s == orientation (relatum s)) internal s = ((position (locatum s)) `elem` (footprint (relatum s))) static s = (motion (locatum s) == none) && (motion (relatum s) == none) ---------------------------------------------------------------------- -- sentences -- generating English sentences from situations -- the subject and verb -- in field or object view subject :: Situation -> View -> String subject s v = if speaker s == locatum s then if v == Object then "I am " else "There is me " else if addressee s == locatum s then if v == Object then "You are " else "There is you " else if v == Object then "The " ++ noun (locatum s) ++ "is " else "There is a " ++ noun (locatum s) -- the predicate -- naming the region in a given direction -- intrinsic and relative use the same expressions! predicate :: Direction -> Situation -> String predicate (0,1) s = if (absolute s) then if (internal s) then "in the north of " else "north of " else if (internal s) then "in the front of " else "in front of " predicate (1,0) s = if (absolute s) then if (internal s) then "in the east of " else "east of " else if (internal s) then "on the right side of " else "to the right of " predicate (0,-1) s = if (absolute s) then if (internal s) then "in the south of " else "south of " else if (internal s) then "in the back of " else "behind " predicate (-1,0) s = if (absolute s) then if (internal s) then "in the west of " else "west of " else if (internal s) then "on the left side of " else "to the left of " -- the object object :: Situation -> String object s = if (speaker s) == (relatum s) then "me" else if (addressee s == relatum s) then "you" else "the " ++ noun (relatum s) describe :: Situation -> View -> String describe s v = subject s v ++ predicate (relativeDirection s) s ++ object s