named-binary-tag-0.1.0.0: NBT (named binary tag) serialization and deserialization.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Nbt

Synopsis

Documentation

data Type Source #

An NBT tag type, in order so that toEnum and fromEnum are useful for serialization and deserialization.

Constructors

EndType

0x00 NUL. Denotes the end of a file.

ByteType

0x01 SOH. Corresponds to Byte.

ShortType

0x02 STX. Corresponds to Short.

IntType

0x03 ETX. Corresponds to Int.

LongType

0x04 EOT. Corresponds to Long.

FloatType

0x05 ENQ. Corresponds to Float.

DoubleType

0x06 ACK. Corresponds to Double.

ByteArrayType

0x07 BEL. Corresponds to ByteArray.

StringType

0x08 BS. Corresponds to String.

ListType

0x09 HT. Corresponds to List.

CompoundType

0x0a LF. Corresponds to Compound.

IntArrayType

0x0b VT. Corresponds to IntArray.

LongArrayType

0x0c FF. Corresponds to LongArray.

Instances

Instances details
Enum Type Source # 
Instance details

Defined in Data.Nbt

Methods

succ :: Type -> Type #

pred :: Type -> Type #

toEnum :: Int -> Type #

fromEnum :: Type -> Int #

enumFrom :: Type -> [Type] #

enumFromThen :: Type -> Type -> [Type] #

enumFromTo :: Type -> Type -> [Type] #

enumFromThenTo :: Type -> Type -> Type -> [Type] #

Show Type Source # 
Instance details

Defined in Data.Nbt

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Serialize Type Source # 
Instance details

Defined in Data.Nbt

Methods

put :: Putter Type #

get :: Get Type #

Eq Type Source # 
Instance details

Defined in Data.Nbt

Methods

(==) :: Type -> Type -> Bool #

(/=) :: Type -> Type -> Bool #

Ord Type Source # 
Instance details

Defined in Data.Nbt

Methods

compare :: Type -> Type -> Ordering #

(<) :: Type -> Type -> Bool #

(<=) :: Type -> Type -> Bool #

(>) :: Type -> Type -> Bool #

(>=) :: Type -> Type -> Bool #

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

data Nbt b Source #

The main NBT type, with support for serialization and deserialization. It couples a Text label with a Tag.

When serialized: 1-byte unsigned Type + 2-byte unsigned integer length + N bytes utf-8 text + Tag

Constructors

Nbt 

Fields

Instances

Instances details
Functor Nbt Source # 
Instance details

Defined in Data.Nbt

Methods

fmap :: (a -> b) -> Nbt a -> Nbt b #

(<$) :: a -> Nbt b -> Nbt a #

Show b => Show (Nbt b) Source # 
Instance details

Defined in Data.Nbt

Methods

showsPrec :: Int -> Nbt b -> ShowS #

show :: Nbt b -> String #

showList :: [Nbt b] -> ShowS #

Serialize (Nbt (Map Text Int)) Source # 
Instance details

Defined in Data.Nbt

Methods

put :: Putter (Nbt (Map Text Int)) #

get :: Get (Nbt (Map Text Int)) #

Serialize (Nbt ()) Source # 
Instance details

Defined in Data.Nbt

Methods

put :: Putter (Nbt ()) #

get :: Get (Nbt ()) #

Eq b => Eq (Nbt b) Source # 
Instance details

Defined in Data.Nbt

Methods

(==) :: Nbt b -> Nbt b -> Bool #

(/=) :: Nbt b -> Nbt b -> Bool #

Ord b => Ord (Nbt b) Source # 
Instance details

Defined in Data.Nbt

Methods

compare :: Nbt b -> Nbt b -> Ordering #

(<) :: Nbt b -> Nbt b -> Bool #

(<=) :: Nbt b -> Nbt b -> Bool #

(>) :: Nbt b -> Nbt b -> Bool #

(>=) :: Nbt b -> Nbt b -> Bool #

max :: Nbt b -> Nbt b -> Nbt b #

min :: Nbt b -> Nbt b -> Nbt b #

type Nbt' = Nbt () Source #

The "simple" form of Nbt, which has no label map on Compounds.

type MapNbt = Nbt (Map Text Int) Source #

A version of Nbt which has a map from labels to element indices for fast lookup.

data Tag b Source #

An NBT tag, responsible for storing the actual data.

Constructors

Byte Int8

1-byte signed integer

Short Int16

2-byte signed integer

Int Int32

4-byte signed integer

Long Int64

8-byte signed integer

Float Float

4-byte float

Double Double

8-byte double

ByteArray (Vector Int8)

4-byte signed integer length + N 1-byte signed integers

String Text

2-byte unsigned integer length + N bytes utf-8 text

List (Vector (Tag b))

1-byte unsigned Type + 4-byte signed integer length + N homogenous tags

Compound (Cmpnd b)

