Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype SileroModel = SileroModel {}
- detectSpeech :: MonadIO m => SileroModel -> Vector Float -> m Float
- windowLength :: Int
- resetModel :: MonadIO m => SileroModel -> m ()
- sampleRate :: Int
- withModel :: MonadUnliftIO m => (SileroModel -> m a) -> m a
Documentation
newtype SileroModel Source #
Holds state to be used for voice activity detection. **Warning**: This is **NOT** thread-safe due to this mutating state internally.
Instances
Storable SileroModel Source # | |
Defined in Silero.Model sizeOf :: SileroModel -> Int # alignment :: SileroModel -> Int # peekElemOff :: Ptr SileroModel -> Int -> IO SileroModel # pokeElemOff :: Ptr SileroModel -> Int -> SileroModel -> IO () # peekByteOff :: Ptr b -> Int -> IO SileroModel # pokeByteOff :: Ptr b -> Int -> SileroModel -> IO () # peek :: Ptr SileroModel -> IO SileroModel # poke :: Ptr SileroModel -> SileroModel -> IO () # | |
Generic SileroModel Source # | |
Defined in Silero.Model type Rep SileroModel :: Type -> Type # from :: SileroModel -> Rep SileroModel x # to :: Rep SileroModel x -> SileroModel # | |
type Rep SileroModel Source # | |
Defined in Silero.Model type Rep SileroModel = D1 ('MetaData "SileroModel" "Silero.Model" "silero-vad-0.1.0.4-LLE8kAW4RRSB4MSAngBbdI" 'True) (C1 ('MetaCons "SileroModel" 'PrefixI 'True) (S1 ('MetaSel ('Just "api") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ptr ())))) |
detectSpeech :: MonadIO m => SileroModel -> Vector Float -> m Float Source #
Detect if speech is found within the given audio samples. This has the following requirements: - Must be 16khz sample rate. - Must be mono-channel. - Must be 16-bit audio. - Must contain exactly 512 samples.
| **Warning: SileroModel holds internal state and is NOT thread safe.**
windowLength :: Int Source #
resetModel :: MonadIO m => SileroModel -> m () Source #
- *Warning: SileroModel holds internal state and is NOT thread safe.**
sampleRate :: Int Source #
withModel :: MonadUnliftIO m => (SileroModel -> m a) -> m a Source #
- *Warning: SileroModel holds internal state and is NOT thread safe.**