isobmff-0.14.0.0: A parser and generator for the ISO-14496-12/14 base media file format

Safe HaskellNone
LanguageHaskell2010

Data.Kind.Extra

Synopsis

Documentation

type Extends a = (a -> Type :: Type) Source #

Indicates that a type constructs another.

type Konst (a :: k) = ((:~:) a :: Extends k) Source #

A Konst a, Extends a.

data (a :: k) :~: (b :: k) :: forall k. k -> k -> Type infix 4 #

Propositional equality. If a :~: b is inhabited by some terminating value, then the type a is the same as the type b. To use this equality in practice, pattern-match on the a :~: b to get out the Refl constructor; in the body of the pattern-match, the compiler knows that a ~ b.

Since: base-4.7.0.0

Instances
Category ((:~:) :: k -> k -> Type)

Since: base-4.7.0.0

Instance details

Defined in Control.Category

Methods

id :: a :~: a #

(.) :: (b :~: c) -> (a :~: b) -> a :~: c #

TestEquality ((:~:) a :: k -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

testEquality :: (a :~: a0) -> (a :~: b) -> Maybe (a0 :~: b) #

HasFunctionBuilder BitBuilder (Proxy nested) => HasFunctionBuilder BitBuilder (Proxy (Konst nested)) Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToFunction BitBuilder (Proxy (Konst nested)) r :: Type #

DynamicContent BitBuilder (Proxy nested) rt => DynamicContent BitBuilder (Proxy (Konst nested)) rt Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Methods

addParameter :: Proxy (Konst nested) -> FunctionBuilder BitBuilder next (rt -> next) #

a ~ b => Bounded (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

minBound :: a :~: b #

maxBound :: a :~: b #

a ~ b => Enum (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

succ :: (a :~: b) -> a :~: b #

pred :: (a :~: b) -> a :~: b #

toEnum :: Int -> a :~: b #

fromEnum :: (a :~: b) -> Int #

enumFrom :: (a :~: b) -> [a :~: b] #

enumFromThen :: (a :~: b) -> (a :~: b) -> [a :~: b] #

enumFromTo :: (a :~: b) -> (a :~: b) -> [a :~: b] #

enumFromThenTo :: (a :~: b) -> (a :~: b) -> (a :~: b) -> [a :~: b] #

Eq (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

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

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

Ord (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

compare :: (a :~: b) -> (a :~: b) -> Ordering #

(<) :: (a :~: b) -> (a :~: b) -> Bool #

(<=) :: (a :~: b) -> (a :~: b) -> Bool #

(>) :: (a :~: b) -> (a :~: b) -> Bool #

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

max :: (a :~: b) -> (a :~: b) -> a :~: b #

min :: (a :~: b) -> (a :~: b) -> a :~: b #

a ~ b => Read (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

readsPrec :: Int -> ReadS (a :~: b) #

readList :: ReadS [a :~: b] #

readPrec :: ReadPrec (a :~: b) #

readListPrec :: ReadPrec [a :~: b] #

Show (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

showsPrec :: Int -> (a :~: b) -> ShowS #

show :: (a :~: b) -> String #

showList :: [a :~: b] -> ShowS #

type From ((:~:) a2 :: a1 -> Type) Source # 
Instance details

Defined in Data.Kind.Extra

type From ((:~:) a2 :: a1 -> Type) = a2
type ToFunction BitBuilder (Proxy (Konst nested)) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

type ToFunction BitBuilder (Proxy (Konst nested)) a = ToFunction BitBuilder (Proxy nested) a

type family From (t :: a -> Type) :: a Source #

An open type family to turn symbolic type representations created with A or Extends into the actual types.

Instances
type From (OptionalRecord (Nothing :: Maybe BitRecord)) Source # 
Instance details

Defined in Data.Type.BitRecords.Core

type From (OptionalRecord (Just t) :: BitRecord -> Type) Source # 
Instance details

Defined in Data.Type.BitRecords.Core

type From (OptionalRecord (Just t) :: BitRecord -> Type) = t
type From (StaticExpandableContent record :: BitRecord -> Type) Source # 
Instance details

Defined in Data.ByteString.Mp4.Boxes.Expandable

type From ((:~:) a2 :: a1 -> Type) Source # 
Instance details

Defined in Data.Kind.Extra

type From ((:~:) a2 :: a1 -> Type) = a2
type From (RecArray r n :: BitRecord -> Type) Source # 
Instance details

Defined in Data.Type.BitRecords.Core

type From (l :^+ r :: BitRecord -> Type) Source # 
Instance details

Defined in Data.Type.BitRecords.Core

type From (l :^+ r :: BitRecord -> Type) = Append (From l) r
type From (l :+^ r :: BitRecord -> Type) Source # 
Instance details

Defined in Data.Type.BitRecords.Core

type From (l :+^ r :: BitRecord -> Type) = Append l (From r)
type From (Labelled s t :: a -> Type) Source # 
Instance details

Defined in Data.Kind.Extra

type From (Labelled s t :: a -> Type) = From t
type From (BitRecordOfList f xs :: BitRecord -> Type) Source # 
Instance details

Defined in Data.Type.BitRecords.Core

type From (GASpecificConfig fl cd ext :: AudioSubConfig -> Type) Source # 
Instance details

Defined in Data.ByteString.Mp4.Boxes.AudioSpecificConfig

type From (GASpecificConfig fl cd ext :: AudioSubConfig -> Type) = (TypeError (Text "AudioSubConfig is abstract!") :: AudioSubConfig)
type From (x :>>=: f :: a2 -> Type) Source # 
Instance details

Defined in Data.Kind.Extra

type From (x :>>=: f :: a2 -> Type) = From (f $ From x)
type From (Sized sf r :: BitRecord -> Type) Source # 
Instance details

Defined in Data.Type.BitRecords.Sized

type From (Sized sf r :: BitRecord -> Type) = (("size" @: sf) := SizeInBytes r) .+: r
type From (RecordField f :: BitRecord -> Type) Source # 
Instance details

Defined in Data.Type.BitRecords.Core

type From (MaybeField (Nothing :: Maybe (Extends (BitRecordField t))) :: BitRecord -> Type) Source # 
Instance details

Defined in Data.Type.BitRecords.Core

type From (MaybeField (Just fld) :: BitRecord -> Type) Source # 
Instance details

Defined in Data.Type.BitRecords.Core

type From (SizedField sf r :: BitRecord -> Type) Source # 
Instance details

Defined in Data.Type.BitRecords.Sized

type From (SizedField sf r :: BitRecord -> Type) = (("size" @: sf) := SizeInBytes r) .+. r
type From (EnumParam label ei :: EnumOf enum -> Type) Source # 
Instance details

Defined in Data.Type.BitRecords.Enum

type From (EnumParam label ei :: EnumOf enum -> Type) = MkEnumOf ei (RuntimeFieldValue label :: FieldValue label enum -> Type) EmptyBitRecord
type From (EnumParamAlt label (FixedEnum enum size) :: EnumOf enum -> Type) Source # 
Instance details

Defined in Data.Type.BitRecords.Enum

type From (EnumParamAlt label (FixedEnum enum size) :: EnumOf enum -> Type) = (TypeError (Text "Cannot assign an extension value to the FixedEnum " :<>: ShowType enum) :: EnumOf enum)
type From (EnumParamAlt label (ExtEnum enum size extInd extField) :: EnumOf enum -> Type) Source # 
Instance details

Defined in Data.Type.BitRecords.Enum

type From (EnumParamAlt label (ExtEnum enum size extInd extField) :: EnumOf enum -> Type) = MkEnumOf (ExtEnum enum size extInd extField) (StaticFieldValue label extInd) (BitRecordMember (extField :~ (RuntimeFieldValue label :: FieldValue label st -> Type)))
type From (SetEnum l ei value :: EnumOf enum -> Type) Source # 
Instance details

Defined in Data.Type.BitRecords.Enum

type From (SetEnum l ei value :: EnumOf enum -> Type) = MkEnumOf ei (StaticFieldValue l value) EmptyBitRecord
type From (SetEnumAlt l (FixedEnum enum size) value :: EnumOf enum -> Type) Source # 
Instance details

Defined in Data.Type.BitRecords.Enum

type From (SetEnumAlt l (FixedEnum enum size) value :: EnumOf enum -> Type) = (TypeError (Text "Cannot assign an 'extended' value to the 'FixedEnum' " :<>: ShowType enum) :: EnumOf enum)
type From (SetEnumAlt l (ExtEnum enum size extInd extField) value :: EnumOf enum -> Type) Source # 
Instance details

Defined in Data.Type.BitRecords.Enum

type From (SetEnumAlt l (ExtEnum enum size extInd extField) value :: EnumOf enum -> Type) = MkEnumOf (ExtEnum enum size extInd extField) (StaticFieldValue l extInd) (BitRecordMember (extField := value))
type From Mp4SyncLayerDescriptor Source #

In the holy scripture, ISO-14496-14 section 3.1.2, it is written that there shall be restrictions on the elementary stream descriptor, in there it says: Thou shall use only two as the value for the predefined field in the blessed SLDescriptor. Not one, this is a value not big enough, nor three, this value is too much. The righteous one ever only uses two. Only a fool will use 257.

Instance details

Defined in Data.ByteString.Mp4.Boxes.SyncLayerConfigDescriptor

type From (ProfileLevelIndicationIndexDescriptor val :: Descriptor ProfileLevelIndicationIndexDescr -> Type) Source # 
Instance details

Defined in Data.ByteString.Mp4.Boxes.DecoderConfigDescriptor

type From (DecoderConfigDescriptor ot st di ps :: Descriptor DecoderConfigDescr -> Type) Source # 
Instance details

Defined in Data.ByteString.Mp4.Boxes.DecoderConfigDescriptor

type From (AudioConfigAacMinimal aoId subCfg freq channels :: DecoderSpecificInfo AudioIso14496_3 AudioStream -> Type) Source # 
Instance details

Defined in Data.ByteString.Mp4.Boxes.AudioSpecificConfig

type From (AudioConfigSbrExplicitHierachical aoId subCfg freq channels extFreq :: DecoderSpecificInfo AudioIso14496_3 AudioStream -> Type) Source # 
Instance details

Defined in Data.ByteString.Mp4.Boxes.AudioSpecificConfig

type From (ESDescriptor esId depEsId url ocrEsId streamPrio decConfig slConfig :: Descriptor ES_Descr -> Type) Source # 
Instance details

Defined in Data.ByteString.Mp4.Boxes.ElementaryStreamDescriptor

type From (ESDescriptor esId depEsId url ocrEsId streamPrio decConfig slConfig :: Descriptor ES_Descr -> Type) = (MkDescriptor ((((((("esId" @: FieldU16) :~ esId) .+: (("depEsIdFlag" @: FlagJust depEsId) .+: (("urlFlag" @: FlagJust url) .+: (("ocrEsIdFlag" @: FlagJust ocrEsId) .+: ((("streamPriority" @: Field 5) :~ streamPrio) .+: (("depEsId" @: FieldU16) :+? depEsId)))))) :+: From (OptionalRecordOf (Fun1 (RecordField :: Extends (BitRecordField (MkFieldCustom :: BitField ASizedString ASizedString len)) -> BitRecord -> Type)) url)) :+: (("ocrEsId" @: FieldU16) :+? ocrEsId)) :+: ((BitRecordOfDescriptor :: (Descriptor DecoderConfigDescr -> BitRecord) -> Type) $ From decConfig)) :+: ((BitRecordOfDescriptor :: (Descriptor SLConfigDescr -> BitRecord) -> Type) $ From slConfig)) :: Descriptor ES_Descr)

type family Apply (f :: Extends (a -> b)) (x :: a) :: b Source #

An open family of functions from a to b

Instances
type Apply (BitRecordAppendFun_ l :: (BitRecord -> BitRecord) -> Type) (r :: BitRecord) Source # 
Instance details

Defined in Data.Type.BitRecords.Core

type Apply (f :>>>: g :: (a -> k2) -> Type) (x :: a) Source # 
Instance details

Defined in Data.Kind.Extra

type Apply (f :>>>: g :: (a -> k2) -> Type) (x :: a) = g $ (f $ x)
type Apply (Extract :: (Extends a -> a) -> Type) (x :: Extends a) Source # 
Instance details

Defined in Data.Kind.Extra

type Apply (Extract :: (Extends a -> a) -> Type) (x :: Extends a) = From x
type Apply (f :^>>>: g :: (Extends a -> k2) -> Type) (x :: Extends a) Source # 
Instance details

Defined in Data.Kind.Extra

type Apply (f :^>>>: g :: (Extends a -> k2) -> Type) (x :: Extends a) = g $ (f $ From x)
type Apply (BitRecordOfDescriptor :: (Descriptor tag -> BitRecord) -> Type) (MkDescriptor body :: Descriptor tag) Source # 
Instance details

Defined in Data.ByteString.Mp4.Boxes.BaseDescriptor

type Apply (Fun1 f :: (a -> Extends b) -> Type) (x :: a) Source # 
Instance details

Defined in Data.Kind.Extra

type Apply (Fun1 f :: (a -> Extends b) -> Type) (x :: a) = f x
type Apply (Fun2 f :: (a1 -> Extends (a2 -> Extends b)) -> Type) (x :: a1) Source # 
Instance details

Defined in Data.Kind.Extra

type Apply (Fun2 f :: (a1 -> Extends (a2 -> Extends b)) -> Type) (x :: a1) = Fun1 (f x)
type Apply (Fun3 f :: (a1 -> Extends (a2 -> Extends (b -> Extends c))) -> Type) (x :: a1) Source # 
Instance details

Defined in Data.Kind.Extra

type Apply (Fun3 f :: (a1 -> Extends (a2 -> Extends (b -> Extends c))) -> Type) (x :: a1) = Fun2 (f x)
type Apply (f :>>>^: g :: (a -> Extends k2) -> Type) (x :: a) Source # 
Instance details

Defined in Data.Kind.Extra

type Apply (f :>>>^: g :: (a -> Extends k2) -> Type) (x :: a) = Konst (g $ (f $ x))
type Apply (Fun4 f :: (a1 -> Extends (a2 -> Extends (b -> Extends (c -> Extends d)))) -> Type) (x :: a1) Source # 
Instance details

Defined in Data.Kind.Extra

type Apply (Fun4 f :: (a1 -> Extends (a2 -> Extends (b -> Extends (c -> Extends d)))) -> Type) (x :: a1) = Fun3 (f x)
type Apply (Optional fallback f :: (Maybe s -> Extends t) -> Type) (Nothing :: Maybe s) Source # 
Instance details

Defined in Data.Kind.Extra

type Apply (Optional fallback f :: (Maybe s -> Extends t) -> Type) (Nothing :: Maybe s) = fallback
type Apply (Optional fallback f :: (Maybe a -> Extends t) -> Type) (Just s :: Maybe a) Source # 
Instance details

Defined in Data.Kind.Extra

type Apply (Optional fallback f :: (Maybe a -> Extends t) -> Type) (Just s :: Maybe a) = f $ s
type Apply (DescriptorOfDecoderSpecificInfo :: (DecoderSpecificInfo ot st -> Descriptor DecSpecificInfo) -> Type) (MkDecoderSpecificInfo body :: DecoderSpecificInfo ot st) Source # 
Instance details

Defined in Data.ByteString.Mp4.Boxes.DecoderSpecificInfo

data Labelled (s :: Symbol) :: Extends a -> Extends a Source #

Assign a symbol to any type in a group.

Instances
HasFunctionBuilder BitBuilder (Proxy nested) => HasFunctionBuilder BitBuilder (Proxy (Labelled l nested)) Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Associated Types

type ToFunction BitBuilder (Proxy (Labelled l nested)) r :: Type #

DynamicContent BitBuilder (Proxy nested) rt => DynamicContent BitBuilder (Proxy (Labelled l nested)) rt Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

Methods

addParameter :: Proxy (Labelled l nested) -> FunctionBuilder BitBuilder next (rt -> next) #

type ToFunction BitBuilder (Proxy (Labelled l nested)) a Source # 
Instance details

Defined in Data.Type.BitRecords.Builder.LazyByteStringBuilder

type ToFunction BitBuilder (Proxy (Labelled l nested)) a = ToFunction BitBuilder (Proxy nested) a
type From (Labelled s t :: a -> Type) Source # 
Instance details

Defined in Data.Kind.Extra

type From (Labelled s t :: a -> Type) = From t
type SizeInBytes (Labelled l f :: a -> Type) Source # 
Instance details

Defined in Data.Type.BitRecords.Core

type SizeInBytes (Labelled l f :: a -> Type) = SizeInBytes f

data Named s Source #

Phantom type for things that have a name

Instances
type GetStructureSize (Record (x ': xs)) Source # 
Instance details

Defined in Data.Type.BitRecords.Structure

type GetStructureSize (Record ([] :: [Extends (Named (Structure FixSize))])) Source # 
Instance details

Defined in Data.Type.BitRecords.Structure

data Name :: Symbol -> Extends s -> Extends (Named s) Source #

Assign a name to something that has no name

Instances
type PrettyStructure (Anonymous (Name name struct) :: Structure sizeType -> Type) Source # 
Instance details

Defined in Data.Type.BitRecords.Structure

type PrettyStructure (Anonymous (Name name struct) :: Structure sizeType -> Type) = name <:> PrettyStructure struct
type GetStructureSize (Anonymous (Name name struct)) Source # 
Instance details

Defined in Data.Type.BitRecords.Structure

type GetStructureSize (Anonymous (Name name struct)) = GetStructureSize struct

type (:#) (name :: Symbol) (x :: Extends s) = Name name x infixr 7 Source #

Alias for Name

data Anonymous (x :: Extends (Named s)) :: Extends s Source #

Remove tha name of a NamedStructure to get to a Structure

Instances
type PrettyStructure (Anonymous (Name name struct) :: Structure sizeType -> Type) Source # 
Instance details

Defined in Data.Type.BitRecords.Structure

type PrettyStructure (Anonymous (Name name struct) :: Structure sizeType -> Type) = name <:> PrettyStructure struct
type GetStructureSize (Anonymous (Name name struct)) Source # 
Instance details

Defined in Data.Type.BitRecords.Structure

type GetStructureSize (Anonymous (Name name struct)) = GetStructureSize struct

type ($) f x = Apply f x Source #

An alias for Apply

data (:>>=:) :: Extends a -> Extends (a -> Extends b) -> Extends b infixl 1 Source #

From and ApplyCompose functions

Instances
type From (x :>>=: f :: a2 -> Type) Source # 
Instance details

Defined in Data.Kind.Extra

type From (x :>>=: f :: a2 -> Type) = From (f $ From x)

data (:>>>:) :: Extends (good -> better) -> Extends (better -> best) -> Extends (good -> best) infixl 1 Source #

Compose functions

Instances
type Apply (f :>>>: g :: (a -> k2) -> Type) (x :: a) Source # 
Instance details

Defined in Data.Kind.Extra

type Apply (f :>>>: g :: (a -> k2) -> Type) (x :: a) = g $ (f $ x)

data (:^>>>:) :: Extends (good -> better) -> Extends (better -> best) -> Extends (Extends good -> best) infixl 1 Source #

From Input & Compose

Instances
type Apply (f :^>>>: g :: (Extends a -> k2) -> Type) (x :: Extends a) Source # 
Instance details

Defined in Data.Kind.Extra

type Apply (f :^>>>: g :: (Extends a -> k2) -> Type) (x :: Extends a) = g $ (f $ From x)

data (:>>>^:) :: Extends (good -> better) -> Extends (better -> best) -> Extends (good -> Extends best) infixl 1 Source #

Compose and Konst

Instances
type Apply (f :>>>^: g :: (a -> Extends k2) -> Type) (x :: a) Source # 
Instance details

Defined in Data.Kind.Extra

type Apply (f :>>>^: g :: (a -> Extends k2) -> Type) (x :: a) = Konst (g $ (f $ x))

data Extract :: Extends (Extends x -> x) Source #

A function that applies From

Instances
type Apply (Extract :: (Extends a -> a) -> Type) (x :: Extends a) Source # 
Instance details

Defined in Data.Kind.Extra

type Apply (Extract :: (Extends a -> a) -> Type) (x :: Extends a) = From x

data Optional :: Extends t -> Extends (s -> Extends t) -> Extends (Maybe s -> Extends t) Source #

Either use the value from Just or return a fallback value(types(kinds))

Instances
type Apply (Optional fallback f :: (Maybe s -> Extends t) -> Type) (Nothing :: Maybe s) Source # 
Instance details

Defined in Data.Kind.Extra

type Apply (Optional fallback f :: (Maybe s -> Extends t) -> Type) (Nothing :: Maybe s) = fallback
type Apply (Optional fallback f :: (Maybe a -> Extends t) -> Type) (Just s :: Maybe a) Source # 
Instance details

Defined in Data.Kind.Extra

type Apply (Optional fallback f :: (Maybe a -> Extends t) -> Type) (Just s :: Maybe a) = f $ s

type family FoldMap (append :: Extends (b -> Extends (b -> b))) (zero :: b) (f :: Extends (a -> b)) (xs :: [(a :: Type)]) :: (b :: Type) where ... Source #

Map over the elements of a list and fold the result.

Equations

FoldMap append zero f '[] = zero 
FoldMap append zero f (x ': xs) = (append $ (f $ x)) $ FoldMap append zero f xs 

data Fun1 :: (a -> Extends b) -> Extends (a -> Extends b) Source #

Like TyCon1 from Data.Singletons

Instances
type Apply (Fun1 f :: (a -> Extends b) -> Type) (x :: a) Source # 
Instance details

Defined in Data.Kind.Extra

type Apply (Fun1 f :: (a -> Extends b) -> Type) (x :: a) = f x

data Fun2 :: (a -> b -> Extends c) -> Extends (a -> Extends (b -> Extends c)) Source #

Instances
type Apply (Fun2 f :: (a1 -> Extends (a2 -> Extends b)) -> Type) (x :: a1) Source # 
Instance details

Defined in Data.Kind.Extra

type Apply (Fun2 f :: (a1 -> Extends (a2 -> Extends b)) -> Type) (x :: a1) = Fun1 (f x)

data Fun3 :: (a -> b -> c -> Extends d) -> Extends (a -> Extends (b -> Extends (c -> Extends d))) Source #

Instances
type Apply (Fun3 f :: (a1 -> Extends (a2 -> Extends (b -> Extends c))) -> Type) (x :: a1) Source # 
Instance details

Defined in Data.Kind.Extra

type Apply (Fun3 f :: (a1 -> Extends (a2 -> Extends (b -> Extends c))) -> Type) (x :: a1) = Fun2 (f x)

data Fun4 :: (a -> b -> c -> d -> Extends e) -> Extends (a -> Extends (b -> Extends (c -> Extends (d -> Extends e)))) Source #

Instances
type Apply (Fun4 f :: (a1 -> Extends (a2 -> Extends (b -> Extends (c -> Extends d)))) -> Type) (x :: a1) Source # 
Instance details

Defined in Data.Kind.Extra

type Apply (Fun4 f :: (a1 -> Extends (a2 -> Extends (b -> Extends (c -> Extends d)))) -> Type) (x :: a1) = Fun3 (f x)