mmm-0.1.0.0: Minecraft 1.21.4 implementation in Haskell
Copyright(c) axionbuster 2025
LicenseBSD-3-Clause
Safe HaskellNone
LanguageGHC2021

M.NBT

Description

Provides types and functions for working with Minecraft's NBT format, which is used for storing structured binary data.

Synopsis

Documentation

data Ty Source #

NBT tag types

Constructors

TEnd

special type for the end of a compound tag

TByte 
TShort 
TInt 
TLong 
TFloat 
TDouble 
TByteArray 
TString 
TList 
TCompound 
TIntArray 
TLongArray 

Instances

Instances details
Data Ty Source # 
Instance details

Defined in M.NBT.Internal.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ty -> c Ty #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ty #

toConstr :: Ty -> Constr #

dataTypeOf :: Ty -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Ty) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ty) #

gmapT :: (forall b. Data b => b -> b) -> Ty -> Ty #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ty -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ty -> r #

gmapQ :: (forall d. Data d => d -> u) -> Ty -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ty -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ty -> m Ty #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ty -> m Ty #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ty -> m Ty #

Bounded Ty Source # 
Instance details

Defined in M.NBT.Internal.Types

Methods

minBound :: Ty #

maxBound :: Ty #

Enum Ty Source # 
Instance details

Defined in M.NBT.Internal.Types

Methods

succ :: Ty -> Ty #

pred :: Ty -> Ty #

toEnum :: Int -> Ty #

fromEnum :: Ty -> Int #

enumFrom :: Ty -> [Ty] #

enumFromThen :: Ty -> Ty -> [Ty] #

enumFromTo :: Ty -> Ty -> [Ty] #

enumFromThenTo :: Ty -> Ty -> Ty -> [Ty] #

Generic Ty Source # 
Instance details

Defined in M.NBT.Internal.Types

Associated Types

type Rep Ty 
Instance details

Defined in M.NBT.Internal.Types

