mediabus-0.2.0.1: Multimedia streaming on top of Conduit

Safe HaskellNone
LanguageHaskell2010

Data.MediaBus.Series

Documentation

data Series a b Source #

Constructors

Next !b 
Start !a 

Instances

Bifunctor Series Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Series a c -> Series b d #

first :: (a -> b) -> Series a c -> Series b c #

second :: (b -> c) -> Series a b -> Series a c #

Functor (Series a) Source # 

Methods

fmap :: (a -> b) -> Series a a -> Series a b #

(<$) :: a -> Series a b -> Series a a #

(Eq a, Eq b) => Eq (Series a b) Source # 

Methods

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

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

(Ord a, Ord b) => Ord (Series a b) Source # 

Methods

compare :: Series a b -> Series a b -> Ordering #

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

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

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

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

max :: Series a b -> Series a b -> Series a b #

min :: Series a b -> Series a b -> Series a b #

(Show a, Show b) => Show (Series a b) Source # 

Methods

showsPrec :: Int -> Series a b -> ShowS #

show :: Series a b -> String #

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

Generic (Series a b) Source # 

Associated Types

type Rep (Series a b) :: * -> * #

Methods

from :: Series a b -> Rep (Series a b) x #

to :: Rep (Series a b) x -> Series a b #

(Arbitrary a, Arbitrary b) => Arbitrary (Series a b) Source # 

Methods

arbitrary :: Gen (Series a b) #

shrink :: Series a b -> [Series a b] #

(NFData a, NFData b) => NFData (Series a b) Source # 

Methods

rnf :: Series a b -> () #

AsSeriesNext (Series a b) Source # 

Associated Types

type GetSeriesNext (Series a b) :: * Source #

type SetSeriesNext (Series a b) t :: * Source #

Methods

seriesNext :: (Choice p, Applicative f) => p (GetSeriesNext (Series a b)) (f n) -> p (Series a b) (f (SetSeriesNext (Series a b) n)) Source #

AsSeriesStart (Series a b) Source # 

Associated Types

type GetSeriesStart (Series a b) :: * Source #

type SetSeriesStart (Series a b) t :: * Source #

Methods

seriesStart :: (Choice p, Applicative f) => p (GetSeriesStart (Series a b)) (f n) -> p (Series a b) (f (SetSeriesStart (Series a b) n)) Source #

(HasSeqNum a, HasSeqNum b, (~) * (GetSeqNum a) (GetSeqNum b)) => HasSeqNum (Series a b) Source # 

Methods

seqNum :: Functor f => (GetSeqNum (Series a b) -> f s) -> Series a b -> f (SetSeqNum (Series a b) s) Source #

(HasSeqNumT a, HasSeqNumT b, (~) * (GetSeqNum a) (GetSeqNum b)) => HasSeqNumT (Series a b) Source # 

Associated Types

type GetSeqNum (Series a b) :: * Source #

type SetSeqNum (Series a b) s :: * Source #

(HasTimestamp a, HasTimestamp b, (~) * (GetTimestamp a) (GetTimestamp b)) => HasTimestamp (Series a b) Source # 

Methods

timestamp :: Functor f => (GetTimestamp (Series a b) -> f s) -> Series a b -> f (SetTimestamp (Series a b) s) Source #

timestamp' :: Lens' (Series a b) (GetTimestamp (Series a b)) Source #

(HasTimestampT a, HasTimestampT b, (~) * (GetTimestamp a) (GetTimestamp b)) => HasTimestampT (Series a b) Source # 

Associated Types

type GetTimestamp (Series a b) :: * Source #

type SetTimestamp (Series a b) s :: * Source #

AsSeries (Series a b) a b Source # 
type Rep (Series a b) Source # 
type Rep (Series a b) = D1 (MetaData "Series" "Data.MediaBus.Series" "mediabus-0.2.0.1-GufOXSQMJOgBSiYlFFnZ4L" False) ((:+:) (C1 (MetaCons "Next" PrefixI True) (S1 (MetaSel (Just Symbol "_seriesValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 b))) (C1 (MetaCons "Start" PrefixI True) (S1 (MetaSel (Just Symbol "_seriesStartValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a))))
type GetSeriesNext (Series a b) Source # 
type GetSeriesNext (Series a b) = b
type GetSeriesStart (Series a b) Source # 
type GetSeriesStart (Series a b) = a
type GetSeqNum (Series a b) Source # 
type GetSeqNum (Series a b) = GetSeqNum a
type GetTimestamp (Series a b) Source # 
type SetSeriesNext (Series a b) n Source # 
type SetSeriesNext (Series a b) n = Series a n
type SetSeriesStart (Series a b) n Source # 
type SetSeriesStart (Series a b) n = Series n b
type SetSeqNum (Series a b) t Source # 
type SetSeqNum (Series a b) t = Series (SetSeqNum a t) (SetSeqNum b t)
type SetTimestamp (Series a b) t Source # 

type Series' a = Series a a Source #

_Next :: forall a b b. Prism (Series a b) (Series a b) b b Source #

_Start :: forall a b a. Prism (Series a b) (Series a b) a a Source #

class AsSeries s a b | s -> a, s -> b where Source #

Minimal complete definition

seriesStart', seriesNext'

Instances

class SetSeriesStart s (GetSeriesStart s) ~ s => AsSeriesStart s where Source #

Minimal complete definition

seriesStart

Associated Types

type GetSeriesStart s Source #

type SetSeriesStart s t Source #

Instances

AsSeriesStart (Either a b) Source # 

Associated Types

type GetSeriesStart (Either a b) :: * Source #

type SetSeriesStart (Either a b) t :: * Source #

Methods

seriesStart :: (Choice p, Applicative f) => p (GetSeriesStart (Either a b)) (f n) -> p (Either a b) (f (SetSeriesStart (Either a b) n)) Source #

AsSeriesStart (Series a b) Source # 

Associated Types

type GetSeriesStart (Series a b) :: * Source #

type SetSeriesStart (Series a b) t :: * Source #

Methods

seriesStart :: (Choice p, Applicative f) => p (GetSeriesStart (Series a b)) (f n) -> p (Series a b) (f (SetSeriesStart (Series a b) n)) Source #

class SetSeriesNext s (GetSeriesNext s) ~ s => AsSeriesNext s where Source #

Minimal complete definition

seriesNext

Associated Types

type GetSeriesNext s Source #

type SetSeriesNext s t Source #

Instances

AsSeriesNext (Either a b) Source # 

Associated Types

type GetSeriesNext (Either a b) :: * Source #

type SetSeriesNext (Either a b) t :: * Source #

Methods

seriesNext :: (Choice p, Applicative f) => p (GetSeriesNext (Either a b)) (f n) -> p (Either a b) (f (SetSeriesNext (Either a b) n)) Source #

AsSeriesNext (Series a b) Source # 

Associated Types

type GetSeriesNext (Series a b) :: * Source #

type SetSeriesNext (Series a b) t :: * Source #

Methods

seriesNext :: (Choice p, Applicative f) => p (GetSeriesNext (Series a b)) (f n) -> p (Series a b) (f (SetSeriesNext (Series a b) n)) Source #

toNextsC' :: Monad m => Conduit (Series a b) m b Source #

monotoneSeriesC :: Monad m => m a -> (i -> m b) -> Conduit i m (Series a b) Source #