streaming-0.2.1.0: an elementary streaming prelude and general stream type.

Safe HaskellSafe
LanguageHaskell2010

Data.Functor.Of

Synopsis

Documentation

data Of a b Source #

A left-strict pair; the base functor for streams of individual elements.

Constructors

!a :> b infixr 5 

Instances

Bifunctor Of Source # 

Methods

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

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

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

Eq2 Of Source # 

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Of a c -> Of b d -> Bool #

Ord2 Of Source # 

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Of a c -> Of b d -> Ordering #

Show2 Of Source # 

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Of a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Of a b] -> ShowS #

Monoid a => Monad (Of a) Source # 

Methods

(>>=) :: Of a a -> (a -> Of a b) -> Of a b #

(>>) :: Of a a -> Of a b -> Of a b #

return :: a -> Of a a #

fail :: String -> Of a a #

Functor (Of a) Source # 

Methods

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

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

Monoid a => Applicative (Of a) Source # 

Methods

pure :: a -> Of a a #

(<*>) :: Of a (a -> b) -> Of a a -> Of a b #

liftA2 :: (a -> b -> c) -> Of a a -> Of a b -> Of a c #

(*>) :: Of a a -> Of a b -> Of a b #

(<*) :: Of a a -> Of a b -> Of a a #

Foldable (Of a) Source # 

Methods

fold :: Monoid m => Of a m -> m #

foldMap :: Monoid m => (a -> m) -> Of a a -> m #

foldr :: (a -> b -> b) -> b -> Of a a -> b #

foldr' :: (a -> b -> b) -> b -> Of a a -> b #

foldl :: (b -> a -> b) -> b -> Of a a -> b #

foldl' :: (b -> a -> b) -> b -> Of a a -> b #

foldr1 :: (a -> a -> a) -> Of a a -> a #

foldl1 :: (a -> a -> a) -> Of a a -> a #

toList :: Of a a -> [a] #

null :: Of a a -> Bool #

length :: Of a a -> Int #

elem :: Eq a => a -> Of a a -> Bool #

maximum :: Ord a => Of a a -> a #

minimum :: Ord a => Of a a -> a #

sum :: Num a => Of a a -> a #

product :: Num a => Of a a -> a #

Traversable (Of a) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Of a a -> f (Of a b) #

sequenceA :: Applicative f => Of a (f a) -> f (Of a a) #

mapM :: Monad m => (a -> m b) -> Of a a -> m (Of a b) #

sequence :: Monad m => Of a (m a) -> m (Of a a) #

Eq a => Eq1 (Of a) Source # 

Methods

liftEq :: (a -> b -> Bool) -> Of a a -> Of a b -> Bool #

Ord a => Ord1 (Of a) Source # 

Methods

liftCompare :: (a -> b -> Ordering) -> Of a a -> Of a b -> Ordering #

Show a => Show1 (Of a) Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Of a a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Of a a] -> ShowS #

Generic1 * (Of a) Source # 

Associated Types

type Rep1 (Of a) (f :: Of a -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (Of a) f a #

to1 :: Rep1 (Of a) f a -> f a #

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

Methods

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

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

(Data b, Data a) => Data (Of a b) Source # 

Methods

gfoldl :: (forall d c. Data d => c (d -> c) -> d -> c c) -> (forall g. g -> c g) -> Of a b -> c (Of a b) #

gunfold :: (forall c r. Data c => c (c -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Of a b) #

toConstr :: Of a b -> Constr #

dataTypeOf :: Of a b -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Of a b)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Of a b)) #

gmapT :: (forall c. Data c => c -> c) -> Of a b -> Of a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Of a b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Of a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> Of a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Of a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Of a b -> m (Of a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Of a b -> m (Of a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Of a b -> m (Of a b) #

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

Methods

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

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

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

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

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

max :: Of a b -> Of a b -> Of a b #

min :: Of a b -> Of a b -> Of a b #

(Read b, Read a) => Read (Of a b) Source # 

Methods

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

readList :: ReadS [Of a b] #

readPrec :: ReadPrec (Of a b) #

readListPrec :: ReadPrec [Of a b] #

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

Methods

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

show :: Of a b -> String #

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

Generic (Of a b) Source # 

Associated Types

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

Methods

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

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

(Semigroup a, Semigroup b) => Semigroup (Of a b) Source # 

Methods

(<>) :: Of a b -> Of a b -> Of a b #

sconcat :: NonEmpty (Of a b) -> Of a b #

stimes :: Integral b => b -> Of a b -> Of a b #

(Monoid a, Monoid b) => Monoid (Of a b) Source # 

Methods

mempty :: Of a b #

mappend :: Of a b -> Of a b -> Of a b #

mconcat :: [Of a b] -> Of a b #

type Rep1 * (Of a) Source # 
type Rep (Of a b) Source # 
type Rep (Of a b) = D1 * (MetaData "Of" "Data.Functor.Of" "streaming-0.2.1.0-k62tIogCS784q9BtifVyf" False) (C1 * (MetaCons ":>" (InfixI RightAssociative 5) False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * a)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * b))))