| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.ByteString.Mp4.Boxes.AudioSpecificConfig
Contents
Description
mp4a Audio sample entry according to ISO 14496-14
Synopsis
- type AudioConfigAacLc freq channels = AudioConfigAacMinimal AacLc DefaultGASpecificConfig freq channels
 - type AudioConfigHeAac freq channels = AudioConfigSbrExplicitHierachical AacLc DefaultGASpecificConfig freq channels freq
 - data AudioConfigAacMinimal :: AudioObjectTypeId -> Extends AudioSubConfig -> Extends (EnumOf SamplingFreqTable) -> Extends (EnumOf ChannelConfigTable) -> Extends (DecoderSpecificInfo AudioIso14496_3 AudioStream)
 - data AudioConfigSbrExplicitHierachical :: AudioObjectTypeId -> Extends AudioSubConfig -> Extends (EnumOf SamplingFreqTable) -> Extends (EnumOf ChannelConfigTable) -> Extends (EnumOf SamplingFreqTable) -> Extends (DecoderSpecificInfo AudioIso14496_3 AudioStream)
 - type AudioConfigCommon aoId samplingFrequencyIndex channels rest = ((AudioObjectTypeRec aoId :+: BitRecordOfEnum samplingFrequencyIndex) :+: BitRecordOfEnum channels) :+: rest
 - data AudioObjectTypeId
- = AacMain
 - | AacLc
 - | AacSsr
 - | AacLtp
 - | Sbr
 - | AacScalable
 - | TwinVq
 - | Celp
 - | Hvxc
 - | AoReserved1
 - | AoReserved2
 - | Ttsi
 - | MainSunthetic
 - | WavetableSynthesis
 - | GeneralMidi
 - | AlgorithmicSynthesisAndAudioFx
 - | ErAacLc
 - | AoReserved3
 - | ErAacLtp
 - | ErAacScalable
 - | ErTwinVq
 - | ErBsac
 - | ErAacLd
 - | ErCelp
 - | ErHvxc
 - | ErHiln
 - | ErParametric
 - | Ssc
 - | AoReserved4
 - | AoReserved5
 - | AoCustom
 - | AoLayer1
 - | AoLayer2
 - | AoLayer3
 - | AoDst
 - | AotInvalid
 
 - type AudioObjectTypeRec n = AudioObjectTypeField1 (FromEnum AudioObjectTypeId n) .+: AudioObjectTypeField2 (FromEnum AudioObjectTypeId n)
 - type family AudioObjectTypeField1 (n :: Nat) :: Extends (BitRecordField (MkFieldBits :: BitField (B 5) Nat 5)) where ...
 - type family AudioObjectTypeField2 (n :: Nat) :: BitRecord where ...
 - type SamplingFreq = ExtEnum SamplingFreqTable 4 SFCustom (Field 24)
 - data SamplingFreqTable
 - sampleRateToNumber :: Num a => SamplingFreqTable -> a
 - sampleRateToEnum :: SamplingFreqTable -> EnumValue SamplingFreqTable
 - type ChannelConfig = FixedEnum ChannelConfigTable 4
 - data ChannelConfigTable
 - channelConfigToNumber :: Num a => ChannelConfigTable -> a
 - channelConfigToEnum :: ChannelConfigTable -> EnumValue ChannelConfigTable
 - data AudioSubConfig :: Type
 - type family BitRecordOfAudioSubConfig (x :: Extends AudioSubConfig) :: BitRecord
 - data GASpecificConfig (frameLenFlag :: Extends (FieldValue "frameLenFlag" Bool)) (coreCoderDelay :: Maybe (Extends (FieldValue "coreCoderDelay" Nat))) (extension :: Extends GASExtension) :: Extends AudioSubConfig
 - type DefaultGASpecificConfig = GASpecificConfig (StaticFieldValue "frameLenFlag" False) Nothing MkGASExtension
 - data GASExtension
 - data MkGASExtension :: Extends GASExtension
 - type BitRecordOfGASExtension (x :: Extends GASExtension) = BitRecordMember (("has-gas-extension" @: Flag) := False)
 
Decoder Configuration for ISO 14496-3 (Audio)
type AudioConfigAacLc freq channels = AudioConfigAacMinimal AacLc DefaultGASpecificConfig freq channels Source #
A audio config using AudioConfigAacMinimal for AAC-LC.
type AudioConfigHeAac freq channels = AudioConfigSbrExplicitHierachical AacLc DefaultGASpecificConfig freq channels freq Source #
A audio config using AudioConfigSbrExplicitHierachical for HE-AAC (v1) in
 dual rate mode.
