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

M.Reg

Description

A generic registry that maintains a three-way mapping between:

  • Numeric codes (Int)
  • Text identifiers (Text)
  • Objects (generic type a)

This is useful for Minecraft's registry system where objects like blocks and items are identified both by numeric IDs and string identifiers.

Usage

Create a registry:

-- imagine tr :: TypeRep exists.
let items = [("minecraft:stone", tr Stone), ("minecraft:dirt", tr Dirt)]
case mkreg0 items of
  Just reg -> -- Use registry
  Nothing -> -- Handle duplicate keys

Look up objects:

-- By numeric code
case lkobjbycode 0 reg of
  Just obj -> -- Found
  Nothing -> -- Not found

-- By string identifier
case lkcodebyid "minecraft:stone" reg of
  Just code -> -- Found
  Nothing -> -- Not found
Synopsis

Documentation

data Reg a Source #

A "registry" type maintaining a triple link between codes, identifiers and objects.

The registry is immutable after creation and provides efficient lookups in both directions:

  • From numeric code to object (using IntMap)
  • From text identifier to numeric code (using HashMap)

Implementation Notes

  • code -> object mapping uses lazy IntMap since object types may be large
  • identifier -> code mapping uses strict HashMap for text lookups
  • Registry cannot be modified after creation (updates planned for future)

Instances

Instances details
Functor Reg Source # 
Instance details

Defined in M.Reg

Methods

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

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

Data a => Data (Reg a) Source # 
Instance details

Defined in M.Reg

Methods

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

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

toConstr :: Reg a -> Constr #

dataTypeOf :: Reg a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (Reg a) Source # 
Instance details

Defined in M.Reg

Associated Types

type Rep (Reg a) 
Instance details

Defined in M.Reg

type Rep (Reg a) = D1 ('MetaData "Reg" "M.Reg" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'False) (C1 ('MetaCons "Reg" 'PrefixI 'True) (S1 ('MetaSel ('Just "regca") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IntMap a)) :*: S1 ('MetaSel ('Just "regic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap Text Int))))

Methods

from :: Reg a -> Rep (Reg a) x #

to :: Rep (Reg a) x -> Reg a #

Show a => Show (Reg a) Source #
[(0, blah:bloh/blee; 42), ..., (<code>, <id>; <object>)]
Instance details

Defined in M.Reg

Methods

showsPrec :: Int -> Reg a -> ShowS #

show :: Reg a -> String #

showList :: [Reg a] -> ShowS #

Eq a => Eq (Reg a) Source # 
Instance details

Defined in M.Reg

Methods

(==) :: Reg a -> Reg a -> Bool #

(/=) :: Reg a -> Reg a -> Bool #

Ord a => Ord (Reg a) Source # 
Instance details

Defined in M.Reg

Methods

compare :: Reg a -> Reg a -> Ordering #

(<) :: Reg a -> Reg a -> Bool #

(<=) :: Reg a -> Reg a -> Bool #

(>) :: Reg a -> Reg a -> Bool #

(>=) :: Reg a -> Reg a -> Bool #

max :: Reg a -> Reg a -> Reg a #

min :: Reg a -> Reg a -> Reg a #

type Rep (Reg a) Source # 
Instance details

Defined in M.Reg

type Rep (Reg a) = D1 ('MetaData "Reg" "M.Reg" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'False) (C1 ('MetaCons "Reg" 'PrefixI 'True) (S1 ('MetaSel ('Just "regca") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IntMap a)) :*: S1 ('MetaSel ('Just "regic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap Text Int))))

mkreg0 :: [(Text, a)] -> Maybe (Reg a) Source #

Create a simple registry from identifier-object pairs. Numeric codes are assigned sequentially starting from 0.

Returns Nothing if there are duplicate identifiers.

Usage

let reg = mkreg0 [("minecraft:stone", Stone), ("minecraft:dirt", Dirt)]

mkreg1 :: (b -> a) -> [(Text, b)] -> Maybe (Reg a) Source #

Create a registry with a transformation function applied to values.

Like mkreg0 but applies a function to transform the values before storing. Returns Nothing if there are duplicate identifiers.

Usage

let reg = mkreg1 Block [("stone", StoneData), ("dirt", DirtData)]
-- Creates registry with Block StoneData, Block DirtData

lkcodebyid :: Text -> Reg a -> Maybe Int Source #

Look up a numeric code by its string identifier.

Usage

case lkcodebyid "minecraft:stone" registry of
  Just code -> -- Found code for identifier
  Nothing -> -- No such identifier

lkobjbycode :: Int -> Reg a -> Maybe a Source #

Look up an object by its numeric code.

Usage

case lkobjbycode 0 registry of
  Just obj -> -- Found object at code 0
  Nothing -> -- No object at code 0

lkobjbyid :: Text -> Reg a -> Maybe a Source #

Look up an object by its string identifier.

Combines lkcodebyid and lkobjbycode for direct identifier to object lookup.

Usage

case lkobjbyid "minecraft:stone" registry of
  Just obj -> -- Found object for identifier
  Nothing -> -- No such identifier