type Rep Ty = D1 ('MetaData "Ty" "M.NBT.Internal.Types" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'False) (((C1 ('MetaCons "TEnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TByte" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TShort" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "TInt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TLong" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TFloat" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "TDouble" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TByteArray" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TString" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TList" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TCompound" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TIntArray" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TLongArray" 'PrefixI 'False) (U1 :: Type -> Type)))))

Methods

from :: Ty -> Rep Ty x #

to :: Rep Ty x -> Ty #

Read Ty Source # 
Instance details

Defined in M.NBT.Internal.Types

Show Ty Source # 
Instance details

Defined in M.NBT.Internal.Types

Methods

showsPrec :: Int -> Ty -> ShowS #

show :: Ty -> String #

showList :: [Ty] -> ShowS #

NFData Ty Source # 
Instance details

Defined in M.NBT.Internal.Types

Methods

rnf :: Ty -> () #

Eq Ty Source # 
Instance details

Defined in M.NBT.Internal.Types

Methods

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

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

Ord Ty Source # 
Instance details

Defined in M.NBT.Internal.Types

Methods

compare :: Ty -> Ty -> Ordering #

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

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

(>) :: Ty -> Ty -> Bool #

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

max :: Ty -> Ty -> Ty #

min :: Ty -> Ty -> Ty #

Hashable Ty Source # 
Instance details

Defined in M.NBT.Internal.Types

Methods

hashWithSalt :: Int -> Ty -> Int

hash :: Ty -> Int

Pack Ty Source # 
Instance details

Defined in M.NBT.Internal.Types

Methods

pack :: Ty -> Builder Source #

Unpack Ty Source # 
Instance details

Defined in M.NBT.Internal.Types

Methods

unpack :: forall (st :: ZeroBitType) r. Parser st r Ty Source #

Lift Ty Source # 
Instance details

Defined in M.NBT.Internal.Types

Methods

lift :: Quote m => Ty -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Ty -> Code m Ty #

type Rep Ty Source # 
Instance details

Defined in M.NBT.Internal.Types

type Rep Ty = D1 ('MetaData "Ty" "M.NBT.Internal.Types" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'False) (((C1 ('MetaCons "TEnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TByte" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TShort" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "TInt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TLong" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TFloat" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "TDouble" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TByteArray" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TString" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TList" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TCompound" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TIntArray" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TLongArray" 'PrefixI 'False) (U1 :: Type -> Type)))))

data Tg where Source #

NBT tag

Constructors

End :: Tg

used for internal purposes only

Byte :: Int8 -> Tg 
Short :: Int16 -> Tg 
Int :: Int32 -> Tg 
Long :: Int64 -> Tg 
Float :: Float -> Tg 
Double :: Double -> Tg 
ByteArray :: ByteString -> Tg 
String :: Text -> Tg 
List :: Ty -> Vector Tg -> Tg

a homogeneous list of tags

Compound :: HashMap Text Tg -> Tg 
IntArray :: Vector Int32 -> Tg 
LongArray :: Vector Int64 -> Tg 

Instances

Instances details
Data Tg Source # 
Instance details

Defined in M.NBT.Internal.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tg -> c Tg #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Tg #

toConstr :: Tg -> Constr #

dataTypeOf :: Tg -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Tg) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tg) #

gmapT :: (forall b. Data b => b -> b) -> Tg -> Tg #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tg -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tg -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tg -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tg -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tg -> m Tg #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tg -> m Tg #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tg -> m Tg #

IsString Tg Source # 
Instance details

Defined in M.NBT.Internal.Types

Methods

fromString :: String -> Tg #

Generic Tg Source # 
Instance details

Defined in M.NBT.Internal.Types

Associated Types

type Rep Tg 
Instance details

Defined in M.NBT.Internal.Types

type Rep Tg = D1 ('MetaData "Tg" "M.NBT.Internal.Types" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'False) (((C1 ('MetaCons "End" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Byte" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int8)) :+: C1 ('MetaCons "Short" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int16)))) :+: (C1 ('MetaCons "Int" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32)) :+: (C1 ('MetaCons "Long" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)) :+: C1 ('MetaCons "Float" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float))))) :+: ((C1 ('MetaCons "Double" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :+: (C1 ('MetaCons "ByteArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)) :+: C1 ('MetaCons "String" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) :+: ((C1 ('MetaCons "List" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ty) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Tg))) :+: C1 ('MetaCons "Compound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap Text Tg)))) :+: (C1 ('MetaCons "IntArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Int32))) :+: C1 ('MetaCons "LongArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Int64)))))))

Methods

from :: Tg -> Rep Tg x #

to :: Rep Tg x -> Tg #

Read Tg Source # 
Instance details

Defined in M.NBT.Internal.Types

Show Tg Source # 
Instance details

Defined in M.NBT.Internal.Types

Methods

showsPrec :: Int -> Tg -> ShowS #

show :: Tg -> String #

showList :: [Tg] -> ShowS #

NFData Tg Source # 
Instance details

Defined in M.NBT.Internal.Types

Methods

rnf :: Tg -> () #

Eq Tg Source # 
Instance details

Defined in M.NBT.Internal.Types

Methods

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

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

Ord Tg Source # 
Instance details

Defined in M.NBT.Internal.Types

Methods

compare :: Tg -> Tg -> Ordering #

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

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

(>) :: Tg -> Tg -> Bool #

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

max :: Tg -> Tg -> Tg #

min :: Tg -> Tg -> Tg #

Pack Tg Source # 
Instance details

Defined in M.NBT.Internal.P

Methods

pack :: Tg -> Builder Source #

Unpack Tg Source # 
Instance details

Defined in M.NBT.Internal.P

Methods

unpack :: forall (st :: ZeroBitType) r. Parser st r Tg Source #

type Rep Tg Source # 
Instance details

Defined in M.NBT.Internal.Types

type Rep Tg = D1 ('MetaData "Tg" "M.NBT.Internal.Types" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'False) (((C1 ('MetaCons "End" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Byte" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int8)) :+: C1 ('MetaCons "Short" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int16)))) :+: (C1 ('MetaCons "Int" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32)) :+: (C1 ('MetaCons "Long" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)) :+: C1 ('MetaCons "Float" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float))))) :+: ((C1 ('MetaCons "Double" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :+: (C1 ('MetaCons "ByteArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)) :+: C1 ('MetaCons "String" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) :+: ((C1 ('MetaCons "List" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ty) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Tg))) :+: C1 ('MetaCons "Compound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap Text Tg)))) :+: (C1 ('MetaCons "IntArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Int32))) :+: C1 ('MetaCons "LongArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Int64)))))))

data NamedPair Source #

named pair of a Text and a Tg

Constructors

NamedPair !Text !Tg 

Instances

Instances details
Data NamedPair Source # 
Instance details

Defined in M.NBT.Internal.P

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NamedPair -> c NamedPair #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NamedPair #

toConstr :: NamedPair -> Constr #

dataTypeOf :: NamedPair -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NamedPair) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NamedPair) #

gmapT :: (forall b. Data b => b -> b) -> NamedPair -> NamedPair #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NamedPair -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NamedPair -> r #

gmapQ :: (forall d. Data d => d -> u) -> NamedPair -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NamedPair -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NamedPair -> m NamedPair #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NamedPair -> m NamedPair #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NamedPair -> m NamedPair #

Generic NamedPair Source # 
Instance details

Defined in M.NBT.Internal.P

Associated Types

type Rep NamedPair 
Instance details

Defined in M.NBT.Internal.P

type Rep NamedPair = D1 ('MetaData "NamedPair" "M.NBT.Internal.P" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'False) (C1 ('MetaCons "NamedPair" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Tg)))
Read NamedPair Source # 
Instance details

Defined in M.NBT.Internal.P

Show NamedPair Source # 
Instance details

Defined in M.NBT.Internal.P

NFData NamedPair Source # 
Instance details

Defined in M.NBT.Internal.P

Methods

rnf :: NamedPair -> () #

Eq NamedPair Source # 
Instance details

Defined in M.NBT.Internal.P

Ord NamedPair Source # 
Instance details

Defined in M.NBT.Internal.P

Pack NamedPair Source # 
Instance details

Defined in M.NBT.Internal.P

Unpack NamedPair Source # 
Instance details

Defined in M.NBT.Internal.P

Methods

unpack :: forall (st :: ZeroBitType) r. Parser st r NamedPair Source #

type Rep NamedPair Source # 
Instance details

Defined in M.NBT.Internal.P

type Rep NamedPair = D1 ('MetaData "NamedPair" "M.NBT.Internal.P" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'False) (C1 ('MetaCons "NamedPair" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Tg)))