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

Raehik.HFunctorMap

Documentation

newtype LFlap a fl Source #

Constructors

LFlap 

Fields

Instances

Instances details
ToJSON (Snd fl a) => ToJSON (LFlap a fl) Source # 
Instance details

Defined in Raehik.HFunctorMap

Methods

toJSON :: LFlap a fl -> Value #

toEncoding :: LFlap a fl -> Encoding #

toJSONList :: [LFlap a fl] -> Value #

toEncodingList :: [LFlap a fl] -> Encoding #

Generic (LFlap a fl) Source # 
Instance details

Defined in Raehik.HFunctorMap

Associated Types

type Rep (LFlap a fl) :: Type -> Type #

Methods

from :: LFlap a fl -> Rep (LFlap a fl) x #

to :: Rep (LFlap a fl) x -> LFlap a fl #

Show (Snd fl a) => Show (LFlap a fl) Source # 
Instance details

Defined in Raehik.HFunctorMap

Methods

showsPrec :: Int -> LFlap a fl -> ShowS #

show :: LFlap a fl -> String #

showList :: [LFlap a fl] -> ShowS #

type Rep (LFlap a fl) Source # 
Instance details

Defined in Raehik.HFunctorMap

type Rep (LFlap a fl) = D1 ('MetaData "LFlap" "Raehik.HFunctorMap" "bytepatch-0.4.1-inplace" 'True) (C1 ('MetaCons "LFlap" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLFlap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Snd fl a))))

lFlap :: forall l a f. f a -> LFlap a '(l, f) Source #

newtype LFunctorList fs a Source #

Constructors

LFunctorList 

Fields

Instances

Instances details
(ToJSON (f a), KnownSymbol l, ToJSON (LFunctorList fs a)) => ToJSON (LFunctorList ('(l, f) ': fs) a) Source # 
Instance details

Defined in Raehik.HFunctorMap

Methods

toJSON :: LFunctorList ('(l, f) ': fs) a -> Value #

toEncoding :: LFunctorList ('(l, f) ': fs) a -> Encoding #

toJSONList :: [LFunctorList ('(l, f) ': fs) a] -> Value #

toEncodingList :: [LFunctorList ('(l, f) ': fs) a] -> Encoding #

ToJSON (LFunctorList ('[] :: [(Symbol, k -> Type)]) a) Source # 
Instance details

Defined in Raehik.HFunctorMap

Generic (LFunctorList fs a) Source # 
Instance details

Defined in Raehik.HFunctorMap

Associated Types

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

Methods

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

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

(ReifyConstraint Show (LFlap a) fs, RMap fs, RecordToList fs) => Show (LFunctorList fs a) Source # 
Instance details

Defined in Raehik.HFunctorMap

Methods

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

show :: LFunctorList fs a -> String #

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

type Rep (LFunctorList fs a) Source # 
Instance details

Defined in Raehik.HFunctorMap

type Rep (LFunctorList fs a) = D1 ('MetaData "LFunctorList" "Raehik.HFunctorMap" "bytepatch-0.4.1-inplace" 'True) (C1 ('MetaCons "LFunctorList" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLFunctorList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Rec (LFlap a) fs))))

lflgetf :: forall (l :: Symbol) f fs a. HasField Rec l fs fs f f => LFunctorList fs a -> f a Source #