Browse Source

v0.2

master
Maxim Lihachev 9 years ago
parent
commit
5b1fae5018
  1. 82
      level.hs

82
level.hs

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

Loading…
Cancel
Save