Browse Source

Раздельный вывод уровня сигнала в форматах dB и LUFS

master
Maxim Lihachev 9 years ago
parent
commit
35b9ed9204
  1. 32
      level.hs

32
level.hs

@ -1,7 +1,7 @@
{-# LANGUAGE DeriveDataTypeable, RecordWildCards #-} {-# LANGUAGE DeriveDataTypeable, RecordWildCards #-}
-- Создан: Ср 28 сен 2016 10:18:53 -- Создан: Ср 28 сен 2016 10:18:53
-- Изменен: Чт 13 окт 2016 18:30:52 -- Изменен: Пт 14 окт 2016 11:45:06
import System.Console.CmdArgs import System.Console.CmdArgs
import System.Environment import System.Environment
@ -26,6 +26,10 @@ everyN n list = [take (n + n) $ drop (x-1) list | x <- [1, n..length list]]
convert :: (Show a, Read c) => a -> c convert :: (Show a, Read c) => a -> c
convert = read . show convert = read . show
-- Проверка на пустую строку
notEmpty :: String -> Bool
notEmpty = (/=) (show "")
-- ============================================================================= -- =============================================================================
-- Чтение данных аудиофайла -- Чтение данных аудиофайла
@ -46,6 +50,12 @@ float2db k x
| not (isNaN x) = fromIntegral k * (logBase 10 x) | not (isNaN x) = fromIntegral k * (logBase 10 x)
| otherwise = 0 | otherwise = 0
-- Вычисление уровня сигнала
calcLevel :: [Char] -> Int -> [Double] -> Int
calcLevel vu = case (map toLower vu) of
"lufs" -> calcLevelLUFS
"db" -> calcLevelDb
-- Вычисление уровня сигнала / Db -- Вычисление уровня сигнала / Db
calcLevelDb :: Int -> [Double] -> Int calcLevelDb :: Int -> [Double] -> Int
calcLevelDb fs samples = case dd of calcLevelDb fs samples = case dd of
@ -103,6 +113,13 @@ defaultOptions = cmdArgs $ Audioread {
vu = "db" &= typ "db/lufs" &= help "Type of vu scale" vu = "db" &= typ "db/lufs" &= help "Type of vu scale"
} &= summary "audioread v0.2: information about audiofiles" } &= summary "audioread v0.2: information about audiofiles"
describe :: (Show s) => Int -> String -> s -> String -> IO ()
describe o p ms s = let message = show ms in do
when (o == 1) $ putStr $ p
when (notEmpty message) $ putStr message
when (o == 1) $ putStr $ s
putStrLn ""
main :: IO () main :: IO ()
main = do main = do
args <- getArgs args <- getArgs
@ -113,16 +130,15 @@ main = do
let w = take (samples cmd) (audioread d) let w = take (samples cmd) (audioread d)
let exec fx = do let exec fx = do
when ((title cmd) == 1) $ putStrLn $ "\n---[ " ++ fx ++ " ]:" describe (title cmd) ("\n---[ " ++ fx) "" (" ]:")
case fx of case fx of
"samples" -> mapM_ print $ getChannel (map toUpper $ channel cmd) w "samples" -> mapM_ print $ getChannel (map toUpper $ channel cmd) w
"phase" -> print $ calcPhase w "phase" -> print $ calcPhase w
"db" -> do "level" -> do
print $ calcLevelDb (samples cmd) (getChannel "L" w) describe (title cmd) "L: "
print $ calcLevelDb (samples cmd) (getChannel "R" w) (calcLevel (vu cmd) (samples cmd) (getChannel "L" w)) (vu cmd)
"lufs" -> do describe (title cmd) "R: "
print $ calcLevelLUFS (samples cmd) (getChannel "L" w) (calcLevel (vu cmd) (samples cmd) (getChannel "R" w)) (vu cmd)
print $ calcLevelLUFS (samples cmd) (getChannel "R" w)
_ -> putStrLn $ "WARNING: Unknown type of information: " ++ fx ++ "\n" _ -> putStrLn $ "WARNING: Unknown type of information: " ++ fx ++ "\n"
mapM_ exec (splitOn "," $ info cmd) mapM_ exec (splitOn "," $ info cmd)

Loading…
Cancel
Save