-- | -- Module : Composition.Sound.ParseList -- Copyright : (c) OleksandrZhabenko 2020-2021 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Helps to create experimental music from a file (or its part) and a Ukrainian text. -- It can also generate a timbre for the notes. Uses SoX inside. {-# OPTIONS_GHC -threaded #-} module Composition.Sound.ParseList where import Data.Char (isSpace) --import qualified Data.Vector as V import Data.List import Data.Maybe (mapMaybe) import Text.Read (lex,readMaybe) import Data.Maybe (isNothing,fromMaybe) parseTup :: String -> [String] parseTup xs = map (dropWhile isSpace . fst) (takeWhile (/= ("","")) . iterate (head . lex . snd) $ head (lex xs)) containsExt :: [String] -> Bool containsExt = elem ".." -- | Predicate to check whether a list does not contain round parentheses or dash (a minus sign) as its elements. Is used internally in the -- 'parseStoLInts' function to avoid lists with negative elements. canBePreParseV :: [String] -> Bool canBePreParseV (xs:xss) = case xs of { "(" -> False ; "-" -> False ; ")" -> False ; ~bbb -> canBePreParseV xss } canBePreParseV _ = True -- | Notification. Uses an 'Int' limitation to avoid infinite lists. All arguments must be not negative. parseV :: Int -> [String] -> Maybe [Int] parseV n v | n >= 0 && findIndices (== "..") v == [2] && length v == 4 = if head v == "[" && (v !! 3) == "]" then let ins1 = readMaybe (v !! 1)::Maybe Int in case ins1 of Just ins -> if n <= ins then Just [ins] else Just [ins..n] Nothing -> Nothing else Nothing | n >= 0 && findIndices (== "..") v == [2] && length v == 5 = if head v == "[" && v !! 4 == "]" then let ins1 = readMaybe (v !! 1)::Maybe Int ins2 = readMaybe (v !! 3)::Maybe Int in case (ins1,ins2) of (Just ins01,Just ins02) -> if ins02 >= ins01 then Just [ins01..ins02] else Nothing _ -> Nothing else Nothing | n >= 0 && findIndices (== "..") v == [4] && length v == 6 = if head v == "[" && v !! 2 == "," && v !! 5 == "]" then let ins1 = readMaybe (v !! 1)::Maybe Int ins2 = readMaybe (v !! 3)::Maybe Int in case (ins1,ins2) of (Just ins01,Just ins02) -> case compare ins02 ins01 of GT -> if compare n ins02 /= LT then Just [ins01,ins02..n] else Just [ins01,ins02] EQ -> Just [ins01] _ -> Just [ins01,ins02..0] _ -> Nothing else Nothing | n >= 0 && findIndices (== "..") v == [4] && length v == 7 = if head v == "[" && v !! 2 == "," && v !! 6 == "]" then let ins1 = readMaybe (v !! 1)::Maybe Int ins2 = readMaybe (v !! 3)::Maybe Int ins3 = readMaybe (v !! 5)::Maybe Int in case (ins1,ins2,ins3) of (Just ins01,Just ins02,Just ins03) -> if null [ins01,ins02..ins03] then Nothing else Just [ins01,ins02..ins03] _ -> Nothing else Nothing | n >= 0 && head v == "[" && v !! (length v - 1) == "]" && length v `rem` 2 == 1 && findIndices (== ",") v == [2,4..(length v - 2)] = let insV1 = map (\(i, _) -> readMaybe (v !! (2 * i + 1))::Maybe Int) . zip [0..] . take (length v `quot` 2) $ v in if any isNothing insV1 then Nothing else Just (mapMaybe id insV1) | otherwise = Nothing -- | From the 0.19.0.0 version. Can be used to parse also into infinite lists. parseVInf :: [String] -> Maybe [Int] parseVInf v | findIndices (== "..") v == [2] && length v == 4 = if head v == "[" && v !! 3 == "]" then let ins1 = readMaybe (v !! 1)::Maybe Int in case ins1 of Just ins -> Just [ins..] Nothing -> Nothing else Nothing | findIndices (== "..") v == [2] && length v == 5 = if head v == "[" && v !! 4 == "]" then let ins1 = readMaybe (v !! 1)::Maybe Int ins2 = readMaybe (v !! 3)::Maybe Int in case (ins1,ins2) of (Just ins01,Just ins02) -> if ins02 >= ins01 then Just [ins01..ins02] else Nothing _ -> Nothing else Nothing | findIndices (== "..") v == [4] && length v == 6 = if head v == "[" && v !! 2 == "," && v !! 5 == "]" then let ins1 = readMaybe (v !! 1)::Maybe Int ins2 = readMaybe (v !! 3)::Maybe Int in case (ins1,ins2) of (Just ins01,Just ins02) -> Just [ins01,ins02..] _ -> Nothing else Nothing | findIndices (== "..") v == [4] && length v == 7 = if head v == "[" && v !! 2 == "," && v !! 6 == "]" then let ins1 = readMaybe (v !! 1)::Maybe Int ins2 = readMaybe (v !! 3)::Maybe Int ins3 = readMaybe (v !! 5)::Maybe Int in case (ins1,ins2,ins3) of (Just ins01,Just ins02,Just ins03) -> if null [ins01,ins02..ins03] then Nothing else Just [ins01,ins02..ins03] _ -> Nothing else Nothing | head v == "[" && v !! (length v - 1) == "]" && length v `rem` 2 == 1 && findIndices (== ",") v == [2,4..(length v - 2)] = let insV1 = map (\(i, _) -> readMaybe (v !! (2 * i + 1))::Maybe Int) . zip [0..] . take (length v `quot` 2) $ v in if any isNothing insV1 then Nothing else Just (mapMaybe id insV1) | otherwise = Nothing -- | Parses a 'String' being a list of Ints written with Haskell rules, e. g. \"[1..]\", \"[2,4..45]\", \"[3,5,6,7,8,3]\" etc. into a list of 'Int'. -- If it is not possible or list is empty, returns []. Preceding whitespaces are ignored. An 'Int' argument is used as a delimiter to avoid infinite lists. parseStoLInts :: Int -> String -> [Int] parseStoLInts n xs | canBePreParseV . parseTup . dropWhile isSpace $ xs = fromMaybe [] (parseV n (parseTup . dropWhile isSpace $ xs)) | otherwise = []