Safe Haskell | None |
---|---|
Language | Haskell2010 |
Language.Java.Class.ConstantPool
- data ConstantPool p c = ConstantPool Word16 (c (ConstantPoolInfo p))
- class AsConstantPool p f s where
- _ConstantPool :: Optic' p f (s p' c) (Word16, c (ConstantPoolInfo p'))
- data ConstantPoolError c
- class AsConstantPoolCountUnexpectedEof p f s where
- _ConstantPoolCountUnexpectedEof :: Optic' p f s ()
- constantPoolCountUnexpectedEof :: AsConstantPoolCountUnexpectedEof Tagged Identity t => t
- class AsConstantPoolConstantPoolInfoError p f s where
- _ConstantPoolConstantPoolInfoError :: Optic' p f (s c) (ConstantPoolInfoError c)
- constantPool :: (AsEmpty (c Word8), AsEmpty (q Char), AsEmpty (c1 (ConstantPoolInfo p')), Cons (c Word8) (c Word8) Word8 Word8, Cons (q Char) (q Char) Char Char, Cons (c1 (ConstantPoolInfo p')) (c1 (ConstantPoolInfo p')) (s1 q) (s1 q), AsUtf8 Tagged Identity s1, AsNameAndType Tagged Identity (s1 q), AsConstantDouble Tagged Identity (s1 q), AsConstantDouble (Market Double Double) Identity (s1 q), AsConstantLong Tagged Identity (s1 q), AsConstantLong (Market Int64 Int64) Identity (s1 q), AsConstantFloat Tagged Identity (s1 q), AsConstantInteger Tagged Identity (s1 q), AsConstantString Tagged Identity (s1 q), AsInterfaceMethodRef Tagged Identity (s1 q), AsMethodRef Tagged Identity (s1 q), AsFieldRef Tagged Identity (s1 q), AsConstantClass Tagged Identity (s1 q), AsConstantPoolConstantPoolInfoError Tagged Identity s, AsConstantPoolCountUnexpectedEof Tagged Identity (s c), AsConstantPool Tagged Identity s2) => Get (s c) (s2 p' c1)
- constantPool' :: (AsEmpty (c1 (ConstantPoolInfo p')), Cons (c1 (ConstantPoolInfo p')) (c1 (ConstantPoolInfo p')) a a, AsConstantDouble (Market Double Double) Identity a, AsConstantLong (Market Int64 Int64) Identity a, AsConstantPoolConstantPoolInfoError Tagged Identity s, AsConstantPoolCountUnexpectedEof Tagged Identity (s c), AsConstantPool Tagged Identity s1) => Get (ConstantPoolInfoError c) a -> Get (s c) (s1 p' c1)
Documentation
data ConstantPool p c Source
Constructors
ConstantPool Word16 (c (ConstantPoolInfo p)) |
Instances
(Profunctor p, Functor f) => AsConstantPool p f ConstantPool Source | |
Eq (c (ConstantPoolInfo p)) => Eq (ConstantPool p c) Source | |
Ord (c (ConstantPoolInfo p)) => Ord (ConstantPool p c) Source | |
Show (c (ConstantPoolInfo p)) => Show (ConstantPool p c) Source |
class AsConstantPool p f s where Source
Minimal complete definition
Nothing
Methods
_ConstantPool :: Optic' p f (s p' c) (Word16, c (ConstantPoolInfo p')) Source
Instances
(Profunctor p, Functor f) => AsConstantPool p f ConstantPool Source |
data ConstantPoolError c Source
Constructors
ConstantPoolCountUnexpectedEof | |
ConstantPoolConstantPoolInfoError (ConstantPoolInfoError c) |
Instances
class AsConstantPoolCountUnexpectedEof p f s where Source
Minimal complete definition
Nothing
Methods
_ConstantPoolCountUnexpectedEof :: Optic' p f s () Source
Instances
(Choice p, Applicative f) => AsConstantPoolCountUnexpectedEof p f (ConstantPoolError c) Source | |
(Choice p, Applicative f) => AsConstantPoolCountUnexpectedEof p f (ClassFileError c) Source |
class AsConstantPoolConstantPoolInfoError p f s where Source
Minimal complete definition
Nothing
Methods
_ConstantPoolConstantPoolInfoError :: Optic' p f (s c) (ConstantPoolInfoError c) Source
Instances
(Choice p, Applicative f) => AsConstantPoolConstantPoolInfoError p f ConstantPoolError Source | |
(Choice p, Applicative f) => AsConstantPoolConstantPoolInfoError p f ClassFileError Source |
constantPool :: (AsEmpty (c Word8), AsEmpty (q Char), AsEmpty (c1 (ConstantPoolInfo p')), Cons (c Word8) (c Word8) Word8 Word8, Cons (q Char) (q Char) Char Char, Cons (c1 (ConstantPoolInfo p')) (c1 (ConstantPoolInfo p')) (s1 q) (s1 q), AsUtf8 Tagged Identity s1, AsNameAndType Tagged Identity (s1 q), AsConstantDouble Tagged Identity (s1 q), AsConstantDouble (Market Double Double) Identity (s1 q), AsConstantLong Tagged Identity (s1 q), AsConstantLong (Market Int64 Int64) Identity (s1 q), AsConstantFloat Tagged Identity (s1 q), AsConstantInteger Tagged Identity (s1 q), AsConstantString Tagged Identity (s1 q), AsInterfaceMethodRef Tagged Identity (s1 q), AsMethodRef Tagged Identity (s1 q), AsFieldRef Tagged Identity (s1 q), AsConstantClass Tagged Identity (s1 q), AsConstantPoolConstantPoolInfoError Tagged Identity s, AsConstantPoolCountUnexpectedEof Tagged Identity (s c), AsConstantPool Tagged Identity s2) => Get (s c) (s2 p' c1) Source
constantPool' :: (AsEmpty (c1 (ConstantPoolInfo p')), Cons (c1 (ConstantPoolInfo p')) (c1 (ConstantPoolInfo p')) a a, AsConstantDouble (Market Double Double) Identity a, AsConstantLong (Market Int64 Int64) Identity a, AsConstantPoolConstantPoolInfoError Tagged Identity s, AsConstantPoolCountUnexpectedEof Tagged Identity (s c), AsConstantPool Tagged Identity s1) => Get (ConstantPoolInfoError c) a -> Get (s c) (s1 p' c1) Source