-- | -- Module : Phladiprelio.Ukrainian.ReadDurations -- Copyright : (c) OleksandrZhabenko 2021-2023 -- License : MIT -- Stability : Experimental -- Maintainer : oleksandr.zhabenko@yahoo.com -- -- Functions to read the properties data from the files with the special Haskell-like syntaxis. {-# LANGUAGE BangPatterns, NoImplicitPrelude #-} module Phladiprelio.Ukrainian.ReadDurations where import GHC.Base import CaseBi.Arr (getBFstLSorted') import Phladiprelio.Ukrainian.SyllableDouble import Text.Read (readMaybe) import Data.Maybe import System.IO import GHC.List import Data.List (unlines,lines) import System.Directory (doesFileExist) import Phladiprelio.Ukrainian.Melodics {-| [(1,\"\1072\"),(2,\"\1077\"),(3,\"\1086\"),(4,\"\1091\"),(5,\"\1080\"),(6,\"\1110\"), (7,\"\1100\"),(8,\"\1076\1079\"),(10,\"\1078\"),(15,\"\1073\"),(17,\"\1076\"),(19,\"\1169\"),(21,\"\1075\"), (23,\"\1076\1078\"),(25,\"\1079\"),(27,\"\1081\"),(28,\"\1083\"),(30,\"\1084\"),(32,\"\1085\"),(34,\"\1088\"), (36,\"\1074\"),(38,\"\1094\"),(39,\"\1095\"),(41,\"\1096\"),(43,\"\1092\"),(45,\"\1082\"),(47,\"\1087\"), (49,\"\1089\"),(50,\"\1090\"),(52,\"\1093\"),(54,\"\1089\1100\"),(66,\"\1094\1100\"),(101,\"-\")] @ UZ \'A\' D дз (plain) 8 UZ \'A\' K дз (palatalized) 9 UZ \'B\' D ж (plain) 10 UZ \'B\' K ж (semi-palatalized) 11 UZ \'C\' S й 27 UZ \'D\' N сь 54 UZ \'E\' L ч (plain) 39 UZ \'E\' M ч (semi-palatalized) 40 UZ \'F\' L ш (plain) 41 UZ \'F\' M ш (semi-palatalized) 42 G 55 H 56 I 57 J 58 K 59 L 60 M 61 N нт 62 O ст 63 P ть 64 Q дзь 12 R зь 13 S нь 65 T дь 14 UZ \'a\' W а 1 UZ \'b\' D б (plain) 15 UZ \'b\' K б (semi-palatalized) 16 UZ \'c\' D ц (plain) 38 UZ \'d\' D д (plain) 17 UZ \'d\' K д (palatalized) 18 UZ \'e\' W е 2 UZ \'f\' L ф (plain) 43 UZ \'f\' M ф (semi-palatalized) 44 UZ \'g\' D ґ (plain) 19 UZ \'g\' K ґ (semi-palatalized) 20 UZ \'h\' D г (plain) 21 UZ \'h\' K г (semi-palatalized) 22 UZ \'i\' W і 6 UZ \'j\' D дж (plain) 23 UZ \'j\' K дж (palatalized) 24 UZ \'k\' L к (plain) 45 UZ \'k\' M к (semi-palatalized) 46 UZ \'l\' S л (plain) 28 UZ \'l\' O л (palatalized) 29 UZ \'m\' S м (plain) 30 UZ \'m\' O м (semi-palatalized) 31 UZ \'n\' S н (plain) 32 UZ \'n\' O н (palatalized) 33 UZ \'o\' W о 3 UZ \'p\' L п (plain) 47 UZ \'p\' M п (semi-palatalized) 48 UZ \'q\' E ь 7 UZ \'r\' S р (plain) 34 UZ \'r\' O р (palatalized) 35 UZ \'s\' L с (plain) 49 UZ \'t\' L т (plain) 50 UZ \'t\' M т (palatalized) 51 UZ \'u\' W у 4 UZ \'v\' S в (plain) 36 UZ \'v\' O в (semi-palatalized) 37 UZ \'w\' N ць 66 UZ \'x\' L х (plain) 52 UZ \'x\' M х (semi-palatalized) 53 UZ \'y\' W и 5 UZ \'z\' D з (plain) 25 UZ \'z\' K з (palatalized) 26 @ -} sound8s :: FlowSound sound8s = [1,2,3,4,5,6,7,8,9,10,11,15,16,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,39,40,41,42, 43,44,45,46,47,48,49,50,51,52,53,54,66,101] {-| The first number is the default value that corresponds usually to the word gap duration (and here is not important). The next 52 'Double' numbers become the durations of the above specified 'Sound8' values respectively, the order must be preserved (if you consider it important, well, it should be!). If some number in the file cannot be read as a 'Double' number the function uses the first one that can be instead (the default value). If no such is specified at all, then the default number is 1.0 for all the 'Sound8' sound representations that is hardly correct. -} readSound8ToDouble :: String -> (Double,[(Sound8, Double)]) readSound8ToDouble xs | null xs = (1.0,zip sound8s . replicate 10000 $ 1.0) | otherwise = let wws = lines xs dbls = map (\ks -> readMaybe ks::Maybe Double) wws dbH | null dbls || all isNothing dbls = 1.0 | otherwise = fromJust . head . filter isJust $ dbls dbSs = map (fromMaybe dbH) dbls (firstD,lsts) | null dbls = (1.0,zip sound8s . replicate 10000 $ 1.0) | otherwise = (dbH,zip sound8s (dbSs `mappend` replicate 10000 1.0)) in (firstD,lsts) divide2SDDs :: String -> [String] divide2SDDs ys | null tss = [unlines kss] | otherwise = unlines kss : divide2SDDs (unlines rss) where wwss = lines ys (kss,tss) = break (any (=='*')) wwss rss = dropWhile (any (== '*')) tss readSyllableDurations :: FilePath -> IO [[[[Sound8]]] -> [[Double]]] readSyllableDurations file = do exists <- doesFileExist file if exists then do xs <- readFile file let yss = take 9 . divide2SDDs $ xs readData = map readSound8ToDouble yss return . map (\(d,zs) -> syllableDurationsGDc (getBFstLSorted' d zs)) $ readData else return []