module Parameters where import qualified Rate import Text.Printf (printf, ) newtype Time = Time Float deriving (Eq, Ord, Show) newtype Freq = Freq Float deriving (Eq, Ord, Show) getTime :: Time -> Float getTime (Time t) = t getFreq :: Freq -> Float getFreq (Freq f) = f freq :: (Rate.C rate) => rate -> Freq -> Float freq sr (Freq f) = f / realToFrac (Rate.unpack sr) time :: (Rate.C rate) => rate -> Time -> Int time sr (Time t) = round (t * realToFrac (Rate.unpack sr)) timeCeil :: (Rate.C rate) => rate -> Time -> Int timeCeil sr (Time t) = ceiling (t * realToFrac (Rate.unpack sr)) toTime :: (Rate.C rate) => rate -> Int -> Double toTime rate n = fromIntegral n / Rate.unpack rate formatFreq :: Freq -> String formatFreq (Freq f) = printf "%.0fHz" f data T = Cons { hardLowDist, hardHighDist, softLowDist, softHighDist :: Time, minClickAttack :: Float, halfDiffDist :: Time, minClickDur :: Time, volumeFrequency :: Freq, envelopeFrequency :: Freq, emphasisExcess :: Float, raspingMinNumClicks :: Int, raspingMaxRelativeClickDistance :: Float, maxInterimRumblingDur :: Time, chirpingHackDur, chirpingMinDur, chirpingMaxDur :: Time, chirpingMainDurMaxDeviation :: Time, weakCounterSlopeSizes :: (Float, Float), sampleRate :: Rate.Sample, featureSampleRate :: Rate.Feature, measureSampleRate :: Rate.Measure, fourierBlockSize, fourierBlockStep :: Int } deflt :: T deflt = Cons { {- mode for high part of the advertisement call: 0.015 separation between low and high part of advertisement call: 0.018 modes for rasping: 0.026, 0.031 interval for regular values: 0.022 - 0.034 some outlier distances at the beginning: 0.049, 0.044, 0.047, 0.049, 0.048 some outlier distances within the rasping sound: 0.053, 0.082, 0.053 -} hardLowDist = Time 0.018, hardHighDist = Time 0.090, softLowDist = Time 0.022, softHighDist = Time 0.034, minClickAttack = 0.2, halfDiffDist = Time 0.0014, minClickDur = Time 0.025, volumeFrequency = Freq 10, envelopeFrequency = Freq 70, emphasisExcess = 1.1, raspingMinNumClicks = 3, raspingMaxRelativeClickDistance = 1.5, maxInterimRumblingDur = Time 0.1, chirpingHackDur = Time 0.08, chirpingMinDur = Time 0.15, chirpingMaxDur = Time 0.8, chirpingMainDurMaxDeviation = Time 0.01, -- value 3 avoids zero-length r1 intervals in training1500.WAV -- value 2 was better for counting clicks in some cases -- weakCounterSlopeSizesBand20 = (3,3), weakCounterSlopeSizes = (0.6,0.6), sampleRate = Rate.Sample 11025, featureSampleRate = Rate.Feature 200, measureSampleRate = Rate.Measure 200, -- Main.spectralParameters expects even block size fourierBlockSize = 256, fourierBlockStep = 128 }