{-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE OverloadedLists #-} {-# LANGUAGE ParallelListComp #-} module WiktionarySpec where import Data.GenValidity.Map () import Data.GenValidity.Sequence () import Data.GenValidity.Set () import Data.GenValidity.Text () import Data.List qualified as List import Data.Map.Strict qualified as Map import Data.Set qualified as Set import Data.Text qualified as Text import Data.Text.Short qualified as ShortText import Data.Validity.Map () import Data.Validity.Set () import Data.Validity.Text () import Language.IPA qualified as IPA import System.Directory qualified as IO import System.FilePath (joinPath, pathSeparator, (<.>), ()) import System.IO qualified as IO import Test.Syd import Data.RadixTree.Word8.Strict qualified as RadixTree import Utils.Tests import Wiktionary qualified import Worksheets.Utils.IPA qualified as IPA import Worksheets.Utils.JSON qualified as JSON import Worksheets.Utils.Prelude import Worksheets.Utils.SQL qualified as SQL import Prelude (mod) {- wiktionaryQueryWord :: LangCode -> ShortText -> IO [Wiktionary] wiktionaryQueryWord lang_code word = SQL.withConnection "data/langs/français/kaikki/wiktionary=fr.lang=fr.sqlite3" \conn -> SQL.query conn ("SELECT " <> SQL.selectors @Wiktionary <> " FROM wiktionary WHERE word = ? AND lang_code = ?") (word, lang_code) wiktionaryQueryAll :: IO [Wiktionary] wiktionaryQueryAll = test = testAll testAll = wiktionaryQueryAll <&> List.length testError0 :: IO [Wiktionary] testError0 = SQL.withConnection "data/langs/français/kaikki/wiktionary=fr.lang=fr.sqlite3" \conn -> SQL.query conn ("SELECT " <> SQL.selectors @Wiktionary <> " FROM wiktionary WHERE redirect = ?") (SQL.Only ("quelqu\8217un"::Text)) -} -- | Join all `IPA.Segment` containing a `IPA.Linking` feature -- with any following `IPA.Segment`. -- And drop all other `IPA.SuprasegmentalFeature`. mangleSupraSegmentalFeatures :: [IPA.Syllable []] -> [[IPA.Segment]] mangleSupraSegmentalFeatures = \case [] -> [] IPA.Syllable syl : ts -> syl : mangleSupraSegmentalFeatures ts IPA.WithSuprasegmentalFeature IPA.Linking syl : ts -> case mangleSupraSegmentalFeatures ts of [] -> [dropSupraSegmentalFeatures syl] x : xs -> (dropSupraSegmentalFeatures syl <> x) : xs IPA.WithSuprasegmentalFeature _feat syl : xs -> mangleSupraSegmentalFeatures (syl : xs) type Support = Int -- A frequent itemset is closed, -- when no (immediate) superset has the same support. supports :: Set Text -> Map Text (Sum Int) supports corpus = [ (prefix, Set.size words & Sum) | (prefix, words) <- prefixToWords & Map.toList ] & Map.fromListWith (<>) where len = corpus & toList <&> Text.length & maximum prefixToWords = [ (prefix, Set.singleton word) | word <- corpus & toList , prefixLen <- [1 .. len] , let prefix = word & Text.take prefixLen ] & Map.fromListWith (<>) {- closedForms (prefix, "") corpus = [(prefix, corpus & Set.size)] closedForms (prefix, suffix) corpus = let newPrefix = prefix <> ShortText.take 1 suffix in let newSuffix = suffix & ShortText.drop 1 in let corpusSize = corpus & Set.size in let corpusWithLongerPrefix = corpus & Set.filter (\t -> t & ShortText.isPrefixOf newPrefix) in if corpusSize == Set.size corpusWithLongerPrefix then closedForms corpus (newPrefix, newSuffix) else (prefix, corpusSize) : closedForms corpusWithLongerPrefix (newPrefix, newSuffix) -} dropSupraSegmentalFeatures = \case IPA.Syllable syl -> syl IPA.WithSuprasegmentalFeature _feat syl -> dropSupraSegmentalFeatures syl lcp :: [Text] -> Text lcp [] = [] -- use foldr1 to apply to the non-empty strings list given lcp lines = List.foldr1 mapCommonPrefix lines where mapCommonPrefix {-new-} :: Text {-acc-} -> Text -> Text mapCommonPrefix len1 len2 = Text.pack $ List.map fst $ List.takeWhile (uncurry (==)) $ Text.zip len1 len2 spec = do withoutTimeout do withoutRetries do describe "Wiktionary" do describe "fr" do describe "lang" do describe "fr" do around (\k -> SQL.withConnection "data/langs/français/kaikki/wiktionary=fr.lang=fr.sqlite3" k) do -- runWiktionaryQuery @(SQL.Only [Wiktionary.Sound]) -- "sounds" -- "SELECT sounds FROM wiktionary WHERE word=?" -- (SQL.Only ("exercice" :: Text)) describe "IPA" do -- do -- forM (["e", "ex", "exercice"] & list) \word -> do -- outPath <- goldenPath $ word -- it word \conn -> do -- res <- testIPAs conn (word & ShortText.pack) -- return $ goldenPrettyShowInstance outPath res let ipasDB = "data/langs/français/kaikki/wiktionary=fr.lang=fr.ipas.sqlite3" ipasDBExists <- IO.doesFileExist ipasDB & liftIO aroundWith ( \k wiktConn -> do SQL.withConnection ipasDB \ipasConn -> k (wiktConn, ipasConn) ) do withoutTimeout do unless (ipasDBExists) do it "can-create-ipas" \(wiktConn, ipasConn) -> do SQL.execute_ ipasConn $ "PRAGMA journal_mode = OFF" SQL.execute_ ipasConn $ "PRAGMA synchronous = OFF" -- SQL.execute_ ipasConn $ "PRAGMA mmap_size = " <> fromString (show (256 * 1024 * 1024 :: Int)) -- SQL.execute_ ipasConn $ "PRAGMA page_size = " <> fromString (show (512 * 8 * 2 :: Int)) -- SQL.execute_ ipasConn $ "VACUUM" SQL.execute_ ipasConn $ "CREATE TABLE IF NOT EXISTS broad_to_words (broad TEXT NON NULL, broads TEXT NON NULL, word TEXT NON NULL, wordID INTEGER NON NULL, UNIQUE (broad, word))" -- SQL.execute_ ipasConn $ "CREATE TABLE IF NOT EXISTS ipas_broad (wordID INTEGER NON NULL, broad1 TEXT NON NULL, word TEXT NON NULL, broad TEXT NON NULL, UNIQUE(broad, word), UNIQUE(broad1, word))" -- SQL.execute_ ipasConn $ "CREATE TABLE IF NOT EXISTS ipas_narrow (wordID INTEGER NON NULL, narrow1 TEXT NON NULL, word TEXT NON NULL, narrow TEXT NON NULL, UNIQUE(narrow, word), UNIQUE(narrow1, word))" -- SQL.execute_ ipasConn $ "CREATE TABLE IF NOT EXISTS ipas_error (wordID INTEGER NON NULL, error TEXT NON NULL, word TEXT NON NULL)" SQL.execute_ ipasConn "CREATE INDEX broad_to_words__broad ON broad_to_words (broad);" SQL.execute_ ipasConn "CREATE INDEX broad_to_words__broad_word ON broad_to_words (broad, word);" -- SQL.execute_ ipasConn "CREATE INDEX ipas_broad1 ON ipas_broad (broad1);" -- SQL.execute_ ipasConn "CREATE INDEX ipas_narrow1 ON ipas_narrow (narrow1);" -- SQL.execute_ ipasConn "DELETE FROM ipas" SQL.fold wiktConn "SELECT id,word,sounds FROM wiktionary WHERE lang_code='fr'" () (1 :: Int) \ !i ( (wordID :: Int) , maybeWord , (sounds :: [Wiktionary.Sound]) ) -> do -- iMax ~= 2075000 forM_ sounds \Wiktionary.Sound{..} -> do -- IO.hPrint IO.stderr (i, ident::Int, maybeWord) case (maybeWord, sound_ipa) of (Just word, Just (IPA.IPAPhons ipas)) -> do forM_ ipas \case IPA.IPAPhonemic ipaSyllables -> do let dropTonicAccent = ShortText.toText >>> Text.replace "'" "" when (i `mod` 5000 == 0) do IO.hPrint IO.stderr ( i , word , show (List.length ipaSyllables) , ipaSyllables & IPA.ipaWordsToText (Just IPA.Phonemic) ) SQL.executeMany ipasConn "INSERT OR IGNORE INTO broad_to_words (broad, broads, word, wordID) VALUES (?,?,?,?)" [ ( ipaSyl & dropSupraSegmentalFeatures & IPA.Syllable & IPA.toIPA_ & IPA.unIPA , ipaSyllables & IPA.ipaWordsToText Nothing , (word :: ShortText) , wordID ) | ipaWord :: NonEmpty (IPA.Syllable []) <- ipaSyllables & toList -- & foldMap (fmap IPA.toIPA_ >>> toList) , ipaSyl :: IPA.Syllable [] <- ipaWord & toList ] -- SQL.execute -- ipasConn -- "INSERT OR IGNORE INTO ipas_broad (wordID, broad1, word, broad) VALUES (?,?,?,?)" -- ( wordID -- , ipaSyllables & nonEmptyHead <&> IPA.toIPA_ & nonEmptyHead & IPA.unIPA -- , (word :: ShortText) -- , ipaSyllables & Wiktionary.ipaWordsToText IPA.Phonemic -- ) IPA.IPAPhonError (t, _err) -> do return () -- SQL.execute -- ipasConn -- "INSERT INTO ipas_error (word, error) VALUES (?,?)" -- ( (word :: ShortText) -- , t -- ) _ -> return () _ -> return () return (i + 1) return @IO () let ngramsDB = "data/langs/français/kaikki/wiktionary=fr.lang=fr.ngrams.sqlite3" ngramsDBExists <- IO.doesFileExist ngramsDB & liftIO aroundWith ( \k wiktConn -> do SQL.withConnection ngramsDB \ngramsConn -> k (wiktConn, ngramsConn) ) do withoutTimeout do unless (ngramsDBExists) do it "can-compute-ngrams" \(wiktConn, ngramsConn) -> do SQL.execute_ ngramsConn $ "PRAGMA journal_mode = OFF" SQL.execute_ ngramsConn $ "PRAGMA synchronous = OFF" SQL.execute_ ngramsConn $ "CREATE TABLE IF NOT EXISTS broad_to_ngrams (broad TEXT NON NULL, ngram TEXT NON NULL, count INT DEFAULT 1, UNIQUE (broad, ngram))" SQL.execute_ ngramsConn "CREATE INDEX broad_to_ngrams__broad ON broad_to_ngrams (broad);" SQL.execute_ ngramsConn "CREATE INDEX broad_to_ngrams__ngram ON broad_to_ngrams (ngram);" -- SQL.execute_ ngramsConn "CREATE INDEX broad_to_ngrams__broad_ngram ON broad_to_ngrams (broad, ngram);" SQL.execute_ ngramsConn $ "CREATE TABLE IF NOT EXISTS errors (wordID INTEGER NON NULL, word TEXT NON NULL, error TEXT NON NULL)" SQL.fold wiktConn "SELECT id,word,sounds FROM wiktionary WHERE lang_code='fr'" () (1 :: Int) \ !i ( (wordID :: Int) , maybeWord , (sounds :: [Wiktionary.Sound]) ) -> do forM_ sounds \Wiktionary.Sound{..} -> do -- IO.hPrint IO.stderr (i, ident::Int, maybeWord) case (maybeWord, sound_ipa) of (Just word, Just (IPA.IPAPhons ipas)) -> do forM_ ipas \case IPA.IPAPhonemic ipaSyllables -> do let ngrams = word & Wiktionary.ngramsWithinLengths 1 6 when (i `mod` 5000 == 0) do IO.hPrint IO.stderr (i, word, ngrams, ipaSyllables) SQL.executeMany ngramsConn "INSERT INTO broad_to_ngrams(broad,ngram) VALUES(?,?) ON CONFLICT(broad,ngram) DO UPDATE SET count=broad_to_ngrams.count+1;" [ ( broad , ngram & Text.toLower ) | wordIPA :: NonEmpty (IPA.Syllable []) <- ipaSyllables & toList , syllableIPA :: IPA.Syllable [] <- wordIPA & toList , let broad = syllableIPA & dropSupraSegmentalFeatures & IPA.Syllable & IPA.toIPA_ & IPA.unIPA , ngram <- ngrams ] IPA.IPAPhonError (errMsg, _err) -> do SQL.execute ngramsConn "INSERT INTO errors (wordID, word, error) VALUES (?,?,?)" ( wordID , word , errMsg ) _ -> return () _ -> return () return (i + 1) return @IO () let b2eDB = "data/langs/français/kaikki/wiktionary=fr.lang=fr.broads_to_expr.sqlite3" b2eDBExists <- IO.doesFileExist b2eDB & liftIO unless b2eDBExists do aroundWith (\k wiktConn -> SQL.withConnection b2eDB \b2eConn -> k (wiktConn, b2eConn)) do it "can-compute-broads_to_expr" do broadsToExprSQL "fr" describe "en" do describe "lang" do describe "en" do around (\k -> SQL.withConnection "data/langs/english/kaikki/wiktionary=en.lang=en.sqlite3" k) do describe "IPA" do let b2eDB = "data/langs/english/kaikki/wiktionary=en.lang=en.broads_to_expr.sqlite3" -- IO.removeFile b2eDB & liftIO b2eDBExists <- IO.doesFileExist b2eDB & liftIO unless b2eDBExists do aroundWith (\k wiktConn -> SQL.withConnection b2eDB \b2eConn -> k (wiktConn, b2eConn)) do it "can-compute-broads_to_expr" $ broadsToExprSQL "en" broadsToExprSQL :: Text -> (SQL.Connection, SQL.Connection) -> _ broadsToExprSQL lang_code (wiktConn, b2eConn) = do SQL.execute_ b2eConn $ "PRAGMA journal_mode = OFF" SQL.execute_ b2eConn $ "PRAGMA synchronous = OFF" SQL.execute_ b2eConn $ "CREATE TABLE IF NOT EXISTS broads (exprLit TEXT NON NULL, exprBroad TEXT NON NULL, sylBroad TEXT NON NULL, wordPos INTEGER NON NULL, sylPos INTEGER NON NULL, wordEnd INTEGER NON NULL, sylEnd INTEGER NON NULL)" SQL.execute_ b2eConn $ "CREATE INDEX broads__broad ON broads (sylBroad);" SQL.execute_ b2eConn $ "CREATE INDEX broads__sylPos ON broads (sylPos);" SQL.execute_ b2eConn $ "CREATE INDEX broads__exprLit ON broads (exprLit);" SQL.execute_ b2eConn $ "CREATE INDEX broads__broad_and_exprLit ON broads (sylBroad, exprLit);" SQL.execute_ b2eConn $ "CREATE TABLE IF NOT EXISTS errors (exprId INTEGER NON NULL, exprLit TEXT NON NULL, error TEXT NON NULL)" SQL.fold wiktConn "SELECT id,word,sounds FROM wiktionary WHERE lang_code=?" (SQL.Only lang_code) (1 :: Int) \ !i ( exprId :: Int , maybeWord :: Maybe Text , sounds :: [Wiktionary.Sound] ) -> do forM_ (sounds) \snd@Wiktionary.Sound{..} -> do -- pHPrint IO.stderr (i, exprId::Int, maybeWord, snd) let ipas | lang_code == "en" = sound_ipa <> sound_enpr | otherwise = sound_ipa case (maybeWord, ipas) of (Just exprLit, Just (IPA.IPAPhons exprIPAs)) -> do when (i `mod` 5000 == 0) do IO.hPrint IO.stderr (i, exprLit, exprIPAs) forM_ exprIPAs \case IPA.IPAPhonemic exprBroad -> do SQL.executeMany b2eConn "INSERT INTO broads(exprLit, exprBroad, sylBroad,wordPos,sylPos,wordEnd,sylEnd) VALUES(?,?,?,?,?,?,?);" $ [ ( exprLit , exprBroad & IPA.ipaWordsToText Nothing , sylBroad , wordPos , sylPos , wordEnd , sylEnd ) -- & traceShowId | let wordEnd = exprBroad & List.length & \x -> x - 1 , (wordPos, wordIPA :: NonEmpty (IPA.Syllable [])) <- exprBroad & toList & List.zip [0 :: Int ..] , let sylEnd = wordIPA & List.length & \x -> x - 1 , (sylPos, syllableIPA :: [IPA.Segment]) <- wordIPA & toList & mangleSupraSegmentalFeatures & List.zip [0 :: Int ..] , let sylBroad = syllableIPA & IPA.Syllable & IPA.toIPA_ & IPA.unIPA ] IPA.IPAPhonError (errMsg, _err) -> do SQL.execute b2eConn "INSERT INTO errors (exprId, exprLit, error) VALUES (?,?,?)" ( exprId , exprLit , errMsg ) _ -> return () _ -> return () return (i + 1) return @IO () {- let dbName = "broads_to_prefix" let b2pDB = "data/langs/français/kaikki/wiktionary=fr.lang=fr."<>dbName<>".sqlite3" b2pDBExists <- IO.doesFileExist b2pDB & liftIO aroundWith ( \k wiktConn -> do SQL.withConnection b2pDB \b2pConn -> k (wiktConn, b2pConn) ) do withoutTimeout do unless (b2pDBExists) do it ("can-compute-"<>dbName) \(wiktConn, b2pConn) -> do SQL.execute_ b2pConn $ "PRAGMA journal_mode = OFF" SQL.execute_ b2pConn $ "PRAGMA synchronous = OFF" SQL.execute_ b2pConn $ "CREATE TABLE IF NOT EXISTS broads (sylBroad TEXT NON NULL, litPrefix1 TEXT NON NULL, litPrefix2 TEXT, litPrefix3 TEXT, litPrefix4 TEXT, litPrefix5 TEXT)" SQL.execute_ b2pConn $ "CREATE INDEX broads__sylBroad ON broads (sylBroad);" SQL.execute_ b2pConn $ "CREATE INDEX broads__litPrefix1 ON broads (litPrefix1);" SQL.execute_ b2pConn $ "CREATE INDEX broads__litPrefix2 ON broads (litPrefix2);" SQL.execute_ b2pConn $ "CREATE INDEX broads__litPrefix3 ON broads (litPrefix3);" SQL.execute_ b2pConn $ "CREATE INDEX broads__litPrefix4 ON broads (litPrefix4);" SQL.execute_ b2pConn $ "CREATE INDEX broads__litPrefix5 ON broads (litPrefix5);" SQL.execute_ b2pConn $ "CREATE TABLE IF NOT EXISTS errors (exprId INTEGER NON NULL, exprLit TEXT NON NULL, error TEXT NON NULL)" SQL.fold wiktConn "SELECT id,word,sounds FROM wiktionary WHERE lang_code='fr'" () (1 :: Int) \ !i ( exprId :: Int , maybeWord :: Maybe Text , sounds :: [Wiktionary.Sound] ) -> do forM_ (sounds & List.take 1) \Wiktionary.Sound{..} -> do -- IO.hPrint IO.stderr (i, ident::Int, maybeWord) case (maybeWord, sound_ipa) of (Just exprLit, Just (IPA.IPAPhons exprIPAs)) -> do let exprLen = exprLit & Text.length forM_ exprIPAs \case IPA.IPAPhonemic exprBroads -> do when (i `mod` 5000 == 0) do IO.hPrint IO.stderr (i, exprLit, exprBroads) SQL.executeMany b2pConn "INSERT INTO broads(sylBroad, litPrefix1, litPrefix2, litPrefix3, litPrefix4, litPrefix5) VALUES(?,?,?,?,?,?);" $ [ ( sylBroad , litPrefix1 , litPrefix2 , litPrefix3 , litPrefix4 , litPrefix5 ) -- & traceShowId | let wordIPA = exprBroads & nonEmptyHead , let syllableIPA = wordIPA & nonEmptyHead , let sylBroad = syllableIPA & IPA.toIPA_ & IPA.unIPA , let litPrefix1 = exprLit & Text.take 1 , let litPrefix2 | 2 <= exprLen = Just $ exprLit & Text.take 2 | otherwise = Nothing , let litPrefix3 | 3 <= exprLen = Just $ exprLit & Text.take 3 | otherwise = Nothing , let litPrefix4 | 4 <= exprLen = Just $ exprLit & Text.take 4 | otherwise = Nothing , let litPrefix5 | 5 <= exprLen = Just $ exprLit & Text.take 5 | otherwise = Nothing ] IPA.IPAPhonError (errMsg, _err) -> do SQL.execute b2pConn "INSERT INTO errors (exprId, exprLit, error) VALUES (?,?,?)" ( exprId , exprLit , errMsg ) _ -> return () _ -> return () return (i + 1) return @IO () -} -- entrevue|\ɑ̃.tʁə.vy\ -- exercice|\ɛg.zɛʁ.sis\ -- exercice|\œ̃.n‿e.gzɛʁ.sis\ -- forM_ (["ɛg."] & list) \syllable -> do -- outPath <- goldenPath $ syllable -- it syllable \(wiktConn, ipasConn) -> do -- res :: [SQL.Only Text] <- SQL.query -- ipasConn -- "SELECT word FROM ipas_broad WHERE broad1=?" -- (SQL.Only ("ɛg."::Text)) -- let corpus = res <&> SQL.fromOnly & Set.fromList -- return $ goldenPrettyShowInstance outPath $ -- supports corpus {- do let testWord = "exercice" let title = "lcp-" <> ShortText.unpack testWord let db = "data/langs/français/kaikki/wiktionary=fr.lang=fr.ipas.sqlite3" outPath <- goldenPath title aroundWith (\k _ -> SQL.withConnection db k) do it title \ipasConn -> do let ipas :: [ShortText] = ["ɛɡ", "zɛʁ", "sis"] -- foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b res <- foldrM ( \ipa acc -> do corpus :: [SQL.Only ShortText] <- SQL.query ipasConn "SELECT LOWER(word) FROM ipas WHERE broad LIKE (?||'.%') OR broad=?" (ipa, ipa) -- return $ [ (ipa, word) | SQL.Only word <- corpus]<>acc return $ (ipa, corpus) : acc ) [] ipas return $ goldenPrettyShowInstance outPath $ [ (ipa, corpus & List.length) | (ipa, corpus) <- res ] -} -- closedForms (corpus & Set.fromList) ("", word) -- res & List.filter (\t -> t & Text.isPrefixOf "ex" & not) -- aroundWith (\k wiktDB -> k (wiktDB, "data/langs/français/kaikki/wiktionary=fr.lang=fr.ipas.sqlite3" :: FilePath)) do {- testIPAs :: SQL.Connection -> ShortText -> IO [IPA.IPA] testIPAs conn word = -- SQL.fold @(SQL.Only [Wiktionary.Sound]) conn "SELECT sounds FROM wiktionary WHERE word=?" (SQL.Only word) [] \ !acc (SQL.Only sounds) -> return (foldMap (\Wiktionary.Sound{sound_ipa} -> sound_ipa & maybeToList & foldMap Wiktionary.unIPAs) sounds List.++ acc) -} {- runWiktionaryFold "can-parse-it-all" ("SELECT " <> SQL.selectors @Wiktionary.Wiktionary <> " FROM wiktionary") () 0 (\ !(acc :: Int) (_row :: Wiktionary.Wiktionary) -> return (acc + 1)) -} runWiktionaryFold :: forall row params outers acc. SQL.ToRow params => SQL.FromRow row => Show acc => String -> SQL.Query -> params -> acc -> (acc -> row -> IO acc) -> TestDefM outers FilePath () runWiktionaryFold title qry params init merge = do outPath <- goldenPath title "txt" aroundWith (\k db -> SQL.withConnection db k) do withoutTimeout do withoutRetries do it title \conn -> do res <- SQL.fold conn qry params init merge return $ goldenPrettyShowInstance outPath res runWiktionaryQuery :: forall row params outers. SQL.FromRow row => Show row => SQL.ToRow params => String -> SQL.Query -> params -> TestDefM outers FilePath () runWiktionaryQuery title qry params = do outPath <- goldenPath title "txt" aroundWith (\k db -> SQL.withConnection db k) do withoutRetries do it title \conn -> do res :: [row] <- SQL.query conn qry params return $ goldenPrettyShowInstance outPath res {- wiktionaryToIPAs :: forall wiktRow wiktParams outers. SQL.FromRow wiktRow => Show wiktRow => SQL.ToRow wiktParams => String -> SQL.Query -> wiktParams -> (SQL.Connection -> IO ()) -> (SQL.Connection -> wiktRow -> IO ()) -> TestDefM outers (FilePath, FilePath) () wiktionaryToIPAs title wiktQry wiktParams init merge = do -- outPath <- goldenPath title aroundWith (\k (wiktDB, ipasDB) -> SQL.withConnection wiktDB \wiktConn -> SQL.withConnection ipasDB \ipasConn -> do init ipasConn k (wiktConn, ipasConn)) do withoutTimeout do withoutRetries do it title \(wiktConn, ipasConn) -> do -- () do SQL.fold wiktConn wiktQry wiktParams () \() row -> merge ipasConn row -}