bytepatch-0.4.1: Patch byte-representable data in a bytestream
Safe HaskellSafe-Inferred
LanguageGHC2021

StreamPatch.HFunctorList

Synopsis

Documentation

newtype HFunctorList fs a Source #

A list of functors parametric over a "shared" a, where each functor stores a single value 'f a'.

Just a wrapper on top of Vinyl with some types swap around.

Constructors

HFunctorList 

Fields

Instances

Instances details
(Foldable r, Foldable (HFunctorList rs)) => Foldable (HFunctorList (r ': rs)) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Methods

fold :: Monoid m => HFunctorList (r ': rs) m -> m #

foldMap :: Monoid m => (a -> m) -> HFunctorList (r ': rs) a -> m #

foldMap' :: Monoid m => (a -> m) -> HFunctorList (r ': rs) a -> m #

foldr :: (a -> b -> b) -> b -> HFunctorList (r ': rs) a -> b #

foldr' :: (a -> b -> b) -> b -> HFunctorList (r ': rs) a -> b #

foldl :: (b -> a -> b) -> b -> HFunctorList (r ': rs) a -> b #

foldl' :: (b -> a -> b) -> b -> HFunctorList (r ': rs) a -> b #

foldr1 :: (a -> a -> a) -> HFunctorList (r ': rs) a -> a #

foldl1 :: (a -> a -> a) -> HFunctorList (r ': rs) a -> a #

toList :: HFunctorList (r ': rs) a -> [a] #

null :: HFunctorList (r ': rs) a -> Bool #

length :: HFunctorList (r ': rs) a -> Int #

elem :: Eq a => a -> HFunctorList (r ': rs) a -> Bool #

maximum :: Ord a => HFunctorList (r ': rs) a -> a #

minimum :: Ord a => HFunctorList (r ': rs) a -> a #

sum :: Num a => HFunctorList (r ': rs) a -> a #

product :: Num a => HFunctorList (r ': rs) a -> a #

Foldable (HFunctorList ('[] :: [TYPE LiftedRep -> Type])) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Methods

fold :: Monoid m => HFunctorList '[] m -> m #

foldMap :: Monoid m => (a -> m) -> HFunctorList '[] a -> m #

foldMap' :: Monoid m => (a -> m) -> HFunctorList '[] a -> m #

foldr :: (a -> b -> b) -> b -> HFunctorList '[] a -> b #

foldr' :: (a -> b -> b) -> b -> HFunctorList '[] a -> b #

foldl :: (b -> a -> b) -> b -> HFunctorList '[] a -> b #

foldl' :: (b -> a -> b) -> b -> HFunctorList '[] a -> b #

foldr1 :: (a -> a -> a) -> HFunctorList '[] a -> a #

foldl1 :: (a -> a -> a) -> HFunctorList '[] a -> a #

toList :: HFunctorList '[] a -> [a] #

null :: HFunctorList '[] a -> Bool #

length :: HFunctorList '[] a -> Int #

elem :: Eq a => a -> HFunctorList '[] a -> Bool #

maximum :: Ord a => HFunctorList '[] a -> a #

minimum :: Ord a => HFunctorList '[] a -> a #

sum :: Num a => HFunctorList '[] a -> a #

product :: Num a => HFunctorList '[] a -> a #

(Traversable r, Traversable (HFunctorList rs)) => Traversable (HFunctorList (r ': rs)) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Methods

traverse :: Applicative f => (a -> f b) -> HFunctorList (r ': rs) a -> f (HFunctorList (r ': rs) b) #

sequenceA :: Applicative f => HFunctorList (r ': rs) (f a) -> f (HFunctorList (r ': rs) a) #

mapM :: Monad m => (a -> m b) -> HFunctorList (r ': rs) a -> m (HFunctorList (r ': rs) b) #

sequence :: Monad m => HFunctorList (r ': rs) (m a) -> m (HFunctorList (r ': rs) a) #

Traversable (HFunctorList ('[] :: [Type -> Type])) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Methods

traverse :: Applicative f => (a -> f b) -> HFunctorList '[] a -> f (HFunctorList '[] b) #

sequenceA :: Applicative f => HFunctorList '[] (f a) -> f (HFunctorList '[] a) #

mapM :: Monad m => (a -> m b) -> HFunctorList '[] a -> m (HFunctorList '[] b) #

sequence :: Monad m => HFunctorList '[] (m a) -> m (HFunctorList '[] a) #

(Applicative r, Applicative (HFunctorList rs)) => Applicative (HFunctorList (r ': rs)) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Methods

pure :: a -> HFunctorList (r ': rs) a #

(<*>) :: HFunctorList (r ': rs) (a -> b) -> HFunctorList (r ': rs) a -> HFunctorList (r ': rs) b #

liftA2 :: (a -> b -> c) -> HFunctorList (r ': rs) a -> HFunctorList (r ': rs) b -> HFunctorList (r ': rs) c #

(*>) :: HFunctorList (r ': rs) a -> HFunctorList (r ': rs) b -> HFunctorList (r ': rs) b #

(<*) :: HFunctorList (r ': rs) a -> HFunctorList (r ': rs) b -> HFunctorList (r ': rs) a #

Applicative (HFunctorList ('[] :: [Type -> Type])) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Methods

pure :: a -> HFunctorList '[] a #

(<*>) :: HFunctorList '[] (a -> b) -> HFunctorList '[] a -> HFunctorList '[] b #

liftA2 :: (a -> b -> c) -> HFunctorList '[] a -> HFunctorList '[] b -> HFunctorList '[] c #

(*>) :: HFunctorList '[] a -> HFunctorList '[] b -> HFunctorList '[] b #

(<*) :: HFunctorList '[] a -> HFunctorList '[] b -> HFunctorList '[] a #

(Functor r, Functor (HFunctorList rs)) => Functor (HFunctorList (r ': rs)) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Methods

fmap :: (a -> b) -> HFunctorList (r ': rs) a -> HFunctorList (r ': rs) b #

(<$) :: a -> HFunctorList (r ': rs) b -> HFunctorList (r ': rs) a #

Functor (HFunctorList ('[] :: [Type -> Type])) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Methods

fmap :: (a -> b) -> HFunctorList '[] a -> HFunctorList '[] b #

(<$) :: a -> HFunctorList '[] b -> HFunctorList '[] a #

ToJSON (Rec (Flap a) fs) => ToJSON (HFunctorList fs a) Source # 
Instance details

Defined in StreamPatch.HFunctorList

(Storable (f a), Storable (Rec (Flap a) fs)) => Storable (HFunctorList (f ': fs) a) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Methods

sizeOf :: HFunctorList (f ': fs) a -> Int #

alignment :: HFunctorList (f ': fs) a -> Int #

peekElemOff :: Ptr (HFunctorList (f ': fs) a) -> Int -> IO (HFunctorList (f ': fs) a) #

pokeElemOff :: Ptr (HFunctorList (f ': fs) a) -> Int -> HFunctorList (f ': fs) a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (HFunctorList (f ': fs) a) #

pokeByteOff :: Ptr b -> Int -> HFunctorList (f ': fs) a -> IO () #

peek :: Ptr (HFunctorList (f ': fs) a) -> IO (HFunctorList (f ': fs) a) #

poke :: Ptr (HFunctorList (f ': fs) a) -> HFunctorList (f ': fs) a -> IO () #

Storable (HFunctorList ('[] :: [k -> Type]) a) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Methods

sizeOf :: HFunctorList '[] a -> Int #

alignment :: HFunctorList '[] a -> Int #

peekElemOff :: Ptr (HFunctorList '[] a) -> Int -> IO (HFunctorList '[] a) #

pokeElemOff :: Ptr (HFunctorList '[] a) -> Int -> HFunctorList '[] a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (HFunctorList '[] a) #

pokeByteOff :: Ptr b -> Int -> HFunctorList '[] a -> IO () #

peek :: Ptr (HFunctorList '[] a) -> IO (HFunctorList '[] a) #

poke :: Ptr (HFunctorList '[] a) -> HFunctorList '[] a -> IO () #

Generic (HFunctorList fs a) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Associated Types

type Rep (HFunctorList fs a) :: Type -> Type #

Methods

from :: HFunctorList fs a -> Rep (HFunctorList fs a) x #

to :: Rep (HFunctorList fs a) x -> HFunctorList fs a #

(ReifyConstraint Show (Flap a) fs, RMap fs, RecordToList fs) => Show (HFunctorList fs a) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Methods

showsPrec :: Int -> HFunctorList fs a -> ShowS #

show :: HFunctorList fs a -> String #

showList :: [HFunctorList fs a] -> ShowS #

Eq (Rec (Flap a) fs) => Eq (HFunctorList fs a) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Methods

(==) :: HFunctorList fs a -> HFunctorList fs a -> Bool #

(/=) :: HFunctorList fs a -> HFunctorList fs a -> Bool #

Ord (Rec (Flap a) fs) => Ord (HFunctorList fs a) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Methods

compare :: HFunctorList fs a -> HFunctorList fs a -> Ordering #

(<) :: HFunctorList fs a -> HFunctorList fs a -> Bool #

(<=) :: HFunctorList fs a -> HFunctorList fs a -> Bool #

(>) :: HFunctorList fs a -> HFunctorList fs a -> Bool #

(>=) :: HFunctorList fs a -> HFunctorList fs a -> Bool #

max :: HFunctorList fs a -> HFunctorList fs a -> HFunctorList fs a #

min :: HFunctorList fs a -> HFunctorList fs a -> HFunctorList fs a #

type Rep (HFunctorList fs a) Source # 
Instance details

Defined in StreamPatch.HFunctorList

type Rep (HFunctorList fs a) = D1 ('MetaData "HFunctorList" "StreamPatch.HFunctorList" "bytepatch-0.4.1-inplace" 'True) (C1 ('MetaCons "HFunctorList" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHFunctorList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Rec (Flap a) fs))))

newtype Flap a f Source #

Flipped apply: a single value at 'f a', but with "flipped" type arguments. Very useless - has no Functor nor Contravariant nor HFunctor instance.

Constructors

Flap 

Fields

Instances

Instances details
FromJSON (f a) => FromJSON (Flap a f) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Methods

parseJSON :: Value -> Parser (Flap a f) #

parseJSONList :: Value -> Parser [Flap a f] #

ToJSON (f a) => ToJSON (Flap a f) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Methods

toJSON :: Flap a f -> Value #

toEncoding :: Flap a f -> Encoding #

toJSONList :: [Flap a f] -> Value #

toEncodingList :: [Flap a f] -> Encoding #

(ToJSON (Flap a r), Generic (Rec (Flap a) rs), GToJSON' Value Zero (Rep (Rec (Flap a) rs)), GToJSON' Encoding Zero (Rep (Rec (Flap a) rs))) => ToJSON (Rec (Flap a) (r ': rs)) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Methods

toJSON :: Rec (Flap a) (r ': rs) -> Value #

toEncoding :: Rec (Flap a) (r ': rs) -> Encoding #

toJSONList :: [Rec (Flap a) (r ': rs)] -> Value #

toEncodingList :: [Rec (Flap a) (r ': rs)] -> Encoding #

Storable (f a) => Storable (Flap a f) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Methods

sizeOf :: Flap a f -> Int #

alignment :: Flap a f -> Int #

peekElemOff :: Ptr (Flap a f) -> Int -> IO (Flap a f) #

pokeElemOff :: Ptr (Flap a f) -> Int -> Flap a f -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Flap a f) #

pokeByteOff :: Ptr b -> Int -> Flap a f -> IO () #

peek :: Ptr (Flap a f) -> IO (Flap a f) #

poke :: Ptr (Flap a f) -> Flap a f -> IO () #

Generic (Flap a f) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Associated Types

type Rep (Flap a f) :: Type -> Type #

Methods

from :: Flap a f -> Rep (Flap a f) x #

to :: Rep (Flap a f) x -> Flap a f #

Show (f a) => Show (Flap a f) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Methods

showsPrec :: Int -> Flap a f -> ShowS #

show :: Flap a f -> String #

showList :: [Flap a f] -> ShowS #

Eq (f a) => Eq (Flap a f) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Methods

(==) :: Flap a f -> Flap a f -> Bool #

(/=) :: Flap a f -> Flap a f -> Bool #

Ord (f a) => Ord (Flap a f) Source # 
Instance details

Defined in StreamPatch.HFunctorList

Methods

compare :: Flap a f -> Flap a f -> Ordering #

(<) :: Flap a f -> Flap a f -> Bool #

(<=) :: Flap a f -> Flap a f -> Bool #

(>) :: Flap a f -> Flap a f -> Bool #

(>=) :: Flap a f -> Flap a f -> Bool #

max :: Flap a f -> Flap a f -> Flap a f #

min :: Flap a f -> Flap a f -> Flap a f #

type Rep (Flap a f) Source # 
Instance details

Defined in StreamPatch.HFunctorList

type Rep (Flap a f) = D1 ('MetaData "Flap" "StreamPatch.HFunctorList" "bytepatch-0.4.1-inplace" 'True) (C1 ('MetaCons "Flap" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFlap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a))))

hflGet :: forall f fs a i. RElem f fs i => HFunctorList fs a -> f a Source #

Get the value at a type in an HFunctorList.

hflPut :: forall f f' fs fs' a. RecElem Rec f f' fs fs' (RIndex f fs) => f' a -> HFunctorList fs a -> HFunctorList fs' a Source #

Put a value at a type in an HFunctorList.

hflLens :: forall f f' fs fs' a s t. (RecElem Rec f f' fs fs' (RIndex f fs), RElem f fs (RIndex f fs), s ~ HFunctorList fs a, t ~ HFunctorList fs' a) => Lens s t (f a) (f' a) Source #

Get a lens to the value at a type in an HFunctorList.

hflStrip :: forall f fs a fs' b i is. (RElem f fs i, fs' ~ RDelete f fs, RSubset fs' fs is) => (f a -> b) -> HFunctorList fs a -> (b, HFunctorList fs' a) Source #

Use the value at a type in an HFunctorList, and remove it from the list.