jvm-binary-0.0.2: A library for reading Java class-files

Copyright(c) Christian Gram Kalhauge 2017
LicenseMIT
Maintainerkalhuage@cs.ucla.edu
Safe HaskellSafe
LanguageHaskell2010

Language.JVM.Utils

Contents

Description

This module contains utilities missing not in other libraries.

Synopsis

Sized Data Structures

These data structures enables binary reading and writing of lists and byte strings that are prepended with the number of elements to read or write.

newtype SizedList w a Source #

SizedList is a binary type, that reads a list of elements. It first reads a length N of type w and then N items of type a.

Constructors

SizedList 

Fields

Instances

Functor (SizedList w) Source # 

Methods

fmap :: (a -> b) -> SizedList w a -> SizedList w b #

(<$) :: a -> SizedList w b -> SizedList w a #

Foldable (SizedList w) Source # 

Methods

fold :: Monoid m => SizedList w m -> m #

foldMap :: Monoid m => (a -> m) -> SizedList w a -> m #

foldr :: (a -> b -> b) -> b -> SizedList w a -> b #

foldr' :: (a -> b -> b) -> b -> SizedList w a -> b #

foldl :: (b -> a -> b) -> b -> SizedList w a -> b #

foldl' :: (b -> a -> b) -> b -> SizedList w a -> b #

foldr1 :: (a -> a -> a) -> SizedList w a -> a #

foldl1 :: (a -> a -> a) -> SizedList w a -> a #

toList :: SizedList w a -> [a] #

null :: SizedList w a -> Bool #

length :: SizedList w a -> Int #

elem :: Eq a => a -> SizedList w a -> Bool #

maximum :: Ord a => SizedList w a -> a #

minimum :: Ord a => SizedList w a -> a #

sum :: Num a => SizedList w a -> a #

product :: Num a => SizedList w a -> a #

Traversable (SizedList w) Source # 

Methods

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

sequenceA :: Applicative f => SizedList w (f a) -> f (SizedList w a) #

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

sequence :: Monad m => SizedList w (m a) -> m (SizedList w a) #

Eq a => Eq (SizedList w a) Source # 

Methods

(==) :: SizedList w a -> SizedList w a -> Bool #

(/=) :: SizedList w a -> SizedList w a -> Bool #

Show a => Show (SizedList w a) Source # 

Methods

showsPrec :: Int -> SizedList w a -> ShowS #

show :: SizedList w a -> String #

showList :: [SizedList w a] -> ShowS #

(Binary w, Integral w, Binary a) => Binary (SizedList w a) Source # 

Methods

put :: SizedList w a -> Put #

get :: Get (SizedList w a) #

putList :: [SizedList w a] -> Put #

listSize :: Num w => SizedList w a -> w Source #

Get the size of the sized list.

byteStringSize :: Num w => SizedByteString w -> w Source #

Get the size of a SizedByteString

Specific sizes

type SizedList16 = SizedList Word16 Source #

A sized list using a 16 bit word as length

type SizedByteString32 = SizedByteString Word32 Source #

A sized bytestring using a 32 bit word as length

type SizedByteString16 = SizedByteString Word16 Source #

A sized bytestring using a 16 bit word as length

Bit Set

A bit set is a set where each element is represented a bit in a word. This section also defines the Enumish type class. It is different than a Enum in that the integers they represent does not have to be subsequent.

newtype BitSet w a Source #

A bit set of size w

Constructors

BitSet 

Fields

Instances

Eq a => Eq (BitSet w a) Source # 

Methods

(==) :: BitSet w a -> BitSet w a -> Bool #

(/=) :: BitSet w a -> BitSet w a -> Bool #

Ord a => Ord (BitSet w a) Source # 

Methods

compare :: BitSet w a -> BitSet w a -> Ordering #

(<) :: BitSet w a -> BitSet w a -> Bool #

(<=) :: BitSet w a -> BitSet w a -> Bool #

(>) :: BitSet w a -> BitSet w a -> Bool #

(>=) :: BitSet w a -> BitSet w a -> Bool #

max :: BitSet w a -> BitSet w a -> BitSet w a #

min :: BitSet w a -> BitSet w a -> BitSet w a #

Show a => Show (BitSet w a) Source # 

Methods

showsPrec :: Int -> BitSet w a -> ShowS #

show :: BitSet w a -> String #

showList :: [BitSet w a] -> ShowS #

(Bits w, Binary w, Enumish a) => Binary (BitSet w a) Source # 

Methods

put :: BitSet w a -> Put #

get :: Get (BitSet w a) #

putList :: [BitSet w a] -> Put #

class (Eq a, Ord a) => Enumish a where Source #

An Enumish value, all maps to a number, but not all integers maps to a enumsish value. There is no guarantee that the integers will be subsequent.

Minimal complete definition

inOrder

Methods

inOrder :: [(Int, a)] Source #

The only needed implementation is a list of integer-enum pairs in ascending order, corresponding to their integer value.

fromEnumish :: a -> Int Source #

toEnumish :: Int -> Maybe a Source #

Specific sizes

type BitSet16 = BitSet Word16 Source #

A BitSet using a 16 bit word

General Utilities

 

trd :: (a, b, c) -> c Source #

Takes the third element of a triple.