Copyright | (c) axionbuster 2025 |
---|---|
License | BSD-3-Clause |
Safe Haskell | None |
Language | GHC2021 |
Defines newtype wrappers that control how values are packed and unpacked, including enum indices, fixed-point numbers, angles, and identifiers.
Synopsis
- newtype EnumIndex (i :: k) a = EnumIndex {
- enumindex :: a
- newtype Fixed' (i :: k) (r :: k1) f = Fixed' {
- unfixed' :: f
- newtype Int8Angle = Int8Angle {}
- newtype Identifier = Identifier {
- identifier :: Text
- newtype IDorX a = IDorX {}
- newtype IDSet = IDSet {
- setnameorids :: Either Text (Vector Int32)
- newtype TakeRest = TakeRest {}
- newtype PackFoldableVI (f :: k -> Type) (a :: k) = PackFoldableVI {
- getpackfoldablevi :: f a
- newtype PackFoldable0 (f :: k -> Type) (a :: k) = PackFoldable0 {
- getpackfoldable0 :: f a
- newtype UnpackRepresentable0 (f :: k -> Type) (a :: k) = UnpackRepresentable0 {
- getunpackrepresentable0 :: f a
- degtoi8angle :: RealFrac a => a -> Int8Angle
- i8angledeg :: RealFrac a => Int8Angle -> a
Documentation
newtype EnumIndex (i :: k) a Source #
represent any Enum
type using a zero-based index
Instances
Lift a => Lift (EnumIndex i a :: Type) Source # | |||||
Functor (EnumIndex i) Source # | |||||
(Typeable i, Typeable k, Data a) => Data (EnumIndex i a) Source # | |||||
Defined in M.Pack.Internal.Newtypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EnumIndex i a -> c (EnumIndex i a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (EnumIndex i a) # toConstr :: EnumIndex i a -> Constr # dataTypeOf :: EnumIndex i a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (EnumIndex i a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (EnumIndex i a)) # gmapT :: (forall b. Data b => b -> b) -> EnumIndex i a -> EnumIndex i a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EnumIndex i a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EnumIndex i a -> r # gmapQ :: (forall d. Data d => d -> u) -> EnumIndex i a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> EnumIndex i a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EnumIndex i a -> m (EnumIndex i a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumIndex i a -> m (EnumIndex i a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumIndex i a -> m (EnumIndex i a) # | |||||
Bounded a => Bounded (EnumIndex i a) Source # | |||||
Enum a => Enum (EnumIndex i a) Source # | |||||
Defined in M.Pack.Internal.Newtypes succ :: EnumIndex i a -> EnumIndex i a # pred :: EnumIndex i a -> EnumIndex i a # toEnum :: Int -> EnumIndex i a # fromEnum :: EnumIndex i a -> Int # enumFrom :: EnumIndex i a -> [EnumIndex i a] # enumFromThen :: EnumIndex i a -> EnumIndex i a -> [EnumIndex i a] # enumFromTo :: EnumIndex i a -> EnumIndex i a -> [EnumIndex i a] # enumFromThenTo :: EnumIndex i a -> EnumIndex i a -> EnumIndex i a -> [EnumIndex i a] # | |||||
Generic (EnumIndex i a) Source # | |||||
Defined in M.Pack.Internal.Newtypes
| |||||
Read a => Read (EnumIndex i a) Source # | |||||
Show a => Show (EnumIndex i a) Source # | |||||
NFData a => NFData (EnumIndex i a) Source # | |||||
Defined in M.Pack.Internal.Newtypes | |||||
Eq a => Eq (EnumIndex i a) Source # | |||||
Ord a => Ord (EnumIndex i a) Source # | |||||
Defined in M.Pack.Internal.Newtypes compare :: EnumIndex i a -> EnumIndex i a -> Ordering # (<) :: EnumIndex i a -> EnumIndex i a -> Bool # (<=) :: EnumIndex i a -> EnumIndex i a -> Bool # (>) :: EnumIndex i a -> EnumIndex i a -> Bool # (>=) :: EnumIndex i a -> EnumIndex i a -> Bool # | |||||
Hashable a => Hashable (EnumIndex i a) Source # | |||||
Defined in M.Pack.Internal.Newtypes | |||||
(Enum a, Integral i, Pack i) => Pack (EnumIndex i a) Source # | |||||
(Enum a, Bounded a, Integral i, Unpack i) => Unpack (EnumIndex i a) Source # | |||||
Defined in M.Pack.Internal.Newtypes | |||||
type Rep (EnumIndex i a) Source # | |||||
Defined in M.Pack.Internal.Newtypes |
newtype Fixed' (i :: k) (r :: k1) f Source #
use an integer type i
for serialization of a fixed-point number
with resolution r
(see HasResolution
, Fixed
), with underlying
numeric representation f
Instances
Lift f => Lift (Fixed' i r f :: Type) Source # | |||||
(Typeable i, Typeable r, Typeable k1, Typeable k2, Data f) => Data (Fixed' i r f) Source # | |||||
Defined in M.Pack.Internal.Newtypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Fixed' i r f -> c (Fixed' i r f) # gunfold :: (forall b r0. Data b => c (b -> r0) -> c r0) -> (forall r1. r1 -> c r1) -> Constr -> c (Fixed' i r f) # toConstr :: Fixed' i r f -> Constr # dataTypeOf :: Fixed' i r f -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Fixed' i r f)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Fixed' i r f)) # gmapT :: (forall b. Data b => b -> b) -> Fixed' i r f -> Fixed' i r f # gmapQl :: (r0 -> r' -> r0) -> r0 -> (forall d. Data d => d -> r') -> Fixed' i r f -> r0 # gmapQr :: forall r0 r'. (r' -> r0 -> r0) -> r0 -> (forall d. Data d => d -> r') -> Fixed' i r f -> r0 # gmapQ :: (forall d. Data d => d -> u) -> Fixed' i r f -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Fixed' i r f -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Fixed' i r f -> m (Fixed' i r f) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixed' i r f -> m (Fixed' i r f) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixed' i r f -> m (Fixed' i r f) # | |||||
Enum f => Enum (Fixed' i r f) Source # | |||||
Defined in M.Pack.Internal.Newtypes succ :: Fixed' i r f -> Fixed' i r f # pred :: Fixed' i r f -> Fixed' i r f # toEnum :: Int -> Fixed' i r f # fromEnum :: Fixed' i r f -> Int # enumFrom :: Fixed' i r f -> [Fixed' i r f] # enumFromThen :: Fixed' i r f -> Fixed' i r f -> [Fixed' i r f] # enumFromTo :: Fixed' i r f -> Fixed' i r f -> [Fixed' i r f] # enumFromThenTo :: Fixed' i r f -> Fixed' i r f -> Fixed' i r f -> [Fixed' i r f] # | |||||
Generic (Fixed' i r f) Source # | |||||
Defined in M.Pack.Internal.Newtypes
| |||||
Num f => Num (Fixed' i r f) Source # | |||||
Defined in M.Pack.Internal.Newtypes (+) :: Fixed' i r f -> Fixed' i r f -> Fixed' i r f # (-) :: Fixed' i r f -> Fixed' i r f -> Fixed' i r f # (*) :: Fixed' i r f -> Fixed' i r f -> Fixed' i r f # negate :: Fixed' i r f -> Fixed' i r f # abs :: Fixed' i r f -> Fixed' i r f # signum :: Fixed' i r f -> Fixed' i r f # fromInteger :: Integer -> Fixed' i r f # | |||||
Read f => Read (Fixed' i r f) Source # | |||||
Fractional f => Fractional (Fixed' i r f) Source # | |||||
Real f => Real (Fixed' i r f) Source # | |||||
Defined in M.Pack.Internal.Newtypes toRational :: Fixed' i r f -> Rational # | |||||
RealFrac f => RealFrac (Fixed' i r f) Source # | |||||
Show f => Show (Fixed' i r f) Source # | |||||
NFData f => NFData (Fixed' i r f) Source # | |||||
Defined in M.Pack.Internal.Newtypes | |||||
Eq f => Eq (Fixed' i r f) Source # | |||||
Ord f => Ord (Fixed' i r f) Source # | |||||
Defined in M.Pack.Internal.Newtypes | |||||
Hashable f => Hashable (Fixed' i r f) Source # | |||||
Defined in M.Pack.Internal.Newtypes | |||||
(Integral i, Pack i, Real f, HasResolution r) => Pack (Fixed' i r f) Source # | |||||
(Integral i, Unpack i, Fractional f, HasResolution r) => Unpack (Fixed' i r f) Source # | |||||
Defined in M.Pack.Internal.Newtypes | |||||
type Rep (Fixed' i r f) Source # | |||||
Defined in M.Pack.Internal.Newtypes |
a signed angle; divides the circle into 256 parts
Instances
newtype Identifier Source #
an "identifier" string, used for names, tags, etc.
example: minecraft:stone
or stone/stone
validation only happens when unpacking (unpack
)
Instances
Data Identifier Source # | |||||
Defined in M.Pack.Internal.Newtypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Identifier -> c Identifier # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Identifier # toConstr :: Identifier -> Constr # dataTypeOf :: Identifier -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Identifier) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Identifier) # gmapT :: (forall b. Data b => b -> b) -> Identifier -> Identifier # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Identifier -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Identifier -> r # gmapQ :: (forall d. Data d => d -> u) -> Identifier -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Identifier -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Identifier -> m Identifier # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Identifier -> m Identifier # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Identifier -> m Identifier # | |||||
IsString Identifier Source # | |||||
Defined in M.Pack.Internal.Newtypes fromString :: String -> Identifier # | |||||
Monoid Identifier Source # | |||||
Defined in M.Pack.Internal.Newtypes mempty :: Identifier # mappend :: Identifier -> Identifier -> Identifier # mconcat :: [Identifier] -> Identifier # | |||||
Semigroup Identifier Source # | |||||
Defined in M.Pack.Internal.Newtypes (<>) :: Identifier -> Identifier -> Identifier # sconcat :: NonEmpty Identifier -> Identifier # stimes :: Integral b => b -> Identifier -> Identifier # | |||||
Generic Identifier Source # | |||||
Defined in M.Pack.Internal.Newtypes
from :: Identifier -> Rep Identifier x # to :: Rep Identifier x -> Identifier # | |||||
Read Identifier Source # | |||||
Defined in M.Pack.Internal.Newtypes readsPrec :: Int -> ReadS Identifier # readList :: ReadS [Identifier] # readPrec :: ReadPrec Identifier # readListPrec :: ReadPrec [Identifier] # | |||||
Show Identifier Source # | |||||
Defined in M.Pack.Internal.Newtypes showsPrec :: Int -> Identifier -> ShowS # show :: Identifier -> String # showList :: [Identifier] -> ShowS # | |||||
NFData Identifier Source # | |||||
Defined in M.Pack.Internal.Newtypes rnf :: Identifier -> () # | |||||
Eq Identifier Source # | |||||
Defined in M.Pack.Internal.Newtypes (==) :: Identifier -> Identifier -> Bool # (/=) :: Identifier -> Identifier -> Bool # | |||||
Ord Identifier Source # | |||||
Defined in M.Pack.Internal.Newtypes compare :: Identifier -> Identifier -> Ordering # (<) :: Identifier -> Identifier -> Bool # (<=) :: Identifier -> Identifier -> Bool # (>) :: Identifier -> Identifier -> Bool # (>=) :: Identifier -> Identifier -> Bool # max :: Identifier -> Identifier -> Identifier # min :: Identifier -> Identifier -> Identifier # | |||||
Hashable Identifier Source # | |||||
Defined in M.Pack.Internal.Newtypes hashWithSalt :: Int -> Identifier -> Int hash :: Identifier -> Int | |||||
Pack Identifier Source # | |||||
Defined in M.Pack.Internal.Newtypes pack :: Identifier -> Builder Source # | |||||
Unpack Identifier Source # | |||||
Defined in M.Pack.Internal.Newtypes unpack :: forall (st :: ZeroBitType) r. Parser st r Identifier Source # | |||||
Lift Identifier Source # | |||||
Defined in M.Pack.Internal.Newtypes lift :: Quote m => Identifier -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => Identifier -> Code m Identifier # | |||||
type Rep Identifier Source # | |||||
Defined in M.Pack.Internal.Newtypes type Rep Identifier = D1 ('MetaData "Identifier" "M.Pack.Internal.Newtypes" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'True) (C1 ('MetaCons "Identifier" 'PrefixI 'True) (S1 ('MetaSel ('Just "identifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
unresolved value; either an ID or an inline value
Instances
Foldable IDorX Source # | |||||
Defined in M.Pack.Internal.Newtypes fold :: Monoid m => IDorX m -> m # foldMap :: Monoid m => (a -> m) -> IDorX a -> m # foldMap' :: Monoid m => (a -> m) -> IDorX a -> m # foldr :: (a -> b -> b) -> b -> IDorX a -> b # foldr' :: (a -> b -> b) -> b -> IDorX a -> b # foldl :: (b -> a -> b) -> b -> IDorX a -> b # foldl' :: (b -> a -> b) -> b -> IDorX a -> b # foldr1 :: (a -> a -> a) -> IDorX a -> a # foldl1 :: (a -> a -> a) -> IDorX a -> a # elem :: Eq a => a -> IDorX a -> Bool # maximum :: Ord a => IDorX a -> a # minimum :: Ord a => IDorX a -> a # | |||||
Applicative IDorX Source # | |||||
Functor IDorX Source # | |||||
Monad IDorX Source # | |||||
Lift a => Lift (IDorX a :: Type) Source # | |||||
Data a => Data (IDorX a) Source # | |||||
Defined in M.Pack.Internal.Newtypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IDorX a -> c (IDorX a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IDorX a) # toConstr :: IDorX a -> Constr # dataTypeOf :: IDorX a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IDorX a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IDorX a)) # gmapT :: (forall b. Data b => b -> b) -> IDorX a -> IDorX a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IDorX a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IDorX a -> r # gmapQ :: (forall d. Data d => d -> u) -> IDorX a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IDorX a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IDorX a -> m (IDorX a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IDorX a -> m (IDorX a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IDorX a -> m (IDorX a) # | |||||
Semigroup (IDorX a) Source # | |||||
Generic (IDorX a) Source # | |||||
Defined in M.Pack.Internal.Newtypes
| |||||
Read a => Read (IDorX a) Source # | |||||
Show a => Show (IDorX a) Source # | |||||
NFData a => NFData (IDorX a) Source # | |||||
Defined in M.Pack.Internal.Newtypes | |||||
Eq a => Eq (IDorX a) Source # | |||||
Ord a => Ord (IDorX a) Source # | |||||
Hashable a => Hashable (IDorX a) Source # | |||||
Defined in M.Pack.Internal.Newtypes | |||||
Pack a => Pack (IDorX a) Source # | |||||
Unpack a => Unpack (IDorX a) Source # | |||||
Defined in M.Pack.Internal.Newtypes | |||||
type Rep (IDorX a) Source # | |||||
Defined in M.Pack.Internal.Newtypes |
potentially unresolved ID set; either an identifier for its location or an inline set of IDs
IDSet | |
|
Instances
Data IDSet Source # | |||||
Defined in M.Pack.Internal.Newtypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IDSet -> c IDSet # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IDSet # dataTypeOf :: IDSet -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IDSet) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IDSet) # gmapT :: (forall b. Data b => b -> b) -> IDSet -> IDSet # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IDSet -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IDSet -> r # gmapQ :: (forall d. Data d => d -> u) -> IDSet -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IDSet -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IDSet -> m IDSet # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IDSet -> m IDSet # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IDSet -> m IDSet # | |||||
Semigroup IDSet Source # | |||||
Generic IDSet Source # | |||||
Defined in M.Pack.Internal.Newtypes
| |||||
Read IDSet Source # | |||||
Show IDSet Source # | |||||
NFData IDSet Source # | |||||
Defined in M.Pack.Internal.Newtypes | |||||
Eq IDSet Source # | |||||
Ord IDSet Source # | |||||
Pack IDSet Source # | |||||
Unpack IDSet Source # | |||||
Defined in M.Pack.Internal.Newtypes | |||||
type Rep IDSet Source # | |||||
Defined in M.Pack.Internal.Newtypes |
a newtype wrapper over ByteString
; not length-prefixed
Instances
Data TakeRest Source # | |||||
Defined in M.Pack.Internal.Newtypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TakeRest -> c TakeRest # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TakeRest # toConstr :: TakeRest -> Constr # dataTypeOf :: TakeRest -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TakeRest) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TakeRest) # gmapT :: (forall b. Data b => b -> b) -> TakeRest -> TakeRest # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TakeRest -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TakeRest -> r # gmapQ :: (forall d. Data d => d -> u) -> TakeRest -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TakeRest -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TakeRest -> m TakeRest # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TakeRest -> m TakeRest # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TakeRest -> m TakeRest # | |||||
Monoid TakeRest Source # | |||||
Semigroup TakeRest Source # | |||||
Generic TakeRest Source # | |||||
Defined in M.Pack.Internal.Newtypes
| |||||
Read TakeRest Source # | |||||
Show TakeRest Source # | |||||
NFData TakeRest Source # | |||||
Defined in M.Pack.Internal.Newtypes | |||||
Eq TakeRest Source # | |||||
Ord TakeRest Source # | |||||
Defined in M.Pack.Internal.Newtypes | |||||
Hashable TakeRest Source # | |||||
Defined in M.Pack.Internal.Newtypes | |||||
Pack TakeRest Source # |
| ||||
Unpack TakeRest Source # |
| ||||
Defined in M.Pack.Internal.Newtypes | |||||
Lift TakeRest Source # | |||||
type Rep TakeRest Source # | |||||
Defined in M.Pack.Internal.Newtypes type Rep TakeRest = D1 ('MetaData "TakeRest" "M.Pack.Internal.Newtypes" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'True) (C1 ('MetaCons "TakeRest" 'PrefixI 'True) (S1 ('MetaSel ('Just "gettakerest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
newtype PackFoldableVI (f :: k -> Type) (a :: k) Source #
PackFoldableVI | |
|
Instances
Generic1 (PackFoldableVI f :: k -> Type) Source # | |||||
Defined in M.Pack.Internal.Newtypes
from1 :: forall (a :: k). PackFoldableVI f a -> Rep1 (PackFoldableVI f) a # to1 :: forall (a :: k). Rep1 (PackFoldableVI f) a -> PackFoldableVI f a # | |||||
Lift (f a) => Lift (PackFoldableVI f a :: Type) Source # | |||||
Defined in M.Pack.Internal.Newtypes lift :: Quote m => PackFoldableVI f a -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => PackFoldableVI f a -> Code m (PackFoldableVI f a) # | |||||
Foldable f => Foldable (PackFoldableVI f) Source # | |||||
Defined in M.Pack.Internal.Newtypes fold :: Monoid m => PackFoldableVI f m -> m # foldMap :: Monoid m => (a -> m) -> PackFoldableVI f a -> m # foldMap' :: Monoid m => (a -> m) -> PackFoldableVI f a -> m # foldr :: (a -> b -> b) -> b -> PackFoldableVI f a -> b # foldr' :: (a -> b -> b) -> b -> PackFoldableVI f a -> b # foldl :: (b -> a -> b) -> b -> PackFoldableVI f a -> b # foldl' :: (b -> a -> b) -> b -> PackFoldableVI f a -> b # foldr1 :: (a -> a -> a) -> PackFoldableVI f a -> a # foldl1 :: (a -> a -> a) -> PackFoldableVI f a -> a # toList :: PackFoldableVI f a -> [a] # null :: PackFoldableVI f a -> Bool # length :: PackFoldableVI f a -> Int # elem :: Eq a => a -> PackFoldableVI f a -> Bool # maximum :: Ord a => PackFoldableVI f a -> a # minimum :: Ord a => PackFoldableVI f a -> a # sum :: Num a => PackFoldableVI f a -> a # product :: Num a => PackFoldableVI f a -> a # | |||||
Foldable1 f => Foldable1 (PackFoldableVI f) Source # | |||||
Defined in M.Pack.Internal.Newtypes fold1 :: Semigroup m => PackFoldableVI f m -> m # foldMap1 :: Semigroup m => (a -> m) -> PackFoldableVI f a -> m # foldMap1' :: Semigroup m => (a -> m) -> PackFoldableVI f a -> m # toNonEmpty :: PackFoldableVI f a -> NonEmpty a # maximum :: Ord a => PackFoldableVI f a -> a # minimum :: Ord a => PackFoldableVI f a -> a # head :: PackFoldableVI f a -> a # last :: PackFoldableVI f a -> a # foldrMap1 :: (a -> b) -> (a -> b -> b) -> PackFoldableVI f a -> b # foldlMap1' :: (a -> b) -> (b -> a -> b) -> PackFoldableVI f a -> b # foldlMap1 :: (a -> b) -> (b -> a -> b) -> PackFoldableVI f a -> b # foldrMap1' :: (a -> b) -> (a -> b -> b) -> PackFoldableVI f a -> b # | |||||
Eq1 f => Eq1 (PackFoldableVI f) Source # | |||||
Defined in M.Pack.Internal.Newtypes liftEq :: (a -> b -> Bool) -> PackFoldableVI f a -> PackFoldableVI f b -> Bool # | |||||
Ord1 f => Ord1 (PackFoldableVI f) Source # | |||||
Defined in M.Pack.Internal.Newtypes liftCompare :: (a -> b -> Ordering) -> PackFoldableVI f a -> PackFoldableVI f b -> Ordering # | |||||
Read1 f => Read1 (PackFoldableVI f) Source # | |||||
Defined in M.Pack.Internal.Newtypes liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (PackFoldableVI f a) # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [PackFoldableVI f a] # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (PackFoldableVI f a) # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [PackFoldableVI f a] # | |||||
Show1 f => Show1 (PackFoldableVI f) Source # | |||||
Defined in M.Pack.Internal.Newtypes liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> PackFoldableVI f a -> ShowS # liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [PackFoldableVI f a] -> ShowS # | |||||
Applicative f => Applicative (PackFoldableVI f) Source # | |||||
Defined in M.Pack.Internal.Newtypes pure :: a -> PackFoldableVI f a # (<*>) :: PackFoldableVI f (a -> b) -> PackFoldableVI f a -> PackFoldableVI f b # liftA2 :: (a -> b -> c) -> PackFoldableVI f a -> PackFoldableVI f b -> PackFoldableVI f c # (*>) :: PackFoldableVI f a -> PackFoldableVI f b -> PackFoldableVI f b # (<*) :: PackFoldableVI f a -> PackFoldableVI f b -> PackFoldableVI f a # | |||||
Functor f => Functor (PackFoldableVI f) Source # | |||||
Defined in M.Pack.Internal.Newtypes fmap :: (a -> b) -> PackFoldableVI f a -> PackFoldableVI f b # (<$) :: a -> PackFoldableVI f b -> PackFoldableVI f a # | |||||
Monad f => Monad (PackFoldableVI f) Source # | |||||
Defined in M.Pack.Internal.Newtypes (>>=) :: PackFoldableVI f a -> (a -> PackFoldableVI f b) -> PackFoldableVI f b # (>>) :: PackFoldableVI f a -> PackFoldableVI f b -> PackFoldableVI f b # return :: a -> PackFoldableVI f a # | |||||
(Typeable a, Typeable f, Typeable k, Data (f a)) => Data (PackFoldableVI f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackFoldableVI f a -> c (PackFoldableVI f a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PackFoldableVI f a) # toConstr :: PackFoldableVI f a -> Constr # dataTypeOf :: PackFoldableVI f a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PackFoldableVI f a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PackFoldableVI f a)) # gmapT :: (forall b. Data b => b -> b) -> PackFoldableVI f a -> PackFoldableVI f a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackFoldableVI f a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackFoldableVI f a -> r # gmapQ :: (forall d. Data d => d -> u) -> PackFoldableVI f a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PackFoldableVI f a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackFoldableVI f a -> m (PackFoldableVI f a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackFoldableVI f a -> m (PackFoldableVI f a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackFoldableVI f a -> m (PackFoldableVI f a) # | |||||
Monoid (f a) => Monoid (PackFoldableVI f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes mempty :: PackFoldableVI f a # mappend :: PackFoldableVI f a -> PackFoldableVI f a -> PackFoldableVI f a # mconcat :: [PackFoldableVI f a] -> PackFoldableVI f a # | |||||
Semigroup (f a) => Semigroup (PackFoldableVI f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes (<>) :: PackFoldableVI f a -> PackFoldableVI f a -> PackFoldableVI f a # sconcat :: NonEmpty (PackFoldableVI f a) -> PackFoldableVI f a # stimes :: Integral b => b -> PackFoldableVI f a -> PackFoldableVI f a # | |||||
Generic (PackFoldableVI f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes
from :: PackFoldableVI f a -> Rep (PackFoldableVI f a) x # to :: Rep (PackFoldableVI f a) x -> PackFoldableVI f a # | |||||
Read (f a) => Read (PackFoldableVI f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes readsPrec :: Int -> ReadS (PackFoldableVI f a) # readList :: ReadS [PackFoldableVI f a] # readPrec :: ReadPrec (PackFoldableVI f a) # readListPrec :: ReadPrec [PackFoldableVI f a] # | |||||
Show (f a) => Show (PackFoldableVI f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes showsPrec :: Int -> PackFoldableVI f a -> ShowS # show :: PackFoldableVI f a -> String # showList :: [PackFoldableVI f a] -> ShowS # | |||||
NFData (f a) => NFData (PackFoldableVI f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes rnf :: PackFoldableVI f a -> () # | |||||
Eq (f a) => Eq (PackFoldableVI f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes (==) :: PackFoldableVI f a -> PackFoldableVI f a -> Bool # (/=) :: PackFoldableVI f a -> PackFoldableVI f a -> Bool # | |||||
Ord (f a) => Ord (PackFoldableVI f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes compare :: PackFoldableVI f a -> PackFoldableVI f a -> Ordering # (<) :: PackFoldableVI f a -> PackFoldableVI f a -> Bool # (<=) :: PackFoldableVI f a -> PackFoldableVI f a -> Bool # (>) :: PackFoldableVI f a -> PackFoldableVI f a -> Bool # (>=) :: PackFoldableVI f a -> PackFoldableVI f a -> Bool # max :: PackFoldableVI f a -> PackFoldableVI f a -> PackFoldableVI f a # min :: PackFoldableVI f a -> PackFoldableVI f a -> PackFoldableVI f a # | |||||
Hashable (f a) => Hashable (PackFoldableVI f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes hashWithSalt :: Int -> PackFoldableVI f a -> Int hash :: PackFoldableVI f a -> Int | |||||
(Pack a, Foldable f) => Pack (PackFoldableVI f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes pack :: PackFoldableVI f a -> Builder Source # | |||||
type Rep1 (PackFoldableVI f :: k -> Type) Source # | |||||
Defined in M.Pack.Internal.Newtypes type Rep1 (PackFoldableVI f :: k -> Type) = D1 ('MetaData "PackFoldableVI" "M.Pack.Internal.Newtypes" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'True) (C1 ('MetaCons "PackFoldableVI" 'PrefixI 'True) (S1 ('MetaSel ('Just "getpackfoldablevi") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 f))) | |||||
type Rep (PackFoldableVI f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes type Rep (PackFoldableVI f a) = D1 ('MetaData "PackFoldableVI" "M.Pack.Internal.Newtypes" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'True) (C1 ('MetaCons "PackFoldableVI" 'PrefixI 'True) (S1 ('MetaSel ('Just "getpackfoldablevi") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a)))) |
newtype PackFoldable0 (f :: k -> Type) (a :: k) Source #
PackFoldable0 | |
|
Instances
Generic1 (PackFoldable0 f :: k -> Type) Source # | |||||
Defined in M.Pack.Internal.Newtypes
from1 :: forall (a :: k). PackFoldable0 f a -> Rep1 (PackFoldable0 f) a # to1 :: forall (a :: k). Rep1 (PackFoldable0 f) a -> PackFoldable0 f a # | |||||
Lift (f a) => Lift (PackFoldable0 f a :: Type) Source # | |||||
Defined in M.Pack.Internal.Newtypes lift :: Quote m => PackFoldable0 f a -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => PackFoldable0 f a -> Code m (PackFoldable0 f a) # | |||||
Foldable f => Foldable (PackFoldable0 f) Source # | |||||
Defined in M.Pack.Internal.Newtypes fold :: Monoid m => PackFoldable0 f m -> m # foldMap :: Monoid m => (a -> m) -> PackFoldable0 f a -> m # foldMap' :: Monoid m => (a -> m) -> PackFoldable0 f a -> m # foldr :: (a -> b -> b) -> b -> PackFoldable0 f a -> b # foldr' :: (a -> b -> b) -> b -> PackFoldable0 f a -> b # foldl :: (b -> a -> b) -> b -> PackFoldable0 f a -> b # foldl' :: (b -> a -> b) -> b -> PackFoldable0 f a -> b # foldr1 :: (a -> a -> a) -> PackFoldable0 f a -> a # foldl1 :: (a -> a -> a) -> PackFoldable0 f a -> a # toList :: PackFoldable0 f a -> [a] # null :: PackFoldable0 f a -> Bool # length :: PackFoldable0 f a -> Int # elem :: Eq a => a -> PackFoldable0 f a -> Bool # maximum :: Ord a => PackFoldable0 f a -> a # minimum :: Ord a => PackFoldable0 f a -> a # sum :: Num a => PackFoldable0 f a -> a # product :: Num a => PackFoldable0 f a -> a # | |||||
Foldable1 f => Foldable1 (PackFoldable0 f) Source # | |||||
Defined in M.Pack.Internal.Newtypes fold1 :: Semigroup m => PackFoldable0 f m -> m # foldMap1 :: Semigroup m => (a -> m) -> PackFoldable0 f a -> m # foldMap1' :: Semigroup m => (a -> m) -> PackFoldable0 f a -> m # toNonEmpty :: PackFoldable0 f a -> NonEmpty a # maximum :: Ord a => PackFoldable0 f a -> a # minimum :: Ord a => PackFoldable0 f a -> a # head :: PackFoldable0 f a -> a # last :: PackFoldable0 f a -> a # foldrMap1 :: (a -> b) -> (a -> b -> b) -> PackFoldable0 f a -> b # foldlMap1' :: (a -> b) -> (b -> a -> b) -> PackFoldable0 f a -> b # foldlMap1 :: (a -> b) -> (b -> a -> b) -> PackFoldable0 f a -> b # foldrMap1' :: (a -> b) -> (a -> b -> b) -> PackFoldable0 f a -> b # | |||||
Eq1 f => Eq1 (PackFoldable0 f) Source # | |||||
Defined in M.Pack.Internal.Newtypes liftEq :: (a -> b -> Bool) -> PackFoldable0 f a -> PackFoldable0 f b -> Bool # | |||||
Ord1 f => Ord1 (PackFoldable0 f) Source # | |||||
Defined in M.Pack.Internal.Newtypes liftCompare :: (a -> b -> Ordering) -> PackFoldable0 f a -> PackFoldable0 f b -> Ordering # | |||||
Read1 f => Read1 (PackFoldable0 f) Source # | |||||
Defined in M.Pack.Internal.Newtypes liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (PackFoldable0 f a) # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [PackFoldable0 f a] # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (PackFoldable0 f a) # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [PackFoldable0 f a] # | |||||
Show1 f => Show1 (PackFoldable0 f) Source # | |||||
Defined in M.Pack.Internal.Newtypes liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> PackFoldable0 f a -> ShowS # liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [PackFoldable0 f a] -> ShowS # | |||||
Applicative f => Applicative (PackFoldable0 f) Source # | |||||
Defined in M.Pack.Internal.Newtypes pure :: a -> PackFoldable0 f a # (<*>) :: PackFoldable0 f (a -> b) -> PackFoldable0 f a -> PackFoldable0 f b # liftA2 :: (a -> b -> c) -> PackFoldable0 f a -> PackFoldable0 f b -> PackFoldable0 f c # (*>) :: PackFoldable0 f a -> PackFoldable0 f b -> PackFoldable0 f b # (<*) :: PackFoldable0 f a -> PackFoldable0 f b -> PackFoldable0 f a # | |||||
Functor f => Functor (PackFoldable0 f) Source # | |||||
Defined in M.Pack.Internal.Newtypes fmap :: (a -> b) -> PackFoldable0 f a -> PackFoldable0 f b # (<$) :: a -> PackFoldable0 f b -> PackFoldable0 f a # | |||||
Monad f => Monad (PackFoldable0 f) Source # | |||||
Defined in M.Pack.Internal.Newtypes (>>=) :: PackFoldable0 f a -> (a -> PackFoldable0 f b) -> PackFoldable0 f b # (>>) :: PackFoldable0 f a -> PackFoldable0 f b -> PackFoldable0 f b # return :: a -> PackFoldable0 f a # | |||||
(Typeable a, Typeable f, Typeable k, Data (f a)) => Data (PackFoldable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackFoldable0 f a -> c (PackFoldable0 f a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PackFoldable0 f a) # toConstr :: PackFoldable0 f a -> Constr # dataTypeOf :: PackFoldable0 f a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PackFoldable0 f a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PackFoldable0 f a)) # gmapT :: (forall b. Data b => b -> b) -> PackFoldable0 f a -> PackFoldable0 f a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackFoldable0 f a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackFoldable0 f a -> r # gmapQ :: (forall d. Data d => d -> u) -> PackFoldable0 f a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PackFoldable0 f a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackFoldable0 f a -> m (PackFoldable0 f a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackFoldable0 f a -> m (PackFoldable0 f a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackFoldable0 f a -> m (PackFoldable0 f a) # | |||||
Monoid (f a) => Monoid (PackFoldable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes mempty :: PackFoldable0 f a # mappend :: PackFoldable0 f a -> PackFoldable0 f a -> PackFoldable0 f a # mconcat :: [PackFoldable0 f a] -> PackFoldable0 f a # | |||||
Semigroup (f a) => Semigroup (PackFoldable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes (<>) :: PackFoldable0 f a -> PackFoldable0 f a -> PackFoldable0 f a # sconcat :: NonEmpty (PackFoldable0 f a) -> PackFoldable0 f a # stimes :: Integral b => b -> PackFoldable0 f a -> PackFoldable0 f a # | |||||
Generic (PackFoldable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes
from :: PackFoldable0 f a -> Rep (PackFoldable0 f a) x # to :: Rep (PackFoldable0 f a) x -> PackFoldable0 f a # | |||||
Read (f a) => Read (PackFoldable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes readsPrec :: Int -> ReadS (PackFoldable0 f a) # readList :: ReadS [PackFoldable0 f a] # readPrec :: ReadPrec (PackFoldable0 f a) # readListPrec :: ReadPrec [PackFoldable0 f a] # | |||||
Show (f a) => Show (PackFoldable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes showsPrec :: Int -> PackFoldable0 f a -> ShowS # show :: PackFoldable0 f a -> String # showList :: [PackFoldable0 f a] -> ShowS # | |||||
NFData (f a) => NFData (PackFoldable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes rnf :: PackFoldable0 f a -> () # | |||||
Eq (f a) => Eq (PackFoldable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes (==) :: PackFoldable0 f a -> PackFoldable0 f a -> Bool # (/=) :: PackFoldable0 f a -> PackFoldable0 f a -> Bool # | |||||
Ord (f a) => Ord (PackFoldable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes compare :: PackFoldable0 f a -> PackFoldable0 f a -> Ordering # (<) :: PackFoldable0 f a -> PackFoldable0 f a -> Bool # (<=) :: PackFoldable0 f a -> PackFoldable0 f a -> Bool # (>) :: PackFoldable0 f a -> PackFoldable0 f a -> Bool # (>=) :: PackFoldable0 f a -> PackFoldable0 f a -> Bool # max :: PackFoldable0 f a -> PackFoldable0 f a -> PackFoldable0 f a # min :: PackFoldable0 f a -> PackFoldable0 f a -> PackFoldable0 f a # | |||||
Hashable (f a) => Hashable (PackFoldable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes hashWithSalt :: Int -> PackFoldable0 f a -> Int hash :: PackFoldable0 f a -> Int | |||||
(Pack a, Foldable f) => Pack (PackFoldable0 f a) Source # |
| ||||
Defined in M.Pack.Internal.Newtypes pack :: PackFoldable0 f a -> Builder Source # | |||||
type Rep1 (PackFoldable0 f :: k -> Type) Source # | |||||
Defined in M.Pack.Internal.Newtypes type Rep1 (PackFoldable0 f :: k -> Type) = D1 ('MetaData "PackFoldable0" "M.Pack.Internal.Newtypes" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'True) (C1 ('MetaCons "PackFoldable0" 'PrefixI 'True) (S1 ('MetaSel ('Just "getpackfoldable0") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 f))) | |||||
type Rep (PackFoldable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes type Rep (PackFoldable0 f a) = D1 ('MetaData "PackFoldable0" "M.Pack.Internal.Newtypes" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'True) (C1 ('MetaCons "PackFoldable0" 'PrefixI 'True) (S1 ('MetaSel ('Just "getpackfoldable0") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a)))) |
newtype UnpackRepresentable0 (f :: k -> Type) (a :: k) Source #
General Unpack
instance provider for Representable
s that are also
Traversable
Instances
Generic1 (UnpackRepresentable0 f :: k -> Type) Source # | |||||
Defined in M.Pack.Internal.Newtypes
from1 :: forall (a :: k). UnpackRepresentable0 f a -> Rep1 (UnpackRepresentable0 f) a # to1 :: forall (a :: k). Rep1 (UnpackRepresentable0 f) a -> UnpackRepresentable0 f a # | |||||
Lift (f a) => Lift (UnpackRepresentable0 f a :: Type) Source # | |||||
Defined in M.Pack.Internal.Newtypes lift :: Quote m => UnpackRepresentable0 f a -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => UnpackRepresentable0 f a -> Code m (UnpackRepresentable0 f a) # | |||||
Foldable f => Foldable (UnpackRepresentable0 f) Source # | |||||
Defined in M.Pack.Internal.Newtypes fold :: Monoid m => UnpackRepresentable0 f m -> m # foldMap :: Monoid m => (a -> m) -> UnpackRepresentable0 f a -> m # foldMap' :: Monoid m => (a -> m) -> UnpackRepresentable0 f a -> m # foldr :: (a -> b -> b) -> b -> UnpackRepresentable0 f a -> b # foldr' :: (a -> b -> b) -> b -> UnpackRepresentable0 f a -> b # foldl :: (b -> a -> b) -> b -> UnpackRepresentable0 f a -> b # foldl' :: (b -> a -> b) -> b -> UnpackRepresentable0 f a -> b # foldr1 :: (a -> a -> a) -> UnpackRepresentable0 f a -> a # foldl1 :: (a -> a -> a) -> UnpackRepresentable0 f a -> a # toList :: UnpackRepresentable0 f a -> [a] # null :: UnpackRepresentable0 f a -> Bool # length :: UnpackRepresentable0 f a -> Int # elem :: Eq a => a -> UnpackRepresentable0 f a -> Bool # maximum :: Ord a => UnpackRepresentable0 f a -> a # minimum :: Ord a => UnpackRepresentable0 f a -> a # sum :: Num a => UnpackRepresentable0 f a -> a # product :: Num a => UnpackRepresentable0 f a -> a # | |||||
Foldable1 f => Foldable1 (UnpackRepresentable0 f) Source # | |||||
Defined in M.Pack.Internal.Newtypes fold1 :: Semigroup m => UnpackRepresentable0 f m -> m # foldMap1 :: Semigroup m => (a -> m) -> UnpackRepresentable0 f a -> m # foldMap1' :: Semigroup m => (a -> m) -> UnpackRepresentable0 f a -> m # toNonEmpty :: UnpackRepresentable0 f a -> NonEmpty a # maximum :: Ord a => UnpackRepresentable0 f a -> a # minimum :: Ord a => UnpackRepresentable0 f a -> a # head :: UnpackRepresentable0 f a -> a # last :: UnpackRepresentable0 f a -> a # foldrMap1 :: (a -> b) -> (a -> b -> b) -> UnpackRepresentable0 f a -> b # foldlMap1' :: (a -> b) -> (b -> a -> b) -> UnpackRepresentable0 f a -> b # foldlMap1 :: (a -> b) -> (b -> a -> b) -> UnpackRepresentable0 f a -> b # foldrMap1' :: (a -> b) -> (a -> b -> b) -> UnpackRepresentable0 f a -> b # | |||||
Eq1 f => Eq1 (UnpackRepresentable0 f) Source # | |||||
Defined in M.Pack.Internal.Newtypes liftEq :: (a -> b -> Bool) -> UnpackRepresentable0 f a -> UnpackRepresentable0 f b -> Bool # | |||||
Ord1 f => Ord1 (UnpackRepresentable0 f) Source # | |||||
Defined in M.Pack.Internal.Newtypes liftCompare :: (a -> b -> Ordering) -> UnpackRepresentable0 f a -> UnpackRepresentable0 f b -> Ordering # | |||||
Read1 f => Read1 (UnpackRepresentable0 f) Source # | |||||
Defined in M.Pack.Internal.Newtypes liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (UnpackRepresentable0 f a) # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [UnpackRepresentable0 f a] # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (UnpackRepresentable0 f a) # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [UnpackRepresentable0 f a] # | |||||
Show1 f => Show1 (UnpackRepresentable0 f) Source # | |||||
Defined in M.Pack.Internal.Newtypes liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> UnpackRepresentable0 f a -> ShowS # liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [UnpackRepresentable0 f a] -> ShowS # | |||||
Applicative f => Applicative (UnpackRepresentable0 f) Source # | |||||
Defined in M.Pack.Internal.Newtypes pure :: a -> UnpackRepresentable0 f a # (<*>) :: UnpackRepresentable0 f (a -> b) -> UnpackRepresentable0 f a -> UnpackRepresentable0 f b # liftA2 :: (a -> b -> c) -> UnpackRepresentable0 f a -> UnpackRepresentable0 f b -> UnpackRepresentable0 f c # (*>) :: UnpackRepresentable0 f a -> UnpackRepresentable0 f b -> UnpackRepresentable0 f b # (<*) :: UnpackRepresentable0 f a -> UnpackRepresentable0 f b -> UnpackRepresentable0 f a # | |||||
Functor f => Functor (UnpackRepresentable0 f) Source # | |||||
Defined in M.Pack.Internal.Newtypes fmap :: (a -> b) -> UnpackRepresentable0 f a -> UnpackRepresentable0 f b # (<$) :: a -> UnpackRepresentable0 f b -> UnpackRepresentable0 f a # | |||||
Monad f => Monad (UnpackRepresentable0 f) Source # | |||||
Defined in M.Pack.Internal.Newtypes (>>=) :: UnpackRepresentable0 f a -> (a -> UnpackRepresentable0 f b) -> UnpackRepresentable0 f b # (>>) :: UnpackRepresentable0 f a -> UnpackRepresentable0 f b -> UnpackRepresentable0 f b # return :: a -> UnpackRepresentable0 f a # | |||||
(Typeable a, Typeable f, Typeable k, Data (f a)) => Data (UnpackRepresentable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnpackRepresentable0 f a -> c (UnpackRepresentable0 f a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (UnpackRepresentable0 f a) # toConstr :: UnpackRepresentable0 f a -> Constr # dataTypeOf :: UnpackRepresentable0 f a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (UnpackRepresentable0 f a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (UnpackRepresentable0 f a)) # gmapT :: (forall b. Data b => b -> b) -> UnpackRepresentable0 f a -> UnpackRepresentable0 f a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnpackRepresentable0 f a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnpackRepresentable0 f a -> r # gmapQ :: (forall d. Data d => d -> u) -> UnpackRepresentable0 f a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UnpackRepresentable0 f a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnpackRepresentable0 f a -> m (UnpackRepresentable0 f a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnpackRepresentable0 f a -> m (UnpackRepresentable0 f a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnpackRepresentable0 f a -> m (UnpackRepresentable0 f a) # | |||||
Monoid (f a) => Monoid (UnpackRepresentable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes mempty :: UnpackRepresentable0 f a # mappend :: UnpackRepresentable0 f a -> UnpackRepresentable0 f a -> UnpackRepresentable0 f a # mconcat :: [UnpackRepresentable0 f a] -> UnpackRepresentable0 f a # | |||||
Semigroup (f a) => Semigroup (UnpackRepresentable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes (<>) :: UnpackRepresentable0 f a -> UnpackRepresentable0 f a -> UnpackRepresentable0 f a # sconcat :: NonEmpty (UnpackRepresentable0 f a) -> UnpackRepresentable0 f a # stimes :: Integral b => b -> UnpackRepresentable0 f a -> UnpackRepresentable0 f a # | |||||
Generic (UnpackRepresentable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes
from :: UnpackRepresentable0 f a -> Rep (UnpackRepresentable0 f a) x # to :: Rep (UnpackRepresentable0 f a) x -> UnpackRepresentable0 f a # | |||||
Read (f a) => Read (UnpackRepresentable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes readsPrec :: Int -> ReadS (UnpackRepresentable0 f a) # readList :: ReadS [UnpackRepresentable0 f a] # readPrec :: ReadPrec (UnpackRepresentable0 f a) # readListPrec :: ReadPrec [UnpackRepresentable0 f a] # | |||||
Show (f a) => Show (UnpackRepresentable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes showsPrec :: Int -> UnpackRepresentable0 f a -> ShowS # show :: UnpackRepresentable0 f a -> String # showList :: [UnpackRepresentable0 f a] -> ShowS # | |||||
NFData (f a) => NFData (UnpackRepresentable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes rnf :: UnpackRepresentable0 f a -> () # | |||||
Eq (f a) => Eq (UnpackRepresentable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes (==) :: UnpackRepresentable0 f a -> UnpackRepresentable0 f a -> Bool # (/=) :: UnpackRepresentable0 f a -> UnpackRepresentable0 f a -> Bool # | |||||
Ord (f a) => Ord (UnpackRepresentable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes compare :: UnpackRepresentable0 f a -> UnpackRepresentable0 f a -> Ordering # (<) :: UnpackRepresentable0 f a -> UnpackRepresentable0 f a -> Bool # (<=) :: UnpackRepresentable0 f a -> UnpackRepresentable0 f a -> Bool # (>) :: UnpackRepresentable0 f a -> UnpackRepresentable0 f a -> Bool # (>=) :: UnpackRepresentable0 f a -> UnpackRepresentable0 f a -> Bool # max :: UnpackRepresentable0 f a -> UnpackRepresentable0 f a -> UnpackRepresentable0 f a # min :: UnpackRepresentable0 f a -> UnpackRepresentable0 f a -> UnpackRepresentable0 f a # | |||||
Hashable (f a) => Hashable (UnpackRepresentable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes hashWithSalt :: Int -> UnpackRepresentable0 f a -> Int hash :: UnpackRepresentable0 f a -> Int | |||||
(Unpack a, Representable f, Traversable f) => Unpack (UnpackRepresentable0 f a) Source # |
| ||||
Defined in M.Pack.Internal.Newtypes unpack :: forall (st :: ZeroBitType) r. Parser st r (UnpackRepresentable0 f a) Source # | |||||
type Rep1 (UnpackRepresentable0 f :: k -> Type) Source # | |||||
Defined in M.Pack.Internal.Newtypes type Rep1 (UnpackRepresentable0 f :: k -> Type) = D1 ('MetaData "UnpackRepresentable0" "M.Pack.Internal.Newtypes" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'True) (C1 ('MetaCons "UnpackRepresentable0" 'PrefixI 'True) (S1 ('MetaSel ('Just "getunpackrepresentable0") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 f))) | |||||
type Rep (UnpackRepresentable0 f a) Source # | |||||
Defined in M.Pack.Internal.Newtypes type Rep (UnpackRepresentable0 f a) = D1 ('MetaData "UnpackRepresentable0" "M.Pack.Internal.Newtypes" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'True) (C1 ('MetaCons "UnpackRepresentable0" 'PrefixI 'True) (S1 ('MetaSel ('Just "getunpackrepresentable0") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a)))) |