module Main where import Data.Monoid import Data.String (fromString) import Language.English.Pluralize import Test.Hspec (<->) :: String -> String -> Spec x <-> y = it (x <> " should pluralize") $ let x'= pluralize (fromString x) in if x' == fromString y then return () :: IO () else error $ "expected " <> y <> " for " <> x <> " but got " <> show x' main = hspec $ do "sandwich" <-> "sandwiches" "roadie" <-> "roadies" "die" <-> "dice" "foo die" <-> "foo dice" "boat" <-> "boats" "cat" <-> "cats" "river" <-> "rivers" "box" <-> "boxes" "pitch" <-> "pitches" "daisy" <-> "daisies" "tooth" <-> "teeth" "mouse" <-> "mice" "oasis" <-> "oases" -- REGULAR -- Sibilant "kiss" <-> "kisses" "phase" <-> "phases" "dish" <-> "dishes" "massage" <-> "massages" "witch" <-> "witches" "judge" <-> "judges" -- Other "boy" <-> "boys" "girl" <-> "girls" "chair" <-> "chairs" -- NOUNS -- consonant "hero" <-> "heroes" "potato" <-> "potatoes" "volcano" <-> "volcanoes" -- foreign "canto" <-> "cantos" "hetero" <-> "heteros" "photo" <->"photos" "zero" <-> "zeros" "piano" <-> "pianos" "portico" <-> "porticos" "pro" <-> "pros" "quarto" <-> "quartos" "kimono" <-> "kimonos" -- in -y "cherry" <-> "cherries" "lady" <-> "ladies" "sky" <-> "skies" "soliloquy" <-> "soliloquies" "day" <-> "days" "monkey" <-> "monkeys" -- NON-REGULAR "bath" <-> "baths" "mouth" <-> "mouths" "calf" <-> "calves" "leaf" <-> "leaves" "knife" <-> "knives" "life" <-> "lives" "house" <-> "houses" "moth" <-> "moths" "proof" <-> "proofs" "dwarf" <-> "dwarves" "hoof" <-> "hooves" "elf" <-> "elfs" "staff" <-> "staffs" "turf" <-> "turfs" -- IRREGULAR "bison" <-> "bison" "buffalo" <-> "buffalo" "carp" <-> "carp" "cod" <-> "cod" "deer" <-> "deer" "duck" <-> "duck" "fish" <-> "fish" "moose" <-> "moose" "pike" <-> "pike" "salmon" <-> "salmon" "sheep" <-> "sheep" "shrimp" <-> "shrimp" "squid" <-> "squid" "trout" <-> "trout" "police" <-> "police" "ox" <-> "oxen" "child" <-> "children" "brother" <-> "brethren" -- Apophonic "foot" <-> "feet" "goose" <-> "geese" "louse" <-> "lice" "dormouse" <-> "dormice" "man" <-> "men" "woman" <-> "women" "mouse" <-> "mice" "tooth" <-> "teeth" "person" <-> "people" "penny" <-> "pennies" "alumna" <-> "alumnae" "index" <-> "indices" "matrix" <-> "matrices" "vertex" <-> "vertices" "axis" <-> "axes" "genesis" <-> "geneses" "nemesis" <-> "nemeses" "thesis" <-> "theses" "parenthesis" <-> "parentheses" "acropolis" <-> "acropoleis" "species" <-> "species" "series" <-> "series" "addendum" <-> "addenda" "agendum" <-> "agenda" "agenda" <-> "agendas" "curriculum" <-> "curricula" "data" <-> "datum" "forum" <-> "fora" "medium" <-> "media" "ovum" <-> "ova" "stadium" <-> "stadia" "stratum" <-> "strata" "alumnus" <-> "alumni" "corpus" <-> "corpora" "campus" <-> "campuses" "census" <-> "censuses" "focus" <-> "foci" "genus" <-> "genera" "prospectus" <-> "prospectuses" "radius" <-> "radii" "succubus" <-> "succubi" "stylus" <-> "styli" "syllabus" <-> "syllabi" "viscus" <-> "viscera" "fungus" <-> "fungi" "uterus" <-> "uteri" "octopus" <-> "octopuses" "platypus" <-> "platypuses" "status" <-> "statuses" -- greek "automaton" <-> "automata" "criterion" <-> "criteria" "phenomenon" <-> "phenomena" "polyhedron" <-> "polyhedra" "Atlas" <-> "Atlantes" "atlas" <-> "atlases" "stigma" <-> "stigmata" "stoma" <-> "stomata" "schema" <-> "schemas" "dogma" <-> "dogmas" "lemma" <-> "lemmas" "magma" <-> "magmas" "enema" <-> "enemas" --french "beau" <-> "beaux" "bureau" <-> "bureaux" "tableau" <-> "tableaux" "cello" <-> "celli" "cherub" <-> "cherubs" "canoe" <-> "canoes" "igloo" <-> "igloos" "aircraft" <-> "aircraft" "perch" <-> "perch" "motto" <-> "mottos" "city-state" <-> "city-states" "coat-of-arms" <-> "coats-of-arms"