module Main where import Materials import Items import Language import LanguageSelect data Sample = Sample Sentence [(Language, String)] samples :: [Sample] samples = let hit = adverb AV_quickly $ adverb AV_silently $ verb V_hit orc = adjective AJ_dirty $ adjective (AJ_MATERIAL Wood) $ noun N_orc orcs = noun_count (Count 2) orc item = unusual_material Silver make_sword is_not = negated $ verb V_is an_orc = noun_count Indefinite $ noun N_orc in [ Sample (BasicSentence you hit orc) [ (English, "You quickly and silently hit the dirty, wooden orc."), (Dutch, "Je raakt de vieze houten ork snel en stil.") ], Sample (BasicSentence orc hit you) [ (English, "The dirty, wooden orc quickly and silently hits you."), (Dutch, "De vieze houten ork raakt je snel en stil.") ], Sample (BasicSentence you hit orcs) [ (English, "You quickly and silently hit two dirty, wooden orcs."), (Dutch, "Je raakt twee vieze houten orken snel en stil.") ], Sample (BasicSentence orcs hit you) [ (English, "Two dirty, wooden orcs quickly and silently hit you."), (Dutch, "Twee vieze houten orken raken je snel en stil.") ], Sample (BasicSentence you (verb V_hit) (item_name item)) [ (English, "You hit the silver sword."), (Dutch, "Je raakt het zilveren zwaard.") ], Sample (BasicSentence that is_not an_orc) [ (English, "That isn't an orc."), (Dutch, "Dat is geen ork.") ], Sample (BasicSentence that is_not orc) [ (English, "That isn't the dirty, wooden orc."), (Dutch, "Dat is de vieze houten ork niet.") ], Sample (BasicSentence that hit an_orc) [ (English, "That quickly and silently hits an orc."), (Dutch, "Dat raakt een ork snel en stil.") ], Sample (BasicSentence an_orc (negated hit) you) [ (English, "An orc quickly and silently doesn't hit you."), (Dutch, "Een ork raakt je niet snel en stil.") ] ] test_sample :: Sample -> IO () test_sample (Sample s ls) = do sequence_ $ map test' ls where test' (lang, str) = do if transSentence lang s /= str then putStrLn ("FAIL: expected '" ++ str ++ "'; got '" ++ (transSentence lang s) ++ "'") else return () main :: IO () main = do sequence_ $ map test_sample samples