|
|
|
@ -1,16 +1,21 @@
@@ -1,16 +1,21 @@
|
|
|
|
|
{-# LANGUAGE DeriveDataTypeable, RecordWildCards #-} |
|
|
|
|
|
|
|
|
|
-- Создан: Ср 28 сен 2016 10:18:53 |
|
|
|
|
-- Изменен: Чт 29 сен 2016 18:50:35 |
|
|
|
|
-- Изменен: Пт 30 сен 2016 12:52:29 |
|
|
|
|
|
|
|
|
|
import System.Console.CmdArgs.Explicit |
|
|
|
|
import System.Console.CmdArgs |
|
|
|
|
import System.Environment |
|
|
|
|
import System.Directory |
|
|
|
|
import Control.Monad |
|
|
|
|
import Data.WAVE |
|
|
|
|
import Data.Char |
|
|
|
|
import Data.List |
|
|
|
|
import Data.List.Split |
|
|
|
|
|
|
|
|
|
-- ============================================================================= |
|
|
|
|
|
|
|
|
|
-- Среднее значение списка |
|
|
|
|
median :: Fractional a => [a] -> a |
|
|
|
|
median l = let (t,n) = foldl' (\(b,c) a -> (a+b,c+1)) (0,0) l in t/n |
|
|
|
|
|
|
|
|
|
-- ============================================================================= |
|
|
|
@ -21,14 +26,14 @@ audioread file = map samplesToDouble (waveSamples file)
@@ -21,14 +26,14 @@ audioread file = map samplesToDouble (waveSamples file)
|
|
|
|
|
where samplesToDouble (l:r:[]) = [sampleToDouble l, sampleToDouble r] |
|
|
|
|
|
|
|
|
|
--Выбор канала из пары |
|
|
|
|
channel :: [Char] -> [[Double]] -> [Double] |
|
|
|
|
channel ch (xs) = map selectChannel xs where |
|
|
|
|
getChannel :: [Char] -> [[Double]] -> [Double] |
|
|
|
|
getChannel ch (xs) = map selectChannel xs where |
|
|
|
|
selectChannel (l:r:[]) | ch == "R" = r |
|
|
|
|
| ch == "L" = l |
|
|
|
|
| otherwise = l |
|
|
|
|
|
|
|
|
|
-- Вычисление уровня сигнала |
|
|
|
|
-- calcLevel :: Int -> [Double] -> Int |
|
|
|
|
calcLevel :: Int -> [Double] -> Int |
|
|
|
|
calcLevel fs samples = case dd of |
|
|
|
|
[] -> -52 -- Неслышимый звук |
|
|
|
|
_ -> round (median dd) |
|
|
|
@ -39,6 +44,7 @@ calcLevel fs samples = case dd of
@@ -39,6 +44,7 @@ calcLevel fs samples = case dd of
|
|
|
|
|
slices = splitWhen (== 0) $ take fs samples; |
|
|
|
|
|
|
|
|
|
-- Вычисление значения фазы |
|
|
|
|
calcPhase :: (Ord a, Fractional a) => [[a]] -> a |
|
|
|
|
calcPhase samples = 2 * median (map ph (zip3 samples (drop 1 samples) (drop 2 samples))) - 1 where |
|
|
|
|
ph ([0,0], [l2,r2], [l3,r3]) | (signum l2 /= signum r2) && (signum l3 /= signum r3) = 0 |
|
|
|
|
| otherwise = 1 |
|
|
|
@ -52,35 +58,45 @@ calcPhase samples = 2 * median (map ph (zip3 samples (drop 1 samples) (drop 2 sa
@@ -52,35 +58,45 @@ calcPhase samples = 2 * median (map ph (zip3 samples (drop 1 samples) (drop 2 sa
|
|
|
|
|
|
|
|
|
|
-- ============================================================================= |
|
|
|
|
|
|
|
|
|
-- Справка по использованию |
|
|
|
|
usage bin = mapM_ putStrLn [ |
|
|
|
|
"Использование: " ++ bin ++ " [функция] file.wav [параметры]" |
|
|
|
|
"Функции:", |
|
|
|
|
" -samples N file.wav CH - вывод Ν сэмплов канала CH (L или R)", |
|
|
|
|
" -level N file.wav - расчёт уровня сигнала по N сэмплам", |
|
|
|
|
" -phase N file.wav - расчёт значения фазы по N сэмплам"] |
|
|
|
|
-- Параметры |
|
|
|
|
data Audioread = Audioread { |
|
|
|
|
info :: String, |
|
|
|
|
samples :: Int, |
|
|
|
|
channel :: String, |
|
|
|
|
file :: String, |
|
|
|
|
title :: Int |
|
|
|
|
} deriving (Show, Data,Typeable) |
|
|
|
|
|
|
|
|
|
-- Стандартные значения и описания параметров |
|
|
|
|
defaultOptions :: IO Audioread |
|
|
|
|
defaultOptions = cmdArgs $ Audioread { |
|
|
|
|
file = "none" &= typ "FILE.WAV" &= help "File for analysis", |
|
|
|
|
info = "none" &= typ "samples,phase,level" &= help "Type of information", |
|
|
|
|
samples = 1200 &= typ "12000" &= help "Number of samples for analysis", |
|
|
|
|
channel = "L" &= typ "L/R" &= help "Channel from stereo stream", |
|
|
|
|
title = 0 &= typ "1/0" &= help "File for analysis" |
|
|
|
|
} &= summary "audioread v0.2: information about audiofiles" |
|
|
|
|
|
|
|
|
|
main :: IO () |
|
|
|
|
main = do |
|
|
|
|
bin <- getProgName |
|
|
|
|
cmd <- getArgs |
|
|
|
|
if (cmd /= [] && isInfixOf ".wav" (cmd!!2)) then do |
|
|
|
|
w <- getWAVEFile (cmd!!2) |
|
|
|
|
let s = read (cmd!!1) :: Int |
|
|
|
|
case cmd of |
|
|
|
|
-- Вывод сэмплов аудиофайла |
|
|
|
|
["-samples", samples, file, ch] -> |
|
|
|
|
mapM_ print $ channel ch (take s (audioread w)) |
|
|
|
|
-- Вывод уровня сигнала для левого и правого каналов |
|
|
|
|
["-level", samples, file] -> do |
|
|
|
|
print $ calcLevel s (channel "L" (take s (audioread w))) |
|
|
|
|
print $ calcLevel s (channel "R" (take s (audioread w))) |
|
|
|
|
-- Вывод значения фазы |
|
|
|
|
["-phase", samples, file] -> |
|
|
|
|
print $ calcPhase (take s (audioread w)) |
|
|
|
|
-- Справка по использованию |
|
|
|
|
_ -> |
|
|
|
|
usage bin |
|
|
|
|
else |
|
|
|
|
usage bin |
|
|
|
|
args <- getArgs |
|
|
|
|
cmd <- (if null args then withArgs ["--help"] else id) defaultOptions |
|
|
|
|
|
|
|
|
|
if (isInfixOf ".wav" $ file cmd) then do |
|
|
|
|
d <- getWAVEFile $ file cmd |
|
|
|
|
let w = take (samples cmd) (audioread d) |
|
|
|
|
|
|
|
|
|
let exec fx = do |
|
|
|
|
when ((title cmd) == 1) $ putStrLn $ "\n---[ " ++ fx ++ " ]:" |
|
|
|
|
case fx of |
|
|
|
|
"samples" -> mapM_ print $ getChannel (map toUpper $ channel cmd) w |
|
|
|
|
"phase" -> print $ calcPhase w |
|
|
|
|
"level" -> do |
|
|
|
|
print $ calcLevel (samples cmd) (getChannel "L" w) |
|
|
|
|
print $ calcLevel (samples cmd) (getChannel "R" w) |
|
|
|
|
_ -> putStrLn $ "WARNING: Unknown type of information: " ++ fx ++ "\n" |
|
|
|
|
|
|
|
|
|
mapM_ exec (splitOn "," $ info cmd) |
|
|
|
|
else do |
|
|
|
|
putStrLn "ERROR: You must specify a correct filename." |
|
|
|
|
|
|
|
|
|