dobutokO-effects-0.13.0.0: A library to deal with SoX effects and possibilities

Copyright(c) OleksandrZhabenko 2020
LicenseMIT
StabilityExperimental
Safe HaskellNone
LanguageHaskell2010

DobutokO.Sound.Effects.Silence

Description

Maintainer : olexandr543@yahoo.com

Helps to create experimental music. Can be used for applying the SoX "silence" effect.

Synopsis

Documentation

data Threshold a Source #

Constructors

T1 a 
D1 a 
P1 a 
Instances
Complex3ParamSet STSpecification2 Duration2 Threshold1 BTSpec Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.ComplexParamSet

Complex3ParamSet STSpecification1 Duration2 Threshold1 ATSpec Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.ComplexParamSet

FstParamSet3 a (Threshold a) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.FstParamSet

Methods

set13 :: a -> Threshold a -> Threshold a Source #

Eq a => Eq (Threshold a) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

Methods

(==) :: Threshold a -> Threshold a -> Bool #

(/=) :: Threshold a -> Threshold a -> Bool #

Show (Threshold Float) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

FstParam (Threshold a) a Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.FstParam

Methods

get1 :: Threshold a -> a Source #

Show (Silence LeftIntact ATSpec BTSpec) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

Show (BelowTSpec1 STSpecification2 Duration2 Threshold1) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

Show (AboveTSpec1 STSpecification1 Duration2 Threshold1) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

data Duration a b Source #

Constructors

B a 
T2 b 
M a b 
Instances
Complex3ParamSet STSpecification2 Duration2 Threshold1 BTSpec Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.ComplexParamSet

Complex3ParamSet STSpecification1 Duration2 Threshold1 ATSpec Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.ComplexParamSet

Complex2ParamSet a b (Duration a b) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.ComplexParamSet

Methods

set21c :: a -> b -> Duration a b Source #

SndParamSet3 b (Duration a b) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.SndParamSet

Methods

set23 :: b -> Duration a b -> Duration a b Source #

FstParamSet3 a (Duration a b) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.FstParamSet

Methods

set13 :: a -> Duration a b -> Duration a b Source #

(Eq a, Eq b) => Eq (Duration a b) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

Methods

(==) :: Duration a b -> Duration a b -> Bool #

(/=) :: Duration a b -> Duration a b -> Bool #

Show (Duration Int Float) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

SndParamM (Duration a b) b Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.SndParam

Methods

get2m :: Duration a b -> Maybe b Source #

FstParamM (Duration a b) a Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.FstParam

Methods

get1m :: Duration a b -> Maybe a Source #

Show (Silence LeftIntact ATSpec BTSpec) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

Show (BelowTSpec1 STSpecification2 Duration2 Threshold1) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

Show (AboveTSpec1 STSpecification1 Duration2 Threshold1) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

durationSet :: a -> b -> Int -> Duration a b Source #

data STSpec a b Source #

Analogical to TSpec but without the first argument (it is unneeded here).

Constructors

STs b 
STm a b 
STh a a b 
SS a 
Instances
Complex3ParamSet STSpecification1 Duration2 Threshold1 ATSpec Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.ComplexParamSet

(Eq b, Eq a) => Eq (STSpec a b) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

Methods

(==) :: STSpec a b -> STSpec a b -> Bool #

(/=) :: STSpec a b -> STSpec a b -> Bool #

Show (TimeSpec Above1TSpec NextTSpec) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

Show (STSpec Int Float) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

Show (Silence LeftIntact ATSpec BTSpec) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

Show (AboveTSpec1 STSpecification1 Duration2 Threshold1) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

data STSpec2 a b Source #

Constructors

STs2 b 
STm2 a b 
STh2 a a b 
SS2 a 
Instances
Complex3ParamSet STSpecification2 Duration2 Threshold1 BTSpec Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.ComplexParamSet

(Eq b, Eq a) => Eq (STSpec2 a b) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

Methods

(==) :: STSpec2 a b -> STSpec2 a b -> Bool #

(/=) :: STSpec2 a b -> STSpec2 a b -> Bool #

Show (TimeSpec BelowTSpec NextTSpec) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

Show (STSpec2 Int Float) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

Show (Silence LeftIntact ATSpec BTSpec) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

Show (BelowTSpec1 STSpecification2 Duration2 Threshold1) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

data AboveTSpec1 a b c Source #

Constructors

Z 
A a b c 
Instances
Complex3ParamSet STSpecification1 Duration2 Threshold1 ATSpec Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.ComplexParamSet

ThdParamSet3 c (AboveTSpec1 a b c) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.ThdParamSet

Methods

set33 :: c -> AboveTSpec1 a b c -> AboveTSpec1 a b c Source #

SndParamSet3 b (AboveTSpec1 a b c) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.SndParamSet