data AudioConfigAacMinimal :: AudioObjectTypeId -> Extends AudioSubConfig -> Extends (EnumOf SamplingFreqTable) -> Extends (EnumOf ChannelConfigTable) -> Extends (DecoderSpecificInfo AudioIso14496_3 AudioStream) Source #
A minimalistic audio config without sync and error protection
Instances
| type From (AudioConfigAacMinimal aoId subCfg freq channels :: DecoderSpecificInfo AudioIso14496_3 AudioStream -> Type) Source # | |
Defined in Data.ByteString.Mp4.Boxes.AudioSpecificConfig type From (AudioConfigAacMinimal aoId subCfg freq channels :: DecoderSpecificInfo AudioIso14496_3 AudioStream -> Type) = (MkDecoderSpecificInfo (AudioConfigCommon aoId freq channels (BitRecordOfAudioSubConfig subCfg)) :: DecoderSpecificInfo AudioIso14496_3 AudioStream)  | |
data AudioConfigSbrExplicitHierachical :: AudioObjectTypeId -> Extends AudioSubConfig -> Extends (EnumOf SamplingFreqTable) -> Extends (EnumOf ChannelConfigTable) -> Extends (EnumOf SamplingFreqTable) -> Extends (DecoderSpecificInfo AudioIso14496_3 AudioStream) Source #
A audio config with SBR signalled explicit and hierachical
Instances
| type From (AudioConfigSbrExplicitHierachical aoId subCfg freq channels extFreq :: DecoderSpecificInfo AudioIso14496_3 AudioStream -> Type) Source # | |
Defined in Data.ByteString.Mp4.Boxes.AudioSpecificConfig type From (AudioConfigSbrExplicitHierachical aoId subCfg freq channels extFreq :: DecoderSpecificInfo AudioIso14496_3 AudioStream -> Type) = (MkDecoderSpecificInfo (AudioConfigCommon Sbr freq channels ((BitRecordOfEnum extFreq :+: AudioObjectTypeRec aoId) :+: BitRecordOfAudioSubConfig subCfg)) :: DecoderSpecificInfo AudioIso14496_3 AudioStream)  | |
type AudioConfigCommon aoId samplingFrequencyIndex channels rest = ((AudioObjectTypeRec aoId :+: BitRecordOfEnum samplingFrequencyIndex) :+: BitRecordOfEnum channels) :+: rest Source #
Common header for audio specific config
Audio Object Type
data AudioObjectTypeId Source #
Constructors
| AacMain | ISO 14496-4 subpart 4  | 
| AacLc | ISO 14496-4 subpart 4  | 
| AacSsr | ISO 14496-4 subpart 4  | 
| AacLtp | ISO 14496-4 subpart 4  | 
| Sbr | ISO 14496-4 subpart 4  | 
| AacScalable | ISO 14496-4 subpart 4  | 
| TwinVq | ISO 14496-4 subpart 4  | 
| Celp | ISO 14496-4 subpart 3  | 
| Hvxc | ISO 14496-4 subpart 2  | 
| AoReserved1 | |
| AoReserved2 | |
| Ttsi | ISO 14496-4 subpart 6  | 
| MainSunthetic | ISO 14496-4 subpart 5  | 
| WavetableSynthesis | ISO 14496-4 subpart 5  | 
| GeneralMidi | ISO 14496-4 subpart 5  | 
| AlgorithmicSynthesisAndAudioFx | ISO 14496-4 subpart 5  | 
| ErAacLc | ISO 14496-4 subpart 4  | 
| AoReserved3 | |
| ErAacLtp | ISO 14496-4 subpart 4  | 
| ErAacScalable | ISO 14496-4 subpart 4  | 
| ErTwinVq | ISO 14496-4 subpart 4  | 
| ErBsac | ISO 14496-4 subpart 4  | 
| ErAacLd | ISO 14496-4 subpart 4  | 
| ErCelp | ISO 14496-4 subpart 3  | 
| ErHvxc | ISO 14496-4 subpart 2  | 
| ErHiln | ISO 14496-4 subpart 7  | 
| ErParametric | ISO 14496-4 subpart 2 or 7  | 
| Ssc | ISO 14496-4 subpart 8  | 
| AoReserved4 | |
| AoReserved5 | |
| AoCustom | |
| AoLayer1 | ISO 14496-4 subpart 9  | 
| AoLayer2 | ISO 14496-4 subpart 9  | 
| AoLayer3 | ISO 14496-4 subpart 9  | 
| AoDst | ISO 14496-4 subpart 10  | 
| AotInvalid | 
Instances
type AudioObjectTypeRec n = AudioObjectTypeField1 (FromEnum AudioObjectTypeId n) .+: AudioObjectTypeField2 (FromEnum AudioObjectTypeId n) Source #
type family AudioObjectTypeField1 (n :: Nat) :: Extends (BitRecordField (MkFieldBits :: BitField (B 5) Nat 5)) where ... Source #
type family AudioObjectTypeField2 (n :: Nat) :: BitRecord where ... Source #
Equations
| AudioObjectTypeField2 n = If (n <=? 30) EmptyBitRecord (BitRecordMember (Field 6 := (n - 31))) | 
Sampling Frequency
type SamplingFreq = ExtEnum SamplingFreqTable 4 SFCustom (Field 24) Source #
data SamplingFreqTable Source #
Constructors
| SF96000 | |
| SF88200 | |
| SF64000 | |
| SF48000 | |
| SF44100 | |
| SF32000 | |
| SF24000 | |
| SF22050 | |
| SF16000 | |
| SF12000 | |
| SF11025 | |
| SF8000 | |
| SF7350 | |
| SFReserved1 | |
| SFReserved2 | |
| SFCustom | 
Instances
| type FromEnum SamplingFreqTable SF96000 Source # | |
| type FromEnum SamplingFreqTable SF88200 Source # | |
| type FromEnum SamplingFreqTable SF64000 Source # | |
| type FromEnum SamplingFreqTable SF48000 Source # | |
| type FromEnum SamplingFreqTable SF44100 Source # | |
| type FromEnum SamplingFreqTable SF32000 Source # | |
| type FromEnum SamplingFreqTable SF24000 Source # | |
| type FromEnum SamplingFreqTable SF22050 Source # | |
| type FromEnum SamplingFreqTable SF16000 Source # | |
| type FromEnum SamplingFreqTable SF12000 Source # | |
| type FromEnum SamplingFreqTable SF11025 Source # | |
| type FromEnum SamplingFreqTable SF8000 Source # | |
| type FromEnum SamplingFreqTable SF7350 Source # | |
| type FromEnum SamplingFreqTable SFReserved1 Source # | |
| type FromEnum SamplingFreqTable SFReserved2 Source # | |
| type FromEnum SamplingFreqTable SFCustom Source # | |
sampleRateToNumber :: Num a => SamplingFreqTable -> a Source #
Channel Config (Mono, Stereo, 7-1 Surround, ...)
type ChannelConfig = FixedEnum ChannelConfigTable 4 Source #
data ChannelConfigTable Source #
Constructors
| GasChannelConfig | |
| SingleChannel | |
| ChannelPair | |
| SinglePair | |
| SinglePairSingle | |
| SinglePairPair | |
| SinglePairPairLfe | |
| SinglePairPairPairLfe | 
Instances
channelConfigToNumber :: Num a => ChannelConfigTable -> a Source #
More Specific audio decoder config
data AudioSubConfig :: Type Source #
Instances
| type From (GASpecificConfig fl cd ext :: AudioSubConfig -> Type) Source # | |
Defined in Data.ByteString.Mp4.Boxes.AudioSpecificConfig type From (GASpecificConfig fl cd ext :: AudioSubConfig -> Type) = (TypeError (Text "AudioSubConfig is abstract!") :: AudioSubConfig)  | |
type family BitRecordOfAudioSubConfig (x :: Extends AudioSubConfig) :: BitRecord Source #
Instances
| type BitRecordOfAudioSubConfig (GASpecificConfig fl cd ext) Source # | |
Defined in Data.ByteString.Mp4.Boxes.AudioSpecificConfig type BitRecordOfAudioSubConfig (GASpecificConfig fl cd ext) = ((Flag :~ fl) .+: (FlagJust cd .+: (Field 14 :+? cd))) :+: BitRecordOfGASExtension ext  | |
data GASpecificConfig (frameLenFlag :: Extends (FieldValue "frameLenFlag" Bool)) (coreCoderDelay :: Maybe (Extends (FieldValue "coreCoderDelay" Nat))) (extension :: Extends GASExtension) :: Extends AudioSubConfig Source #
Instances
| type From (GASpecificConfig fl cd ext :: AudioSubConfig -> Type) Source # | |
Defined in Data.ByteString.Mp4.Boxes.AudioSpecificConfig type From (GASpecificConfig fl cd ext :: AudioSubConfig -> Type) = (TypeError (Text "AudioSubConfig is abstract!") :: AudioSubConfig)  | |
| type BitRecordOfAudioSubConfig (GASpecificConfig fl cd ext) Source # | |
Defined in Data.ByteString.Mp4.Boxes.AudioSpecificConfig type BitRecordOfAudioSubConfig (GASpecificConfig fl cd ext) = ((Flag :~ fl) .+: (FlagJust cd .+: (Field 14 :+? cd))) :+: BitRecordOfGASExtension ext  | |
type DefaultGASpecificConfig = GASpecificConfig (StaticFieldValue "frameLenFlag" False) Nothing MkGASExtension Source #
data GASExtension Source #
TODO implment that GAS extensions
data MkGASExtension :: Extends GASExtension Source #
type BitRecordOfGASExtension (x :: Extends GASExtension) = BitRecordMember (("has-gas-extension" @: Flag) := False) Source #