N heterogenous NBT elements punctuated by an EndType

IntArray (Vector Int32)

4-byte signed integer length + N 4-byte signed integers

LongArray (Vector Int64)

4-byte signed integer length + N 8-byte signed integers

Instances

Instances details
Functor Tag Source # 
Instance details

Defined in Data.Nbt

Methods

fmap :: (a -> b) -> Tag a -> Tag b #

(<$) :: a -> Tag b -> Tag a #

Show b => Show (Tag b) Source # 
Instance details

Defined in Data.Nbt

Methods

showsPrec :: Int -> Tag b -> ShowS #

show :: Tag b -> String #

showList :: [Tag b] -> ShowS #

Eq b => Eq (Tag b) Source # 
Instance details

Defined in Data.Nbt

Methods

(==) :: Tag b -> Tag b -> Bool #

(/=) :: Tag b -> Tag b -> Bool #

Ord b => Ord (Tag b) Source # 
Instance details

Defined in Data.Nbt

Methods

compare :: Tag b -> Tag b -> Ordering #

(<) :: Tag b -> Tag b -> Bool #

(<=) :: Tag b -> Tag b -> Bool #

(>) :: Tag b -> Tag b -> Bool #

(>=) :: Tag b -> Tag b -> Bool #

max :: Tag b -> Tag b -> Tag b #

min :: Tag b -> Tag b -> Tag b #

type Tag' = Tag () Source #

The "simple" form of Tag, which has no label map on Compounds.

type MapTag = Tag (Map Text Int) Source #

A version of Tag which has a map from labels to element indices for fast lookup.

data Cmpnd b Source #

The payload of the Compound constructor.

Constructors

Cmpnd b (Vector (Nbt b)) 

Instances

Instances details
Functor Cmpnd Source # 
Instance details

Defined in Data.Nbt

Methods

fmap :: (a -> b) -> Cmpnd a -> Cmpnd b #

(<$) :: a -> Cmpnd b -> Cmpnd a #

Show b => Show (Cmpnd b) Source # 
Instance details

Defined in Data.Nbt

Methods

showsPrec :: Int -> Cmpnd b -> ShowS #

show :: Cmpnd b -> String #

showList :: [Cmpnd b] -> ShowS #

Eq b => Eq (Cmpnd b) Source # 
Instance details

Defined in Data.Nbt

Methods

(==) :: Cmpnd b -> Cmpnd b -> Bool #

(/=) :: Cmpnd b -> Cmpnd b -> Bool #

Ord b => Ord (Cmpnd b) Source # 
Instance details

Defined in Data.Nbt

Methods

compare :: Cmpnd b -> Cmpnd b -> Ordering #

(<) :: Cmpnd b -> Cmpnd b -> Bool #

(<=) :: Cmpnd b -> Cmpnd b -> Bool #

(>) :: Cmpnd b -> Cmpnd b -> Bool #

(>=) :: Cmpnd b -> Cmpnd b -> Bool #

max :: Cmpnd b -> Cmpnd b -> Cmpnd b #

min :: Cmpnd b -> Cmpnd b -> Cmpnd b #

type Cmpnd' = Cmpnd () Source #

The "simple" form of Cmpnd, which has no label map.

type MapCmpnd = Cmpnd (Map Text Int) Source #

A version of Cmpnd which has a map from labels to element indices for fast lookup.

pattern Compound' :: Vector Nbt' -> Tag' Source #

A pattern synonym for "Compound (Cmpnd () v)".

lookupNbt :: Text -> MapCmpnd -> Maybe MapNbt Source #

Use a MapCmpnd to quickly look up a MapNbt by label.

getNbt :: Text -> MapCmpnd -> MapNbt Source #

Use a MapCmpnd to quickly get a MapNbt by label.

lookupTag :: Text -> MapCmpnd -> Maybe MapTag Source #

Runs lookupNbt, then retrieves the tag.

getTag :: Text -> MapCmpnd -> MapTag Source #

Runs getNbt, then retrieves the tag.

typeOf :: Tag b -> Type Source #

Get the type of an NBT tag.

readUncompressed :: Serialize (Nbt b) => FilePath -> IO (Either String (Nbt b)) Source #

Read an uncompressed NBT file. Exceptions are thrown as usual if the internal call to readFile fails, and the Either message is that returned by decode.

writeUncompressed :: Serialize (Nbt b) => FilePath -> Nbt b -> IO () Source #

Write an uncompressed NBT file.

readCompressed :: Serialize (Nbt b) => FilePath -> IO (Either String (Nbt b)) Source #

Read a GZip-compressed NBT file. Exceptions are thrown as usual if the internal call to readFile fails, and the Either message is that returned by decode.

writeCompressed :: Serialize (Nbt b) => FilePath -> Nbt b -> IO () Source #

Write a GZip-compressed NBT file.