]> Git — Sourcephile - julm/worksheets.git/blob - tests/Language/FrenchSpec.hs
update
[julm/worksheets.git] / tests / Language / FrenchSpec.hs
1 {-# LANGUAGE OverloadedLists #-}
2 {-# LANGUAGE OverloadedStrings #-}
3
4 module Language.FrenchSpec where
5
6 import Data.ByteString.Builder qualified as ByteString.Builder
7 import Data.Char qualified as Char
8 import Data.GenValidity.Map ()
9 import Data.GenValidity.Sequence ()
10 import Data.GenValidity.Set ()
11 import Data.GenValidity.Text ()
12 import Data.List qualified as List
13 import Data.Map.Strict qualified as Map
14 import Data.Set qualified as Set
15 import Data.Text qualified as Text
16 import Data.Text.Encoding qualified as Text
17 import Data.Text.Lazy.Encoding qualified as Text.Lazy
18 import Data.Text.Short qualified as ShortText
19 import Data.Validity.Map ()
20 import Data.Validity.Set ()
21 import Data.Validity.Text ()
22 import Language
23 import Language.French qualified as French
24 import Language.Pronunciation (ExampleLiteral (..), Lexeme (..), Rule (..), RuleLexemes, after, before, begining, ending, meaning, occurence, rule, silent, word)
25 import Language.Pronunciation qualified as Pron
26 import Paths_worksheets qualified as Self
27 import System.Directory qualified as IO
28 import System.FilePath (joinPath, pathSeparator, (<.>), (</>))
29 import System.FilePath.Posix qualified as File
30 import System.IO qualified as IO
31 import Test.Syd
32 import Text.Blaze.Html5.Attributes qualified as HA
33 import Utils.Pronunciation qualified as Pron
34 import Utils.Tests
35 import Wiktionary qualified
36 import Worksheets.Utils.HTML (Html, className, classes, cm, styles, (!))
37 import Worksheets.Utils.HTML qualified as HTML
38 import Worksheets.Utils.IPA qualified as IPA
39 import Worksheets.Utils.Paper qualified as Paper
40 import Worksheets.Utils.Prelude
41 import Worksheets.Utils.SQL qualified as SQL
42 import Prelude (error, even, mod)
43
44 {-
45 instance IsString Rule where
46 fromString s = rule {ruleLexemes = fromString s}
47 [ ful "de" := single "də" ["de" & occurence]
48 , inf "'" := single "" []
49 , inf "-" := single "" []
50 , inf "," := single "" []
51 , inf "?" := single "" []
52 , inf "!" := single "" []
53 , inf borderLeftText := single "" []
54 , inf borderRightText := single "" []
55
56 , inf "demi" := single "dəmi" ["demi" & occurence]
57 , -- , inf "amb" := single "ɑ̃b" ["amb" & occurence, "ulance"]
58 -- , inf "amp" := single "ɑ̃p" ["amp" & occurence, "oule"]
59 -- , inf "amph" := single "ɑ̃f" ["amph" & occurence, "ithéâtre"]
60 -- , inf "an" := multi
61 -- [ [PronContextBeforeBorder] := LexemePron{lexemePronunciation="ɑ̃", lexemeExample=["pl", "an" & occurence]}
62 -- , [PronContextBeforeAnyVowel] := LexemePron{lexemePronunciation="an", lexemeExample=["an" & occurence, "imal"]}
63 -- , [PronContextBeforeAny] := LexemePron{lexemePronunciation="ɑ̃", lexemeExample=["an" & occurence, "tilope"]}
64 -- ]
65 , -- , inf "coin" := single "kwɛ̃" ["coin" & occurence, "cer"]
66
67 , -- , inf "im"
68 -- := multi
69 -- [ [PronContextBeforeBorder] := LexemePron{lexemePronunciation = "", lexemeExample = }
70 -- , [PronContextBeforeAnyVowel] := LexemePron{lexemePronunciation = "im", lexemeExample = ["im" & occurence, "ortel"]}
71 -- , [PronContextBeforeAny] := LexemePron{lexemePronunciation = "ɛ̃", lexemeExample = ["im" & occurence, "primer"]}
72 -- ]
73 , -- , inf "in" := single "ɛ̃" ["merl", "in" & occurence]
74 -- , inf "ina" := single "ina" ["ord", "ina" & occurence, "teur"]
75 -- , inf "ine" := single "in" ["rout", "ine" & occurence]
76 -- , inf "inent" := single "in" ["dess", "inent" & occurence]
77 -- , inf "iner" := single "inɛʁ" ["iner" & occurence, "tie"]
78 -- , inf "inex" := single "inɛgz" ["inex" & occurence, "istant"]
79 -- , inf "inexp" := single "inɛksp" ["inexp" & occurence, "licable"]
80 -- , inf "inima" := single "inima" ["inima" & occurence, "ginable"]
81 -- , inf "inimi" := single "inimi" ["inimi" & occurence, "table"]
82 -- , inf "inimp" := single "inimp" ["inimp" & occurence, "ortant"]
83 -- , inf "ininf" := single "inɛ̃" ["ininf" & occurence, "lammation"]
84 -- , inf "inint" := single "inɛ̃t" ["inint" & occurence, "éressant"]
85 -- , inf "inn" := single "in" ["inn" & occurence, "ocent"]
86 -- , inf "ino" := single "ino" ["ino" & occurence, "dore"]
87 -- , inf "inu" := single "inu" ["inu" & occurence, "tile"]
88 -- , inf "ix" := single "iks" ["phén", "ix" & occurence]
89 -- , inf "gine" := single "ʒin" ["an", "gine" & occurence]
90 -- , inf "era" := single "əʁa" ["s", "era" & occurence]
91 -- , inf "erai" := single "əʁɛ" ["s", "erai" & occurence]
92 , inf "era" :=
93 multi
94 [ [PronContextBeforeAnyVowel] := LexemePron{lexemePronunciation = "əʁ", lexemeExample = ["mer" & occurence, "ingue"]}
95 , [PronContextBeforeAny] := LexemePron{lexemePronunciation = "ɛʁ", lexemeExample = ["mer" & occurence, "le"]}
96 ]
97 , inf "erin" := single "əʁɛ̃" ["m", "erin" & occurence, "gue"]
98 , inf "s" :=
99 multi
100 [ [PronContextBeforeAnyVowel] := LexemePron{lexemePronunciation = "z", lexemeExample = ["ti", "s" & occurence, "ane"]}
101 , [PronContextBeforeAnySemiVowel] := LexemePron{lexemePronunciation = "z", lexemeExample = ["pari", "s" & occurence, "ienne"]}
102 , [PronContextBeforeAny] := LexemePron{lexemePronunciation = "s", lexemeExample = ["s", "a" & occurence]}
103 ]
104 , -- , inf "shirt" := single "ʃœʁt" ["shirt" & occurence]
105 , -- , inf "teau" := single "to" ["teau" & occurence]
106 -- , inf "ti" := single "ti" ["ti" & occurence, "gre"]
107 , pre "ukulele" := single "jukulele" ["ukulele" & occurence]
108 , -- , inf "ui" := single "ɥi" ["ling", "ui" & occurence, "stique"]
109 , pre "abrivent" := single "abʁivɑ̃" ["abrivent" & occurence]
110 , pre "adjuvent" := single "adʒyvɑ̃" ["adjuvent" & occurence]
111 , pre "antivent" := single "ɑ̃tivɑ̃" ["antivent" & occurence]
112 , pre "auvent" := single "ovɑ̃" ["auvent" & occurence]
113 , pre "avent" := single "avɑ̃" ["avent" & occurence]
114 , pre "aï" := single "ai" ["c", "aï" & occurence, "man"]
115 , pre "bavent" := single "bavɑ̃" ["bavent" & occurence]
116 , pre "boutavent" := single "butavɑ̃" ["boutavent" & occurence]
117 , pre "bouvent" := single "buvɑ̃" ["bouvent" & occurence]
118 , pre "bénévent" := single "benevɑ̃" ["bénévent" & occurence]
119 , pre "connivent" := single "konivɑ̃" ["connivenr" & occurence]
120 , pre "contrevent" := single "kɔ̃tʁəvɑ̃" ["contrevent" & occurence]
121 , pre "convent" := single "kɔ̃vɑ̃" ["convent" & occurence]
122 , pre "couvent" := single "kuvɑ̃" ["couvent" & occurence]
123 , pre "couvents" := single "kuvɑ̃" ["couvents" & occurence]
124 , pre "engoulevent" := single "ɑ̃gulvɑ̃" ["engoulevent" & occurence]
125 , pre "fervent" := single "fɛʁvɑ̃" ["fervent" & occurence]
126 , pre "frévent" := single "fʁevɑ̃" ["frévent" & occurence]
127 , pre "heurtevent" := single "œʁtəvɑ̃" ["heurtevent" & occurence]
128 , pre "her" := single "ɛʁ" ["her" & occurence, "be"]
129 , pre "hi" := single "i" ["hi" & occurence, "ver"]
130 , pre "ill" := single "il" ["ill" & occurence, "étrisme"]
131 , pre "jack" := single "dʒak" ["jack" & occurence]
132 , pre "jazz" := single "dʒaz" ["jazz" & occurence]
133 , pre "montsurvent" := single "mɔ̃syʁvɑ̃" ["montsurvent" & occurence]
134 , -- , pre "ni" := single "ni" ["ni" & occurence, "ais"]
135 pre "niai" := single "njɛ" ["niai" & occurence, "s"]
136 , pre "paravent" := single "paʁavɑ̃" ["paravent" & occurence]
137 , pre "sen" :=
138 multi
139 [ [PronContextBeforeAny] := LexemePron{lexemePronunciation = "sɑ̃", lexemeExample = ["sen" & occurence, "t"]}
140 , [PronContextBeforeAnyVowel] := LexemePron{lexemePronunciation = "sen", lexemeExample = ["sen" & occurence, "a"]}
141 -- , inf "a" := LexemePron{lexemePronunciation="sen", lexemeExample=["sen" & occurence, "a"]}
142 -- , inf "e" := LexemePron{lexemePronunciation="sən", lexemeExample=["sen" & occurence, "estre"]}
143 -- , inf "i" := LexemePron{lexemePronunciation="sen", lexemeExample=["sen" & occurence, "ior"]}
144 -- , inf "o" := LexemePron{lexemePronunciation="sen", lexemeExample=["Sen" & occurence, "oueix"]}
145 -- , inf "u" := LexemePron{lexemePronunciation="sen", lexemeExample=[]}
146 ]
147 , pre "souvent" := single "suvɑ̃" ["souvent" & occurence]
148 , pre "taillevent" := single "tɑjvɑ̃" ["taillevent" & occurence]
149 , pre "tournevent" := single "tuʁnəvɑ̃" ["tournevent" & occurence]
150 , pre "vent" := single "vɑ̃" ["vent" & occurence]
151 , pre "virevent" := single "viʁvɑ̃" ["virevent" & occurence]
152 , pre "volvent" := single "vɔlvɑ̃" ["volvent" & occurence]
153 , pre "évent" := single "evɑ̃" ["évent" & occurence]
154 , pre "œ" := single "œ" ["œ" & occurence, "uf"]
155 , pre "fier" := single "fjɛʁ" ["fier" & occurence]
156 , pre "tier" := single "tjɛʁ" ["tier" & occurence]
157
158 ]
159 & list
160 & foldMap (\(ks, v) -> [(k, v) | k <- ks])
161 & mapFromListCheckingDuplicates
162 where
163 single pron exs =
164 Map.singleton PronContextBeforeAny $ LexemePron{lexemePronunciation = pron, lexemeExample = exs}
165 multi l =
166 l
167 & list
168 & foldMap (\(ks, v) -> [(k, v) | k <- ks])
169 & mapFromListCheckingDuplicates
170 -}
171
172 spec :: HasCallStack => Spec
173 spec = do
174 -- Pron.lexerRender $ French.pronunciationDict
175 describe "pronunciation" do
176 -- describe "decomposition" do
177 -- forM_ sentences \sentence ->
178 -- Pron.pronunciationDecompositionTest French.pronunciationDict $ sentence & Text.unpack
179 -- describe "result" do
180 -- forM_ sentences \sentence ->
181 -- Pron.pronunciationResultTest French.pronunciationDict $ sentence & Text.unpack
182 describe "parser" do
183 Pron.pronunciationParserTest pronunciationRules sentences
184
185 {-
186 withoutRetries do
187 withoutTimeout do
188 around (\k -> SQL.withConnection "data/langs/français/kaikki/wiktionary=fr.lang=fr.sqlite3" k) do
189 outDB <- goldenPath "wiktionary" "sqlite"
190 outDBExists <- IO.doesFileExist outDB & liftIO
191 when (outDBExists) do
192 IO.removeFile outDB & liftIO
193 aroundWith
194 ( \k wiktConn -> do
195 SQL.withConnection outDB \outConn ->
196 k (wiktConn, outConn)
197 )
198 do
199 it "check-against-wiktionary" \(wiktConn, outConn) -> do
200 SQL.execute_ outConn $ "PRAGMA journal_mode = OFF"
201 SQL.execute_ outConn $ "PRAGMA synchronous = OFF"
202 SQL.execute_ outConn $ "CREATE TABLE IF NOT EXISTS results (exprLit TEXT NON NULL, wiktBroad TEXT NON NULL, wiktBroadSegments TEXT NON NULL, synthBroad TEXT NON NULL, synthExplain TEXT NON NULL)"
203 SQL.execute_ outConn $ "CREATE INDEX results__exprLit ON results (exprLit);"
204 SQL.execute_ outConn $ "CREATE INDEX results__wiktBroad ON results (wiktBroad);"
205 SQL.execute_ outConn $ "CREATE INDEX results__synthBroad ON results (synthBroad);"
206 SQL.execute_ outConn $ "CREATE TABLE IF NOT EXISTS errors (exprId INTEGER NON NULL, exprLit TEXT NON NULL, error TEXT NON NULL)"
207 SQL.fold
208 wiktConn
209 "SELECT id,word,sounds FROM wiktionary WHERE lang_code='fr' LIMIT 1000"
210 ()
211 (1 :: Int)
212 \ !i
213 ( exprId :: Int
214 , maybeWord :: Maybe Text
215 , sounds :: [Wiktionary.Sound]
216 ) -> do
217 case maybeWord of
218 Nothing -> return ()
219 Just exprLit ->
220 case exprLit & Pron.run French.pronunciationRules of
221 Left err -> do
222 SQL.execute
223 outConn
224 "INSERT INTO errors (exprId, exprLit, error) VALUES (?,?,?)"
225 ( exprId
226 , exprLit
227 , err & pShowNoColor
228 )
229 Right lexemes -> do
230 let synthExplain = lexemes <&> (\Pron.Pron{pronInput, pronRule} -> Pron.chars pronInput <> " → " <> show (Pron.rulePron pronRule)) & List.intercalate "; "
231 let synthBroad = lexemes & foldMap (Pron.pronRule >>> Pron.rulePron >>> Pron.pronunciationText)
232 forM_ sounds \Wiktionary.Sound{..} -> do
233 -- IO.hPrint IO.stderr (i, ident::Int, maybeWord)
234 case sound_ipa of
235 Just (IPA.IPAPhons exprIPAs) -> do
236 forM_ exprIPAs \case
237 IPA.IPAPhonemic exprBroad -> do
238 when (i `mod` 5000 == 0) do
239 IO.hPrint IO.stderr (i, exprLit, exprBroad)
240 SQL.execute
241 outConn
242 "INSERT INTO results(exprLit, wiktBroad, wiktBroadSegments, synthBroad, synthExplain) VALUES(?,?,?,?,?);"
243 ( exprLit
244 , exprBroad & IPA.ipaWordsToText Nothing
245 , exprBroad & IPA.dropSupraSegmentalFeatures & IPA.ipaWordsToText Nothing
246 , synthBroad
247 , synthExplain
248 ) -- & traceShowId
249 IPA.IPAPhonError (_errMsg, _err) -> return ()
250 _ -> return ()
251 _ -> return ()
252 return (i + 1)
253 return @IO ()
254 -}
255
256 {-
257 mangleSupraSegmentalFeatures :: [IPA.Syllable []] -> [[IPA.Segment]]
258 mangleSupraSegmentalFeatures = \case
259 [] -> []
260 IPA.Syllable syl : ts -> syl : mangleSupraSegmentalFeatures ts
261 IPA.WithSuprasegmentalFeature IPA.Linking syl : ts ->
262 case mangleSupraSegmentalFeatures ts of
263 [] -> [dropSupraSegmentalFeatures syl]
264 x : xs -> (dropSupraSegmentalFeatures syl <> x) : xs
265 IPA.WithSuprasegmentalFeature _feat syl : xs ->
266 mangleSupraSegmentalFeatures (syl : xs)
267 -}
268
269 -- cardsHtml "syllabes" $ French.syllablesTable & French.syllablesTableToHTML
270
271 sentences :: Map Pron.InputLexemes Pron.Pronunciation
272 sentences =
273 [ -- [ ["aiguille"]
274 -- , ["ail"]
275 -- , ["aimer"]
276 -- , ["ampoules"]
277 -- , ["couvent"{exampleLiteralMeaning = "couver"}]
278 -- , ["couvent"{exampleLiteralMeaning = "monastère"}]
279 -- , ["papillon"]
280 -- ] :: [[]]
281 pronunciationRules
282 & Pron.examples
283 ]
284 & list
285 & Map.unionsWith (curry errorShow)
286 pronunciationRules :: Pron.Table
287 pronunciationRules =
288 [ "Escherichia" := Rule{rulePron = ["E" := "ɛ", "sche" := "ʃe", "ri" := "ʁi", "chia" := "ʃja"], ruleExamples = ["Escherichia" := "ɛ.ʃe.ʁi.ʃja"]}
289 , "Maël" := Rule{rulePron = ["ma" := "ma", "ël" := "ɛl"], ruleExamples = ["Maël" := "ma.ɛl"]}
290 , "a" := Rule{rulePron = ["a" := "a"], ruleExamples = ["allume" := "a.lym"]}
291 , "au" := Rule{rulePron = ["au" := "o"], ruleExamples = ["au" := "o"]}
292 , "à" := Rule{rulePron = ["à" := "a"], ruleExamples = ["à" := "a"]}
293 , "arc" := Rule{rulePron = ["arc" := "aʁk"], ruleExamples = ["arc" := "aʁk"]}
294 , word "l" := Rule{rulePron = ["l" := "l"], ruleExamples = ["l" := "l"]}
295 , "ancrage" := Rule{rulePron = ["an" := "ɑ̃", "crage" := "kʁaʒ"], ruleExamples = ["ancrage" := "ɑ̃.kʁaʒ"]}
296 , "ancre" := Rule{rulePron = ["ancre" := "ɑ̃kʁ"], ruleExamples = ["ancre" := "ɑ̃kʁ"]}
297 , "ba" := Rule{rulePron = ["ba" := "ba"], ruleExamples = ["bateau" := "ba.to"]}
298 , "bal" := Rule{rulePron = ["bal" := "bal"], ruleExamples = ["bal" := "bal"]}
299 , "balle" := Rule{rulePron = ["balle" := "bal"], ruleExamples = ["balle" := "bal"]}
300 , "bain" := Rule{rulePron = ["bain" := "bɛ̃"], ruleExamples = ["bain" := "bɛ̃"]}
301 , "bile" := Rule{rulePron = ["bile" := "bil"], ruleExamples = ["immobile" := "i.mɔ.bil"]}
302 , "bo" := Rule{rulePron = ["bo" := "bɔ"], ruleExamples = ["bobo" := "bɔ.bo"]}
303 , "boi" := Rule{rulePron = ["boi" := "bwa"], ruleExamples = ["boit" := "bwa"]}
304 , "boué" := Rule{rulePron = ["boué" := "bwe"], ruleExamples = ["boué" := "bwe"]}
305 , "bri" := Rule{rulePron = ["bri" := "bʁi"], ruleExamples = ["sabrina" := "sa.bʁi.na"]}
306 , "brou" := Rule{rulePron = ["brou" := "bʁu"], ruleExamples = ["brouette" := "bʁu.ɛt"]}
307 , "ca" := Rule{rulePron = ["ca" := "ka"], ruleExamples = ["calla" := "ka.la"]}
308 , "cha" := Rule{rulePron = ["cha" := "ʃa"], ruleExamples = ["chamotté" := "ʃa.mɔ.te"]}
309 , "cham" <> [LexemeConsonant] := Rule{rulePron = ["cham" := "ʃɑ̃"], ruleExamples = ["champignon" := "ʃɑ̃.pi.ɲɔ̃"]}
310 , "chon" := Rule{rulePron = ["chon" := "ʃɔ̃"], ruleExamples = ["cochon" := "kɔ.ʃɔ̃"]}
311 , "chry" := Rule{rulePron = ["chry" := "kʁi"], ruleExamples = ["chrysanthème" := "kʁi.zɑ̃.tɛm"]}
312 , "ci" := Rule{rulePron = ["ci" := "si"], ruleExamples = ["mucidule" := "my.si.dyl"]}
313 , "cla" := Rule{rulePron = ["cla" := "kla"], ruleExamples = ["éclat" := "e.kla"]}
314 , "clate" := Rule{rulePron = ["clate" := "klat"], ruleExamples = ["éclate" := "e.klat"]}
315 , "clatent" := Rule{rulePron = ["clatent" := "klat"], ruleExamples = ["éclatent" := "e.klat"]}
316 , "cinthe" := Rule{rulePron = ["cinthe" := "sɛ̃t"], ruleExamples = ["jacinthe" := "ʒa.sɛ̃t"]}
317 , "co" := Rule{rulePron = ["co" := "kɔ"], ruleExamples = ["cochon" := "kɔ.ʃɔ̃"]}
318 , "de" := Rule{rulePron = ["de" := "də"], ruleExamples = ["demi" := "də.mi"]}
319 , "de" := Rule{rulePron = ["de" := "də"], ruleExamples = ["demi" := "də.mi"]}
320 , "deau" := Rule{rulePron = ["deau" := "do"], ruleExamples = ["rideau" := "ʁi.do"]}
321 , "dent" := Rule{rulePron = ["dent" := "dɑ̃"], ruleExamples = ["dent" := "dɑ̃"]}
322 , "deuil" := Rule{rulePron = ["deuil" := "dœj"], ruleExamples = ["deuil" := "dœj"]}
323 , "do" := Rule{rulePron = ["do" := "dɔ"], ruleExamples = ["doré" := "dɔ.ʁe"]}
324 , "drai" := Rule{rulePron = ["drai" := "dʁɛ"], ruleExamples = ["draisienne" := "dʁɛ.zjɛn"]}
325 , "du" := Rule{rulePron = ["du" := "dy"], ruleExamples = ["du" := "dy"]}
326 , "dule" := Rule{rulePron = ["dule" := "dyl"], ruleExamples = ["mucidule" := "my.si.dyl"]}
327 , "en" := Rule{rulePron = ["en" := "ɑ̃"], ruleExamples = ["en" := "ɑ̃"]}
328 , "ette" := Rule{rulePron = ["ette" := "ɛt"], ruleExamples = ["brouette" := "bʁu.ɛt"]}
329 , ending "blanc" := Rule{rulePron = [ending "blanc" := "blɑ̃"], ruleExamples = ["blanc" := "blɑ̃"]}
330 , "blanche" := Rule{rulePron = ["blanche" := "blɑ̃ʃ"], ruleExamples = ["blanche" := "blɑ̃ʃ"]}
331 , "blan" <> [LexemeConsonant] := Rule{rulePron = ["blan" <> [LexemeConsonant] := "blɑ̃"], ruleExamples = ["blanc" := "blɑ̃"]}
332 , "che" := Rule{rulePron = ["che" := "ʃə"], ruleExamples = ["cheval" := "ʃə.val"]}
333 , "val" := Rule{rulePron = ["val" := "val"], ruleExamples = ["cheval" := "ʃə.val"]}
334 , "fait" := Rule{rulePron = ["fait" := "fɛ"], ruleExamples = ["fait" := "fɛ"]}
335 , "fa" <> [LexemeConsonant] := Rule{rulePron = ["fa" <> [LexemeConsonant] := "fa"], ruleExamples = ["famille" := "fa.mij"]}
336 , "da" <> [LexemeConsonant] := Rule{rulePron = ["da" <> [LexemeConsonant] := "da"], ruleExamples = ["mandarine" := "mɑ̃.da.ʁin"]}
337 , "gin" <> [LexemeConsonant] := Rule{rulePron = ["gin" := "ʒɛ̃"], ruleExamples = ["gingembre" := "ʒɛ̃.ʒɑ̃bʁ"]}
338 , "gembre" := Rule{rulePron = ["gembre" := "ʒɑ̃bʁ"], ruleExamples = ["gingembre" := "ʒɛ̃.ʒɑ̃bʁ"]}
339 , "mille" := Rule{rulePron = ["mille" := "mij"], ruleExamples = ["famille" := "fa.mij"]}
340 , "man" <> [LexemeConsonant] := Rule{rulePron = ["man" <> [LexemeConsonant] := "mɑ̃"], ruleExamples = ["mandarine" := "mɑ̃.da.ʁin"]}
341 , "fram" <> [LexemeConsonant] := Rule{rulePron = ["fram" <> [LexemeConsonant] := "fʁɑ̃"], ruleExamples = ["framboise" := "fʁɑ̃.bwaz"]}
342 , "boise" := Rule{rulePron = ["boise" := "bwaz"], ruleExamples = ["framboise" := "fʁɑ̃.bwaz"]}
343 , "hibiscus" := Rule{rulePron = ["hi" := "i", "bis" := "bis", "cus" := "kys"], ruleExamples = ["hibiscus" := "i.bis.kys"]}
344 , word "mille" := Rule{rulePron = [word "mille" := "mil"], ruleExamples = ["mille" := "mil"]}
345 , "feu" := Rule{rulePron = ["feu" := "fø"], ruleExamples = ["feu" := "fø"]}
346 , "four" := Rule{rulePron = ["four" := "fuʁ"], ruleExamples = ["four" := "fuʁ"]}
347 , "feuille" := Rule{rulePron = ["feuille" := "fœj"], ruleExamples = ["feuille" := "fœj"]}
348 , "font" := Rule{rulePron = ["font" := "fɔ̃"], ruleExamples = ["font" := "fɔ̃"]}
349 , "fraise" := Rule{rulePron = ["fraise" := "fʁɛz"], ruleExamples = ["fraise" := "fʁɛz"]}
350 , "ga" := Rule{rulePron = ["ga" := "ga"], ruleExamples = ["alligator" := "a.li.ga.tɔʁ"]}
351 , "ge" := Rule{rulePron = ["ge" := "ʒə"], ruleExamples = ["gelée" := "ʒə.le"]}
352 , "grue" := Rule{rulePron = ["grue" := "gʁy"], ruleExamples = ["grue" := "gʁy"]}
353 , "sque" := Rule{rulePron = ["sque" := "skə"], ruleExamples = ["squelette" := "skə.lɛt"]}
354 , "lette" := Rule{rulePron = ["lette" := "lɛt"], ruleExamples = ["squelette" := "skə.lɛt"]}
355 , "geoir" := Rule{rulePron = ["geoir" := "ʒwaʁ"], ruleExamples = ["plongeoir" := "plɔ̃.ʒwaʁ"]}
356 , "geur" := Rule{rulePron = ["geur" := "ʒœʁ"], ruleExamples = ["nageur" := "na.ʒœʁ"]}
357 , "geuse" := Rule{rulePron = ["geuse" := "ʒøz"], ruleExamples = ["nageuse" := "na.ʒøz"]}
358 , "gi" <> [LexemeConsonant] := Rule{rulePron = ["gi" <> [LexemeConsonant] := "ʒi"], ruleExamples = ["gilet" := "ʒi.lɛ"]}
359 , "glace" := Rule{rulePron = ["glace" := "glas"], ruleExamples = ["glace" := "glas"]}
360 , "gnon" := Rule{rulePron = ["gnon" := "ɲɔ̃"], ruleExamples = ["champignon" := "ʃɑ̃.pi.ɲɔ̃"]}
361 , "gou" := Rule{rulePron = ["gou" := "gu"], ruleExamples = ["gouttière" := "gu.tjɛʁ"]}
362 , "gue" := Rule{rulePron = ["gue" := "gə"], ruleExamples = ["marguerite" := "maʁ.gə.ʁit"]}
363 , "gâ" := Rule{rulePron = ["gâ" := "ga"], ruleExamples = ["gâté" := "ga.te"]}
364 , "gé" := Rule{rulePron = ["gé" := "ʒe"], ruleExamples = ["orangé" := "ɔ.ʁɑ̃.ʒe"]}
365 , "gée" := Rule{rulePron = ["gée" := "ʒe"], ruleExamples = ["orangée" := "ɔ.ʁɑ̃.ʒe"]}
366 , "hi" := Rule{rulePron = ["hi" := "i"], ruleExamples = ["hippopotame" := "i.pɔ.pɔ.tam"]}
367 , "ppo" := Rule{rulePron = ["ppo" := "pɔ"], ruleExamples = ["hippopotame" := "i.pɔ.pɔ.tam"]}
368 , "tame" := Rule{rulePron = ["tame" := "tam"], ruleExamples = ["hippopotame" := "i.pɔ.pɔ.tam"]}
369 , "ho" := Rule{rulePron = ["ho" := "o"], ruleExamples = ["homo" := "o.mo"]}
370 , "hêtre" := Rule{rulePron = ["hêtre" := "ɛtʁ"], ruleExamples = ["hêtre" := "ɛtʁ"]}
371 , "é" := Rule{rulePron = ["é" := "e"], ruleExamples = ["éclat" := "e.kla"]}
372 , "i" := Rule{rulePron = ["i" := "i"], ruleExamples = ["ibis" := "i.bis"]}
373 , "illet" := Rule{rulePron = ["illet" := "jɛ"], ruleExamples = ["œillet" := "œ.jɛ"]}
374 , "illo" := Rule{rulePron = ["illo" := "jo"], ruleExamples = ["maillot" := "ma.jo"]}
375 , "ja" := Rule{rulePron = ["ja" := "ʒa"], ruleExamples = ["jacinthe" := "ʒa.sɛ̃t"]}
376 , "jas" := Rule{rulePron = ["jas" := "ʒas"], ruleExamples = ["jasmin" := "ʒas.mɛ̃"]}
377 , "je" := Rule{rulePron = ["je" := "ʒə"], ruleExamples = ["jetée" := "ʒə.te"]}
378 , "jon" <> [LexemeConsonant] := Rule{rulePron = ["jon" := "ʒɔ̃"], ruleExamples = ["jonquille" := "ʒɔ̃.kij"]}
379 , "ju" := Rule{rulePron = ["ju" := "ʒy"], ruleExamples = ["judo" := "ʒy.do"]}
380 , "kan" <> [LexemeConsonant] := Rule{rulePron = ["kan" <> [LexemeConsonant] := "kɑ̃"], ruleExamples = ["kangourou" := "kɑ̃.gu.ʁu"]}
381 , "gou" := Rule{rulePron = ["gou" := "gu"], ruleExamples = ["kangourou" := "kɑ̃.gu.ʁu"]}
382 , "rou" := Rule{rulePron = ["rou" := "ʁu"], ruleExamples = ["kangourou" := "kɑ̃.gu.ʁu"]}
383 , "rousse" := Rule{rulePron = ["rousse" := "ʁus"], ruleExamples = ["rousse" := "ʁus"]}
384 , "la" := Rule{rulePron = ["la" := "la"], ruleExamples = ["la" := "la"]}
385 , "lac" := Rule{rulePron = ["lac" := "lak"], ruleExamples = ["lac" := "lak"]}
386 , "langue" := Rule{rulePron = ["langue" := "lɑ̃g"], ruleExamples = ["langue" := "lɑ̃g"]}
387 , "le" := Rule{rulePron = ["le" := "lə"], ruleExamples = ["le" := "lə"]}
388 , "li" := Rule{rulePron = ["li" := "li"], ruleExamples = ["pissenlit" := "pi.sɑ̃.li"]}
389 , "lier" := Rule{rulePron = ["lier" := "lje"], ruleExamples = ["voilier" := "vwa.lje"]}
390 , "lin" <> [LexemeBorder] := Rule{rulePron = ["lin" := "lɛ̃"], ruleExamples = ["merlin" := "mɛʁ.lɛ̃"]}
391 , "lion" := Rule{rulePron = ["lion" := "ljɔ̃"], ruleExamples = ["lion" := "ljɔ̃"]}
392 , "lionne" := Rule{rulePron = ["lionne" := "ljɔ̃n"], ruleExamples = ["lionne" := "ljɔ̃n"]}
393 , "lla" := Rule{rulePron = ["lla" := "la"], ruleExamples = ["calla" := "ka.la"]}
394 , "lli" := Rule{rulePron = ["lli" := "li"], ruleExamples = ["alligator" := "a.li.ga.tɔʁ"]}
395 , "llon" := Rule{rulePron = ["llon" := "jɔ̃"], ruleExamples = ["papillon" := "pa.pi.jɔ̃"]}
396 , "llume" := Rule{rulePron = ["llume" := "lym"], ruleExamples = ["allume" := "a.lym", "allume-feu" := "a.lym.fø"]}
397 , "lu" := Rule{rulePron = ["lu" := "ly"], ruleExamples = ["révolution" := "ʁe.vɔ.ly.sjɔ̃"]}
398 , "ly" := Rule{rulePron = ["ly" := "li"], ruleExamples = ["polypore" := "pɔ.li.pɔʁ"]}
399 , "lé" := Rule{rulePron = ["lé" := "le"], ruleExamples = ["gelé" := "ʒə.le"]}
400 , "leur" := Rule{rulePron = ["leur" := "lœʁ"], ruleExamples = ["leur" := "lœʁ"]}
401 , "griffe" := Rule{rulePron = ["griffe" := "gʁif"], ruleExamples = ["griffe" := "gʁif"]}
402 , "ra" := Rule{rulePron = ["ra" := "ʁa"], ruleExamples = ["ra" := "ʁa"]}
403 , "ma" := Rule{rulePron = ["ma" := "ma"], ruleExamples = ["ma" := "ma"]}
404 , "mar" <> [LexemeConsonant] := Rule{rulePron = ["mar" <> [LexemeConsonant] := "maʁ"], ruleExamples = ["marguerite" := "maʁ.gə.ʁit"]}
405 , "masque" := Rule{rulePron = ["masque" := "mask"], ruleExamples = ["masque" := "mask"]}
406 , "mer" <> [LexemeConsonant] := Rule{rulePron = ["mer" <> [LexemeConsonant] := "mɛʁ"], ruleExamples = ["merlin" := "mɛʁ.lɛ̃"]}
407 , "mi" := Rule{rulePron = ["mi" := "mi"], ruleExamples = ["demi" := "də.mi"]}
408 , "miel" := Rule{rulePron = ["miel" := "mjɛl"], ruleExamples = ["miel" := "mjɛl"]}
409 , "mmo" := Rule{rulePron = ["mmo" := "mɔ"], ruleExamples = ["immobile" := "i.mɔ.bil"]}
410 , "mo" := Rule{rulePron = ["mo" := "mɔ"], ruleExamples = ["moto" := "mɔ.to"]}
411 , -- , "mon" := Rule{rulePron = ["mon" := "mɔ̃"], ruleExamples = ["montre" := "mɔ̃"]}
412 "montre" := Rule{rulePron = ["montre" := "mɔ̃tʁ"], ruleExamples = ["montre" := "mɔ̃tʁ"]}
413 , "montrent" := Rule{rulePron = ["montrent" := "mɔ̃tʁ"], ruleExamples = ["montrent" := "mɔ̃tʁ"]}
414 , -- , "tre" := Rule{rulePron = ["tre" := "tʁ"], ruleExamples = ["montre" := "tʁ"]}
415 "mu" := Rule{rulePron = ["mu" := "my"], ruleExamples = ["mucidule" := "my.si.dyl"]}
416 , "mène" := Rule{rulePron = ["mène" := "mɛn"], ruleExamples = ["promène" := "pʁɔ.mɛn"]}
417 , "mènent" := Rule{rulePron = ["mènent" := "mɛn"], ruleExamples = ["promènent" := "pʁɔ.mɛn"]}
418 , "na" := Rule{rulePron = ["na" := "na"], ruleExamples = ["na" := "na"]}
419 , "nette" := Rule{rulePron = ["nette" := "nɛt"], ruleExamples = ["lunette" := "ly.nɛt", "lunettes" := "ly.nɛt"]}
420 , "niche" := Rule{rulePron = ["niche" := "niʃ"], ruleExamples = ["péniche" := "pe.niʃ"]}
421 , "nnet" := Rule{rulePron = ["nnet" := "nɛ"], ruleExamples = ["bonnet" := "bɔ.nɛ"]}
422 , "noc" := Rule{rulePron = ["noc" := "nɔk"], ruleExamples = ["nocturne" := "nɔk.tyʁn"]}
423 , "nou" := Rule{rulePron = ["nou" := "nu"], ruleExamples = ["nourrit" := "nu.ʁi"]}
424 , "o" := Rule{rulePron = ["o" := "ɔ"], ruleExamples = ["orange" := "ɔ.ʁɑ̃ʒ"]}
425 , "ou" := Rule{rulePron = ["ou" := "u"], ruleExamples = ["ou" := "u"]}
426 , "pa" := Rule{rulePron = ["pa" := "pa"], ruleExamples = ["papillon" := "pa.pi.jɔ̃"]}
427 , "paque" := Rule{rulePron = ["paque" := "pak"], ruleExamples = ["paquebot" := "pak.bo"]}
428 , "passe" := Rule{rulePron = ["passe" := "pas"], ruleExamples = ["passerelle" := "pas.ʁɛl"]}
429 , "pi" := Rule{rulePron = ["pi" := "pi"], ruleExamples = ["papillon" := "pa.pi.jɔ̃"]}
430 , "pi" := Rule{rulePron = ["pi" := "pi"], ruleExamples = ["pissenlit" := "pi.sɑ̃.li"]}
431 , "plon" := Rule{rulePron = ["plon" := "plɔ̃"], ruleExamples = ["plongeoir" := "plɔ̃.ʒwaʁ"]}
432 , "pneu" := Rule{rulePron = ["pneu" := "pnø"], ruleExamples = ["pneumatique" := "pnø.ma.tik"]}
433 , "po" := Rule{rulePron = ["po" := "pɔ"], ruleExamples = ["polypore" := "pɔ.li.pɔʁ"]}
434 , "foin" := Rule{rulePron = ["foin" := "fwɛ̃"], ruleExamples = ["foin" := "fwɛ̃"]}
435 , "pon" := Rule{rulePron = ["pon" := "pɔ̃"], ruleExamples = ["pont" := "pɔ̃"]}
436 , "pore" := Rule{rulePron = ["pore" := "pɔʁ"], ruleExamples = ["polypore" := "pɔ.li.pɔʁ"]}
437 , "porte" := Rule{rulePron = ["porte" := "pɔʁt"], ruleExamples = ["porte" := "pɔʁt"]}
438 , "pro" := Rule{rulePron = ["pro" := "pʁɔ"], ruleExamples = ["promène" := "pʁɔ.mɛn"]}
439 , "pâ" := Rule{rulePron = ["pâ" := "pa"], ruleExamples = ["pâquerette" := "pa.kʁɛt"]} -- ɑ
440 , "pé" := Rule{rulePron = ["pé" := "pe"], ruleExamples = ["péniche" := "pe.niʃ"]}
441 , "que" := Rule{rulePron = ["que" := "kə"], ruleExamples = ["querelle" := "kə.ʁɛl"]}
442 , "querette" := Rule{rulePron = ["querette" := "kʁɛt"], ruleExamples = ["pâquerette" := "pa.kʁɛt"]}
443 , "queuse" := Rule{rulePron = ["queuse" := "køz"], ruleExamples = ["visqueuse" := "vis.køz"]}
444 , "quille" := Rule{rulePron = ["quille" := "kij"], ruleExamples = ["jonquille" := "ʒɔ̃.kij"]}
445 , "quipe" := Rule{rulePron = ["quipe" := "kip"], ruleExamples = ["équipe" := "e.kip"]}
446 , "range" := Rule{rulePron = ["range" := "ʁɑ̃ʒ"], ruleExamples = ["orange" := "ɔ.ʁɑ̃ʒ"]}
447 , "rangent" := Rule{rulePron = ["rangent" := "ʁɑ̃ʒ"], ruleExamples = ["rangent" := "ʁɑ̃ʒ"]}
448 , "ran" <> [LexemeConsonant] := Rule{rulePron = ["range" <> [LexemeConsonant] := "ʁɑ̃"], ruleExamples = ["orangé" := "ɔ.ʁɑ̃.ʒe"]}
449 , "relle" := Rule{rulePron = ["relle" := "ʁɛl"], ruleExamples = ["passerelle" := "pas.ʁɛl"]}
450 , -- , "ra" := Rule{rulePron = ["ra" := "ʁa"], ruleExamples = ["girafe" := "ʒi.ʁaf"]}
451 "rafe" := Rule{rulePron = ["rafe" := "ʁaf"], ruleExamples = ["girafe" := "ʒi.ʁaf"]}
452 , "aigle" := Rule{rulePron = ["aigle" := "ɛgl"], ruleExamples = ["aigle" := "ɛgl"]}
453 , "cor" <> [LexemeConsonant] := Rule{rulePron = ["cor" <> [LexemeConsonant] := "kɔʁ"], ruleExamples = ["corbeau" := "kɔʁ.bo"]}
454 , "ri" := Rule{rulePron = ["ri" := "ʁi"], ruleExamples = ["rideau" := "ʁi.do"]}
455 , "rhi" := Rule{rulePron = ["rhi" := "ʁi"], ruleExamples = ["rhinocéros" := "ʁi.nɔ.se.ʁɔs"]}
456 , "no" := Rule{rulePron = ["no" := "nɔ"], ruleExamples = ["rhinocéros" := "ʁi.nɔ.se.ʁɔs"]}
457 , "cé" := Rule{rulePron = ["cé" := "se"], ruleExamples = ["rhinocéros" := "ʁi.nɔ.se.ʁɔs"]}
458 , "rhinocéros" := Rule{rulePron = ["rhi" := "ʁi", "no" := "nɔ", "cé" := "se", "ros" <> [LexemeMeaning "animal"] := "ʁɔs"], ruleExamples = ["rhinocéros" := "ʁi.nɔ.se.ʁɔs"]}
459 , "no" := Rule{rulePron = ["no" := "nɔ"], ruleExamples = ["rhinocéros" := "ʁi.nɔ.se.ʁɔs"]}
460 , "cé" := Rule{rulePron = ["cé" := "se"], ruleExamples = ["rhinocéros" := "ʁi.nɔ.se.ʁɔs"]}
461 , "rine" := Rule{rulePron = ["rine" := "ʁin"], ruleExamples = ["marine" := "ma.ʁin"]}
462 , "rite" := Rule{rulePron = ["rite" := "ʁit"], ruleExamples = ["marguerite" := "maʁ.gə.ʁit"]}
463 , "ro" := Rule{rulePron = ["ro" := "rɔ"], ruleExamples = ["robot" := "rɔ.bo"]}
464 , "rose" := Rule{rulePron = ["rose" := "rɔz"], ruleExamples = ["rose" := "rɔz"]}
465 , "rou" := Rule{rulePron = ["rou" := "ʁu"], ruleExamples = ["rouler" := "ʁu.le"]}
466 , "rouge" := Rule{rulePron = ["rouge" := "ʁuʒ"], ruleExamples = ["rouge" := "ʁuʒ"]}
467 , "rri" := Rule{rulePron = ["rri" := "ʁi"], ruleExamples = ["nourrit" := "nu.ʁi"]}
468 , "ré" := Rule{rulePron = ["ré" := "ʁe"], ruleExamples = ["révolution" := "ʁe.vɔ.ly.sjɔ̃"]}
469 , "sa" := Rule{rulePron = ["sa" := "sa"], ruleExamples = ["satellite" := "sa.te.lit"]}
470 , begining "singe" := Rule{rulePron = [begining "singe" := "sɛ̃ʒ"], ruleExamples = ["singe" := "sɛ̃ʒ"]}
471 , "buse" := Rule{rulePron = ["buse" := "byz"], ruleExamples = ["buse" := "byz"]}
472 , "bulle" := Rule{rulePron = ["bulle" := "byl"], ruleExamples = ["bulle" := "byl"]}
473 , "tigre" := Rule{rulePron = ["tigre" := "tigʁ"], ruleExamples = ["tigre" := "tigʁ"]}
474 , "tigresse" := Rule{rulePron = ["ti" := "ti", "gresse" := "gʁɛs"], ruleExamples = ["tigresse" := "ti.gʁɛs"]}
475 , "lombe" := Rule{rulePron = ["lombe" := "lɔ̃b"], ruleExamples = ["colombe" := "kɔ.lɔ̃b"]}
476 , "sauve" := Rule{rulePron = ["sauve" := "sov"], ruleExamples = ["sauvetage" := "sov.taʒ"]}
477 , "scine" := Rule{rulePron = ["scine" := "sin"], ruleExamples = ["piscine" := "pi.sin"]}
478 , "short" := Rule{rulePron = ["short" := "ʃɔʁt"], ruleExamples = ["short" := "ʃɔʁt"]}
479 , "ssen" := Rule{rulePron = ["ssen" := "sɑ̃"], ruleExamples = ["pissenlit" := "pi.sɑ̃.li"]}
480 , "cha" := Rule{rulePron = ["cha" := "ʃa"], ruleExamples = ["cha" := "ʃa"]}
481 , "chasse" := Rule{rulePron = ["chasse" := "ʃas"], ruleExamples = ["chasse" := "ʃas"]}
482 , "chassent" := Rule{rulePron = ["chassent" := "ʃas"], ruleExamples = ["chassent" := "ʃas"]}
483 , "sur" := Rule{rulePron = ["sur" := "syʁ"], ruleExamples = ["sur" := "syʁ"]}
484 , "ta" := Rule{rulePron = ["ta" := "ta"], ruleExamples = ["ta" := "ta"]}
485 , "tage" := Rule{rulePron = ["tage" := "taʒ"], ruleExamples = ["sauvetage" := "sov.taʒ"]}
486 , "tan" <> [LexemeConsonant] := Rule{rulePron = ["tan" <> [LexemeConsonant] := "tɑ̃"], ruleExamples = ["tan" := "tɑ̃"]}
487 , "tellite" := Rule{rulePron = ["te" <> [LexemeDoubleConsonant] := "te", "llite" := "lit"], ruleExamples = ["satellite" := "sa.te.lit"]}
488 , "terie" := Rule{rulePron = ["terie" := "tʁi"], ruleExamples = ["poterie" := "pɔ.tʁi"]}
489 , "thème" := Rule{rulePron = ["thème" := "tɛm"], ruleExamples = ["chrysanthème" := "kʁi.zɑ̃.tɛm"]}
490 , "tient" := Rule{rulePron = ["tient" := "tjɛ̃"], ruleExamples = ["tient" := "tjɛ̃"]}
491 , "tier" := Rule{rulePron = ["tier" := "tje"], ruleExamples = ["chalutier" := "ʃa.ly.tje"]}
492 , "tion" := Rule{rulePron = ["tion" := "sjɔ̃"], ruleExamples = ["révolution" := "ʁe.vɔ.ly.sjɔ̃"]}
493 , "ssion" := Rule{rulePron = ["ssion" := "sjɔ̃"], ruleExamples = ["passion" := "pa.sjɔ̃"]}
494 , "tille" := Rule{rulePron = ["tille" := "tij"], ruleExamples = ["myrtille" := "miʁ.tij"]}
495 , "tique" := Rule{rulePron = ["tique" := "tik"], ruleExamples = ["pneumatique" := "pnø.ma.tik"]}
496 , "tir" := Rule{rulePron = ["tir" := "tiʁ"], ruleExamples = ["tire" := "tiʁ"]}
497 , "pêche" := Rule{rulePron = ["pêche" := "pɛʃ"], ruleExamples = ["pêche" := "pɛʃ"]}
498 , "vert" := Rule{rulePron = ["vert" := "vɛʁ"], ruleExamples = ["vert" := "vɛʁ"]}
499 , "myr" := Rule{rulePron = ["myr" := "miʁ"], ruleExamples = ["myrtille" := "miʁ.tij"]}
500 , begining "si" := Rule{rulePron = [begining "si" := "si"], ruleExamples = ["sirop" := "si.ʁo"]}
501 , ending "rop" := Rule{rulePron = ["rop" := "ʁo"], ruleExamples = ["sirop" := "si.ʁo"]}
502 , "tor" := Rule{rulePron = ["tor" := "tɔʁ"], ruleExamples = ["alligator" := "a.li.ga.tɔʁ"]}
503 , "touche" := Rule{rulePron = ["touche" := "tuʃ"], ruleExamples = ["touche" := "tuʃ"]}
504 , "tris" <> [LexemeConsonant] := Rule{rulePron = ["tris" := "tʁis"], ruleExamples = ["ma" := "ma"]}
505 , "truffe" := Rule{rulePron = ["truffe" := "tʁyf"], ruleExamples = ["Truffe" := "tʁyf"]}
506 , "trône" := Rule{rulePron = ["trône" := "tʁon"], ruleExamples = ["trône" := "tʁon"]}
507 , "ttière" := Rule{rulePron = ["ttière" := "tjɛʁ"], ruleExamples = ["gouttière" := "gu.tjɛʁ"]}
508 , "tu" := Rule{rulePron = ["tu" := "ty"], ruleExamples = ["tuba" := "ty.ba"]}
509 , "turne" := Rule{rulePron = ["turne" := "tyʁn"], ruleExamples = ["nocturne" := "nɔk.tyʁn"]}
510 , "té" := Rule{rulePron = ["té" := "te"], ruleExamples = ["gâté" := "ga.te"]}
511 , "vache" := Rule{rulePron = ["vache" := "vaʃ"], ruleExamples = ["vache" := "vaʃ"]}
512 , "vec" := Rule{rulePron = ["vec" := "vɛk"], ruleExamples = ["avec" := "a.vɛk"]}
513 , "vis" := Rule{rulePron = ["vis" := "vis"], ruleExamples = ["visqueuse" := "vis.køz"]}
514 , "vo" := Rule{rulePron = ["vo" := "vɔ"], ruleExamples = ["révolution" := "ʁe.vɔ.ly.sjɔ̃"]}
515 , "von" := Rule{rulePron = ["von" := "vɔ̃"], ruleExamples = ["savon" := "sa.vɔ̃"]}
516 , "sson" := Rule{rulePron = ["sson" := "sɔ̃"], ruleExamples = ["boisson" := "bwa.sɔ̃"]}
517 , "zeuse" := Rule{rulePron = ["zeuse" := "zøz"], ruleExamples = ["gazeuse" := "ga.zøz"]}
518 , "voi" := Rule{rulePron = ["voi" := "vwa"], ruleExamples = ["voilier" := "vwa.lje"]}
519 , "vé" := Rule{rulePron = ["vé" := "ve"], ruleExamples = ["vélo" := "ve.lo"]}
520 , "fête" := Rule{rulePron = ["fête" := "fɛt"], ruleExamples = ["fête" := "fɛt"]}
521 , "fruit" := Rule{rulePron = ["fruit" := "fʁɥi"], ruleExamples = ["fruit" := "fʁɥi"]}
522 , "nane" := Rule{rulePron = ["nane" := "nan"], ruleExamples = ["banane" := "ba.nan"]}
523 , "pomme" := Rule{rulePron = ["pomme" := "pɔm"], ruleExamples = ["pomme" := "pɔm"]}
524 , "ce" := Rule{rulePron = ["ce" := "sə"], ruleExamples = ["cerise" := "sə.ʁiz"]}
525 , "rise" := Rule{rulePron = ["rise" := "ʁiz"], ruleExamples = ["cerise" := "sə.ʁiz"]}
526 , "yo" := Rule{rulePron = ["yo" := "jo"], ruleExamples = ["Yohan" := "jo.an"]}
527 , "é" := Rule{rulePron = ["é" := "e"], ruleExamples = ["équipe" := "e.kip"]}
528 , "dé" := Rule{rulePron = ["dé" := "de"], ruleExamples = ["décorations" := "de.kɔ.ʁa.sjɔ̃"]}
529 , "œ" := Rule{rulePron = ["œ" := "œ"], ruleExamples = ["œillet" := "œ.jɛ"]}
530 , "ti" := Rule{rulePron = ["ti" := "ti"], ruleExamples = ["d'artifices" := "daʁ.ti.fis"]}
531 , "fice" := Rule{rulePron = ["fice" := "fis"], ruleExamples = ["d'artifices" := "daʁ.ti.fis"]}
532 , -- kɑ̃.ta.lu
533 "can" <> [LexemeConsonant] := Rule{rulePron = ["can" <> [LexemeConsonant] := "kɑ̃"], ruleExamples = ["cantaloup" := "kɑ̃.ta.lu"]}
534 , ending "loup" := Rule{rulePron = [ending "loup" := "lu"], ruleExamples = ["cantaloup" := "kɑ̃.ta.lu"]}
535 , begining "d'ar" := Rule{rulePron = [begining "d'ar" := "daʁ"], ruleExamples = ["d'artifices" := "daʁ.ti.fis"]}
536 , "mustang" := Rule{rulePron = ["mus" := "mys", "tang" := "tɑ̃g"], ruleExamples = ["mustang" := "mys.tɑ̃g"]}
537 , "tarte" := Rule{rulePron = ["tarte" := "taʁt"], ruleExamples = ["tarte" := "taʁt"]}
538 , "citron" := Rule{rulePron = ["ci" := "si", "tron" := "tʁɔ̃"], ruleExamples = ["citron" := "si.tʁɔ̃"]}
539 , begining "d'o" := Rule{rulePron = [begining "d'o" := "dɔ"], ruleExamples = ["d'orange" := "dɔ.ʁɑ̃ʒ"]}
540 , begining "d'a" <> [LexemeConsonant] := Rule{rulePron = [begining "d'a" <> [LexemeConsonant] := "da"], ruleExamples = ["d'ananas" := "da.na.nas"]}
541 , word "d'ananas" := Rule{rulePron = ["d'a" <> [LexemeMeaning "fruit"] := "da", "na" <> [LexemeMeaning "fruit"] := "na", "nas" <> [LexemeMeaning "fruit"] := "nas"], ruleExamples = ["d'ananas" := "da.na.nas"]}
542 , [LexemeVowel] <> "san" <> [LexemeConsonant] := Rule{rulePron = [[LexemeVowel] <> "san" <> [LexemeConsonant] := "zɑ̃"], ruleExamples = ["chrysanthème" := "kʁi.zɑ̃.tɛm"]}
543 , [LexemeVowel] <> "sienne" := Rule{rulePron = [[LexemeVowel] <> "sienne" := "zjɛn"], ruleExamples = ["draisienne" := "dʁɛ.zjɛn"]}
544 , [LexemeVowel] <> "ya" := Rule{rulePron = [[LexemeVowel] <> "ya" := "ja"], ruleExamples = ["ya" := "ja"]}
545 , begining "absent" := Rule{rulePron = [begining "ab" := "ab", "sent" := "sɑ̃"], ruleExamples = ["absent" := "ab.sɑ̃", "absents" := "ab.sɑ̃"]}
546 , begining "exer" := Rule{rulePron = ["e" := "ɛ", "x" := "g.z", "er" := "ɛʁ"], ruleExamples = ["exercice" := "ɛg.zɛʁ.sis"]}
547 , begining "ya" := Rule{rulePron = [begining "ya" := "ja"], ruleExamples = ["ya" := "ja"]}
548 , begining "yacht" := Rule{rulePron = ["yacht" := "jɔt"], ruleExamples = ["yacht" := "jɔt"]}
549 , ending "bis" := Rule{rulePron = [ending "bis" := "bis"], ruleExamples = ["ibis" := "i.bis"]}
550 , ending "bo" := Rule{rulePron = [ending "bo" := "bo"], ruleExamples = ["bobo" := "bɔ.bo"]}
551 , ending "bot" := Rule{rulePron = [ending "bot" := "bo"], ruleExamples = ["robot" := "rɔ.bo"]}
552 , ending "cice" := Rule{rulePron = [ending "cice" := ["sis"]], ruleExamples = ["exercice" := "ɛg.zɛʁ.sis"]}
553 , ending "cices" := Rule{rulePron = [ending "cices" := ["sis"]], ruleExamples = ["exercices" := "ɛg.zɛʁ.sis"]}
554 , ending "co" := Rule{rulePron = ["co" := "ko"], ruleExamples = ["cocorico" := "kɔ.kɔ.ʁi.ko"]}
555 , ending "do" := Rule{rulePron = [ending "do" := "do"], ruleExamples = ["judo" := "ʒy.do"]}
556 , ending "e" := Rule{rulePron = [ending "e" := [""]], ruleExamples = ["gelée" := "ʒə.le"]}
557 , ending "han" := Rule{rulePron = [ending "han" := "an"], ruleExamples = ["Yohan" := "jo.an"]}
558 , ending "ler" := Rule{rulePron = [ending "ler" := "le"], ruleExamples = ["rouler" := "ʁu.le"]}
559 , ending "let" := Rule{rulePron = [ending "let" := "lɛ"], ruleExamples = ["gilet" := "ʒi.lɛ"]}
560 , ending "lo" := Rule{rulePron = [ending "lo" := "lo"], ruleExamples = ["vélo" := "ve.lo"]}
561 , ending "min" := Rule{rulePron = [ending "min" := "mɛ̃"], ruleExamples = ["jasmin" := "ʒas.mɛ̃"]}
562 , ending "mmo" := Rule{rulePron = [ending "mmo" := "mo"], ruleExamples = ["immo" := "i.mo"]}
563 , ending "mo" := Rule{rulePron = [ending "mo" := "mo"], ruleExamples = ["homo" := "o.mo"]}
564 , ending "mot" := Rule{rulePron = [ending "mot" := "mo"], ruleExamples = ["mot" := "mo"]}
565 , ending "doux" := Rule{rulePron = [ending "doux" := "du"], ruleExamples = ["doux" := "du"]}
566 , ending "not" := Rule{rulePron = [ending "not" := "no"], ruleExamples = ["canot" := "ka.no"]}
567 , ending "s" := Rule{rulePron = [ending "s" := [""]], ruleExamples = ["bulles" := "byl"]}
568 , ending "ent" := Rule{rulePron = [ending "ent" := [""]], ruleExamples = ["tirent" := "tiʁ"]}
569 , ending "t" := Rule{rulePron = [ending "t" := [""]], ruleExamples = []}
570 , ending "tan" := Rule{rulePron = [ending "tan" := "tɑ̃"], ruleExamples = ["tan" := "tɑ̃"]}
571 , "teau" := Rule{rulePron = ["teau" := "to"], ruleExamples = ["bateau" := "ba.to"]}
572 , "beau" := Rule{rulePron = ["beau" := "bo"], ruleExamples = ["corbeau" := "kɔʁ.bo"]}
573 , "ceau" := Rule{rulePron = ["ceau" := "so"], ruleExamples = ["lionceau" := "ljɔ̃.so"]}
574 , ending "to" := Rule{rulePron = [ending "to" := "to"], ruleExamples = ["moto" := "mɔ.to"]}
575 , ending "ts" := Rule{rulePron = [ending "ts" := [""]], ruleExamples = ["maillots" := "ma.jo"]}
576 , word "dans" := Rule{rulePron = [word "dans" := "dɑ̃"], ruleExamples = ["dans" := "dɑ̃"]}
577 , word "et" := Rule{rulePron = [word "et" := "e"], ruleExamples = ["et" := "e"]}
578 , word "des" := Rule{rulePron = ["des" := "de"], ruleExamples = ["des" := "de"]}
579 , word "les" := Rule{rulePron = [word "les" := "le"], ruleExamples = ["les" := "le"]}
580 , word "sous" := Rule{rulePron = [word "sous" := "su"], ruleExamples = ["sous" := "su"]}
581 , word "un" := Rule{rulePron = [word "un" := "œ̃"], ruleExamples = ["un" := "œ̃"]}
582 , word "une" := Rule{rulePron = [word "une" := "yn"], ruleExamples = ["une" := "yn"]}
583 , "coli" := Rule{rulePron = ["co" := "kɔ", "li" := "li"], ruleExamples = ["Escherichia coli" := "ɛ.ʃe.ʁi.ʃja.kɔ.li"]}
584 ]
585 & Pron.withCapital
586 & fromList
587
588 {-
589 , word "mer" :=
590 Rule
591 { rulePron =
592 [ "mer" := ["mɛʁ"]
593 ]
594 , ruleExamples = [["mer" & occurence]]
595 }
596 , begining "mer" <> [LexemeConsonant] :=
597 Rule
598 { rulePron = [ "mer" := ["mɛʁ"] ]
599 , ruleExamples = [["mer" & occurence, "le"]]
600 }
601 , begining "Mer" <> [LexemeConsonant] :=
602 Rule
603 { rulePron = [ "Mer" := ["mɛʁ"] ]
604 , ruleExamples = [["Mer" & occurence, "lin"]]
605 }
606 , begining "Mer" <> [LexemeConsonant] :=
607 Rule
608 { rulePron = [ "Mer" := ["mɛʁ"] ]
609 , ruleExamples = [["Mer" & occurence, "lin"]]
610 }
611 , "abstrait" :=
612 Rule
613 { rulePron =
614 [ "ab" := ["ap"] -- sic
615 , "strait" := ["stʁɛ"]
616 ]
617 , ruleExamples = [["abstrait" & occurence]]
618 }
619 , "ab" :=
620 Rule
621 { rulePron = ["ab" := ["ab"]]
622 , ruleExamples = [["ab" & occurence, "solu"]]
623 }
624 , "so" :=
625 Rule
626 { rulePron = ["so" := ["sɔ"]]
627 , ruleExamples = [["ab", "so" & occurence, "lu"]]
628 }
629 , "lu" :=
630 Rule
631 { rulePron = ["lu" := ["ly"]]
632 , ruleExamples = [["lu" & occurence], ["abso", "lu" & occurence]]
633 }
634 , "a" :=
635 Rule
636 { rulePron = ["a" := ["a"]]
637 , ruleExamples = [["a" & occurence]]
638 }
639 , "llume" :=
640 Rule
641 { rulePron = ["llume" := ["lym"]]
642 , ruleExamples = [["a", "llume" & occurence]]
643 }
644 , "cice" :=
645 Rule
646 { rulePron =
647 [ "cice" := ["sis"]
648 ]
649 , ruleExamples = [["exer", "cice" & occurence]]
650 }
651 -}