module Language.English ( sentence_to_English, noun_to_English ) where import Language import Util.Text import Materials import BodyParts data Plural = Single | Plural data Person = First | Second | Third sentence_to_English :: Sentence -> String sentence_to_English (BasicSentence subj v obj) = let plural = isPlural (getCount subj) person = getPerson (getNoun subj) in capitalize $ join_spaced [ npEnglish subj , advsEnglish (getAdverbs v) , tverb person plural (getVerb v) (getNegation v) , npEnglish obj ] ++ "." sentence_to_English (DescriptiveSentence subj advs adjs) = let plural = isPlural (getCount subj) person = getPerson (getNoun subj) in capitalize $ join_spaced [ npEnglish subj , tverb person plural V_is Is , advsEnglish advs , adjsEnglish adjs ] ++ "." sentence_to_English (DirQuestion v obj) = capitalize $ join_spaced [ advsEnglish (getAdverbs v) , tverb First Single (getVerb v) Is -- FIXME: wrong for V_is ("be") , npEnglish obj , "in which direction?" ] noun_to_English :: NounPhrase -> String noun_to_English = npEnglish isPlural :: Numeric -> Plural isPlural None = Plural isPlural Definite = Single isPlural Indefinite = Single isPlural (Count n) = if n == 1 then Single else Plural getPerson :: Noun -> Person getPerson PN_you = Second getPerson _ = Third npEnglish :: NounPhrase -> String npEnglish (NounPhrase n None as) = join_spaced ["no", adjsEnglish as, pluralNoun n] npEnglish (NounPhrase n Definite as) | isPronoun n = join_spaced [adjsEnglish as, tnoun n] npEnglish (NounPhrase n Definite as) = join_spaced ["the", adjsEnglish as, tnoun n] npEnglish (NounPhrase n Indefinite as) = add_article $ join_spaced [adjsEnglish as, tnoun n] npEnglish (NounPhrase n (Count 1) as) = join_spaced ["one", adjsEnglish as, tnoun n] npEnglish (NounPhrase n (Count c) as) = join_spaced [numeral c, adjsEnglish as, pluralNoun n] -- Translate a list of adjectives that modify a noun. adjsEnglish :: [Adjective] -> String adjsEnglish as = join_text ", " (map adj as) -- Translate a list of adverbs that modify a verb. advsEnglish :: [Adverb] -> String advsEnglish as = join_text2 ", " " and " (map adv as) add_article :: String -> String add_article [] = [] add_article s = get_article s ++ s get_article :: String -> String get_article [] = [] get_article (c : _) = case c of 'a' -> "an " 'e' -> "an " 'i' -> "an " 'o' -> "an " 'u' -> "an " _ -> "a " -- Individual word translations adj :: Adjective -> String adj AJ_dirty = "dirty" adj AJ_locked = "locked" adj AJ_broken = "broken" adj AJ_closed = "closed" adj AJ_empty = "empty" adj AJ_strange = "strange" adj AJ_smelly = "smelly" adj AJ_huge = "huge" adj AJ_large = "large" adj AJ_small = "small" adj AJ_tiny = "tiny" adj AJ_hairy = "hairy" adj AJ_bald = "bald" adj AJ_fast = "fast" adj AJ_slow = "slow" adj AJ_red = "red" adj AJ_green = "green" adj AJ_brown = "brown" adj (AJ_MATERIAL Iron) = "iron" adj (AJ_MATERIAL Silver) = "silver" adj (AJ_MATERIAL Wood) = "wooden" adj (AJ_MATERIAL Glass) = "glass" adj (AJ_MATERIAL Liquid) = "liquid" adj (AJ_MATERIAL Leather) = "leather" adj (AJ_MATERIAL Stone) = "stone" adj (AJ_MATERIAL Dirt) = "dirt" adv :: Adverb -> String adv AV_quickly = "quickly" adv AV_silently = "silently" adv AV_already = "already" tnoun :: Noun -> String tnoun PN_you = "you" tnoun PN_it = "it" tnoun PN_that = "that" tnoun N_sword = "sword" tnoun N_helmet = "helmet" tnoun N_vial = "vial" tnoun N_orc = "orc" tnoun N_cave_monster = "cave monster" tnoun N_door = "door" tnoun N_doorway = "doorway" tnoun N_direction = "direction" tnoun (N_BODY Torso) = "torso" tnoun (N_BODY Waist) = "waist" tnoun (N_BODY Neck) = "neck" tnoun (N_BODY Head) = "head" tnoun (N_BODY Ear) = "ear" tnoun (N_BODY Shoulder) = "shoulder" tnoun (N_BODY Arm) = "arm" tnoun (N_BODY Hand) = "hand" tnoun (N_BODY Finger) = "finger" tnoun (N_BODY Leg) = "leg" tnoun (N_BODY Foot) = "foot" pluralNoun :: Noun -> String pluralNoun PN_you = "you" pluralNoun PN_it = "they" pluralNoun PN_that = "those" pluralNoun (N_BODY Foot) = "feet" -- Default rule pluralNoun n = tnoun n ++ "s" tverb :: Person -> Plural -> Verb -> Negation -> String tverb First Single V_is Is = "am" tverb First Single V_is IsNot = "am not" tverb Third Single V_is Is = "is" tverb Third Single V_is IsNot = "isn't" tverb _ _ V_is Is = "are" tverb _ _ V_is IsNot = "aren't" tverb Third Single V_hit Is = "hits" tverb _ _ V_hit Is = "hit" tverb Third Single V_kill Is = "kills" tverb _ _ V_kill Is = "kill" tverb Third Single V_open Is = "opens" tverb _ _ V_open Is = "open" tverb Third Single V_close Is = "closes" tverb _ _ V_close Is = "close" -- Default negation rule (Plural to force "hits" -> "doesn't hit") tverb pr _ v IsNot = "doesn't " ++ (tverb pr Plural v Is) numeral :: Int -> String numeral 0 = "zero" numeral 1 = "one" numeral 2 = "two" numeral 3 = "three" numeral 4 = "four" numeral 5 = "five" numeral 6 = "six" numeral 7 = "seven" numeral 8 = "eight" numeral 9 = "nine" numeral 10 = "ten" numeral 11 = "eleven" numeral 12 = "twelve" numeral 13 = "thirteen" numeral 14 = "fourteen" numeral 15 = "fifteen" numeral 16 = "sixteen" numeral 17 = "seventeen" numeral 18 = "eighteen" numeral 19 = "nineteen" numeral 20 = "twenty" numeral 30 = "thirty" numeral 40 = "forty" numeral 50 = "fifty" numeral 60 = "sixty" numeral 70 = "seventy" numeral 80 = "eighty" numeral 90 = "ninety" numeral n | n > 20 && n < 100 = let singles = n `mod` 10 in numeral (n - singles) ++ "-" ++ numeral singles numeral n | n < 1000 && n `mod` 100 == 0 = numeral (n `div` 100) ++ " hundred" numeral n | n < 10000 && n `mod` 1000 == 0 = numeral (n `div` 1000) ++ " thousand" -- Default: just print the number numeral n = show n