Methods

set23 :: b -> AboveTSpec1 a b c -> AboveTSpec1 a b c Source #

FstParamSet3 a (AboveTSpec1 a b c) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.FstParamSet

Methods

set13 :: a -> AboveTSpec1 a b c -> AboveTSpec1 a b c Source #

(Eq a, Eq b, Eq c) => Eq (AboveTSpec1 a b c) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

Methods

(==) :: AboveTSpec1 a b c -> AboveTSpec1 a b c -> Bool #

(/=) :: AboveTSpec1 a b c -> AboveTSpec1 a b c -> Bool #

Show (Silence LeftIntact ATSpec BTSpec) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

Show (AboveTSpec1 STSpecification1 Duration2 Threshold1) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

ThdParamM (AboveTSpec1 a b c) c Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.ThdParam

Methods

get3m :: AboveTSpec1 a b c -> Maybe c Source #

SndParamM (AboveTSpec1 a b c) b Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.SndParam

Methods

get2m :: AboveTSpec1 a b c -> Maybe b Source #

FstParamM (AboveTSpec1 a b c) a Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.FstParam

Methods

get1m :: AboveTSpec1 a b c -> Maybe a Source #

aboveTSpecSet1 :: a -> b -> c -> AboveTSpec1 a b c Source #

data BelowTSpec1 a b c Source #

Constructors

Z2 
BL a b c 
Instances
Complex3ParamSet STSpecification2 Duration2 Threshold1 BTSpec Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.ComplexParamSet

ThdParamSet3 c (BelowTSpec1 a b c) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.ThdParamSet

Methods

set33 :: c -> BelowTSpec1 a b c -> BelowTSpec1 a b c Source #

SndParamSet3 b (BelowTSpec1 a b c) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.SndParamSet

Methods

set23 :: b -> BelowTSpec1 a b c -> BelowTSpec1 a b c Source #

FstParamSet3 a (BelowTSpec1 a b c) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.FstParamSet

Methods

set13 :: a -> BelowTSpec1 a b c -> BelowTSpec1 a b c Source #

(Eq a, Eq b, Eq c) => Eq (BelowTSpec1 a b c) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

Methods

(==) :: BelowTSpec1 a b c -> BelowTSpec1 a b c -> Bool #

(/=) :: BelowTSpec1 a b c -> BelowTSpec1 a b c -> Bool #

Show (Silence LeftIntact ATSpec BTSpec) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

Show (BelowTSpec1 STSpecification2 Duration2 Threshold1) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

ThdParamM (BelowTSpec1 a b c) c Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.ThdParam

Methods

get3m :: BelowTSpec1 a b c -> Maybe c Source #

SndParamM (BelowTSpec1 a b c) b Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.SndParam

Methods

get2m :: BelowTSpec1 a b c -> Maybe b Source #

FstParamM (BelowTSpec1 a b c) a Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.FstParam

Methods

get1m :: BelowTSpec1 a b c -> Maybe a Source #

belowTSpecSet1 :: a -> b -> c -> BelowTSpec1 a b c Source #

data Silence a b c Source #

Constructors

SL2 a b 
SL3 a b c 
Instances
ThdParamSet3 c (Silence a b c) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.ThdParamSet

Methods

set33 :: c -> Silence a b c -> Silence a b c Source #

SndParamSet3 b (Silence a b c) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.SndParamSet

Methods

set23 :: b -> Silence a b c -> Silence a b c Source #

FstParamSet3 a (Silence a b c) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.FstParamSet

Methods

set13 :: a -> Silence a b c -> Silence a b c Source #

(Eq a, Eq b, Eq c) => Eq (Silence a b c) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

Methods

(==) :: Silence a b c -> Silence a b c -> Bool #

(/=) :: Silence a b c -> Silence a b c -> Bool #

Show (Silence LeftIntact ATSpec BTSpec) Source # 
Instance details

Defined in DobutokO.Sound.Effects.Silence

ThdParamM (Silence a b c) c Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.ThdParam

Methods

get3m :: Silence a b c -> Maybe c Source #

SndParam (Silence a b c) b Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.SndParam

Methods

get2 :: Silence a b c -> b Source #

FstParam (Silence a b c) a Source # 
Instance details

Defined in DobutokO.Sound.Effects.Classes.FstParam

Methods

get1 :: Silence a b c -> a Source #

silence1 :: Silence a b c -> a Source #

silence2 :: Silence a b c -> b Source #

silence3 :: Silence a b c -> Maybe c Source #

silenceSet1 :: a -> Silence a b c -> Silence a b c Source #

silenceSet2 :: b -> Silence a b c -> Silence a b c Source #

silenceSet3 :: c -> Silence a b c -> Silence a b c Source #