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

M.Crypto

Description

Provides cryptographic functionality required by the Minecraft protocol, including AES encryption/decryption, RSA operations, and server-specific hashing utilities.

Synopsis

AES

data AES (mode :: Mode) Source #

encryption/decryption context for AES (AES-128-CFB8)

Instances

Instances details
Show (AES mode) Source # 
Instance details

Defined in M.Crypto

Methods

showsPrec :: Int -> AES mode -> ShowS #

show :: AES mode -> String #

showList :: [AES mode] -> ShowS #

Eq (AES mode) Source # 
Instance details

Defined in M.Crypto

Methods

(==) :: AES mode -> AES mode -> Bool #

(/=) :: AES mode -> AES mode -> Bool #

data Mode Source #

encryption/decryption mode

Constructors

Encrypt 
Decrypt 

Instances

Instances details
Data Mode Source # 
Instance details

Defined in M.Crypto

Methods

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

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

toConstr :: Mode -> Constr #

dataTypeOf :: Mode -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded Mode Source # 
Instance details

Defined in M.Crypto

Enum Mode Source # 
Instance details

Defined in M.Crypto

Methods

succ :: Mode -> Mode #

pred :: Mode -> Mode #

toEnum :: Int -> Mode #

fromEnum :: Mode -> Int #

enumFrom :: Mode -> [Mode] #

enumFromThen :: Mode -> Mode -> [Mode] #

enumFromTo :: Mode -> Mode -> [Mode] #

enumFromThenTo :: Mode -> Mode -> Mode -> [Mode] #

Generic Mode Source # 
Instance details

Defined in M.Crypto

Associated Types

type Rep Mode 
Instance details

Defined in M.Crypto

type Rep Mode = D1 ('MetaData "Mode" "M.Crypto" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'False) (C1 ('MetaCons "Encrypt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Decrypt" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

Read Mode Source # 
Instance details

Defined in M.Crypto

Show Mode Source # 
Instance details

Defined in M.Crypto

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

Eq Mode Source # 
Instance details

Defined in M.Crypto

Methods

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

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

type Rep Mode Source # 
Instance details

Defined in M.Crypto

type Rep Mode = D1 ('MetaData "Mode" "M.Crypto" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'False) (C1 ('MetaCons "Encrypt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Decrypt" 'PrefixI 'False) (U1 :: Type -> Type))

aesnew :: AESClass mode => ByteString -> IO (AES mode) Source #

create a new AES context

aesupdate :: AESClass mode => AES mode -> ByteString -> IO ByteString Source #

either encrypt or decrypt a message

RSA

data RSA Source #

RSA pkey

Instances

Instances details
Show RSA Source # 
Instance details

Defined in M.Crypto

Methods

showsPrec :: Int -> RSA -> ShowS #

show :: RSA -> String #

showList :: [RSA] -> ShowS #

Eq RSA Source # 
Instance details

Defined in M.Crypto

Methods

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

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

rsanew :: Int -> IO RSA Source #

create a new RSA pkey

rsaup :: RSAClass mode => RSA -> ByteString -> IO ByteString Source #

either encrypt or decrypt a message

rsaspki :: RSA -> IO ByteString Source #

write the SubjectPublicKeyInfo to a ByteString

Hash

hashservnam Source #

Arguments

:: ByteString

server id

-> ByteString

shared secret

-> ByteString

verify token

-> IO ByteString

SHA1 hash (20 bytes)

generate a SHA1 hash of the server name

General

newtype Error Source #

error type

Constructors

Error String 

Instances

Instances details
Data Error Source # 
Instance details

Defined in M.Crypto

Methods

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

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

toConstr :: Error -> Constr #

dataTypeOf :: Error -> DataType #

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

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

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

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

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

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

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

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

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

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

Exception Error Source # 
Instance details

Defined in M.Crypto

Generic Error Source # 
Instance details

Defined in M.Crypto

Associated Types

type Rep Error 
Instance details

Defined in M.Crypto

type Rep Error = D1 ('MetaData "Error" "M.Crypto" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'True) (C1 ('MetaCons "Error" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

Methods

from :: Error -> Rep Error x #

to :: Rep Error x -> Error #

Show Error Source # 
Instance details

Defined in M.Crypto

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

Eq Error Source # 
Instance details

Defined in M.Crypto

Methods

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

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

type Rep Error Source # 
Instance details

Defined in M.Crypto

type Rep Error = D1 ('MetaData "Error" "M.Crypto" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'True) (C1 ('MetaCons "Error" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

class AESClass (mode :: Mode) Source #

Minimal complete definition

aesnew_, aesupdate_

Instances

Instances details
AESClass 'Decrypt Source # 
Instance details

Defined in M.Crypto

AESClass 'Encrypt Source # 
Instance details

Defined in M.Crypto

class RSAClass (mode :: Mode) Source #

Minimal complete definition

rsaup_

Instances

Instances details
RSAClass 'Decrypt Source # 
Instance details

Defined in M.Crypto

Methods

rsaup_ :: Ptr EVP_PKEY -> Ptr Word8 -> CSize -> Ptr MMMRSAOUT -> IO CInt

rsaup :: RSA -> ByteString -> IO ByteString Source #

RSAClass 'Encrypt Source # 
Instance details

Defined in M.Crypto

Methods

rsaup_ :: Ptr EVP_PKEY -> Ptr Word8 -> CSize -> Ptr MMMRSAOUT -> IO CInt

rsaup :: RSA -> ByteString -> IO ByteString Source #

Re-exports

data ByteString #

A space-efficient representation of a Word8 vector, supporting many efficient operations.

A ByteString contains 8-bit bytes, or by using the operations from Data.ByteString.Char8 it can be interpreted as containing 8-bit characters.

Instances

Instances details
Data ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Methods

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

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

toConstr :: ByteString -> Constr #

dataTypeOf :: ByteString -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString ByteString

Beware: fromString truncates multi-byte characters to octets. e.g. "枯朶に烏のとまりけり秋の暮" becomes �6k�nh~�Q��n�

Instance details

Defined in Data.ByteString.Internal.Type

Monoid ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Semigroup ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

IsList ByteString

Since: bytestring-0.10.12.0

Instance details

Defined in Data.ByteString.Internal.Type

Associated Types

type Item ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Read ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Show ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

NFData ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Methods

rnf :: ByteString -> () #

Eq ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Ord ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Hashable ByteString 
Instance details

Defined in Data.Hashable.Class

Ixed ByteString 
Instance details

Defined in Control.Lens.At

Methods

ix :: Index ByteString -> Traversal' ByteString (IxValue ByteString)

AsEmpty ByteString 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' ByteString ()

Reversing ByteString 
Instance details

Defined in Control.Lens.Internal.Iso

Prefixed ByteString 
Instance details

Defined in Control.Lens.Prism

Suffixed ByteString 
Instance details

Defined in Control.Lens.Prism

IsByteString ByteString 
Instance details

Defined in Data.ByteString.Lens

Methods

packedBytes :: Iso' [Word8] ByteString

packedChars :: Iso' String ByteString

bytes :: IndexedTraversal' Int ByteString Word8

chars :: IndexedTraversal' Int ByteString Char

Stream ByteString 
Instance details

Defined in Text.Megaparsec.Stream

Associated Types

type Token ByteString 
Instance details

Defined in Text.Megaparsec.Stream

type Token ByteString = Token (ShareInput ByteString)
type Tokens ByteString 
Instance details

Defined in Text.Megaparsec.Stream

type Tokens ByteString = Tokens (ShareInput ByteString)
TraversableStream ByteString 
Instance details

Defined in Text.Megaparsec.Stream

Methods

reachOffset :: Int -> PosState ByteString -> (Maybe String, PosState ByteString)

reachOffsetNoLine :: Int -> PosState ByteString -> PosState ByteString

VisualStream ByteString 
Instance details

Defined in Text.Megaparsec.Stream

Pack ByteString Source # 
Instance details

Defined in M.Pack.Internal.Etc

Unpack ByteString Source # 
Instance details

Defined in M.Pack.Internal.Etc

Methods

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

Lift ByteString

Since: bytestring-0.11.2.0

Instance details

Defined in Data.ByteString.Internal.Type

Methods

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

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

Cons ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

Snoc ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

(a ~ Word8, b ~ Word8) => Each ByteString ByteString a b 
Instance details

Defined in Control.Lens.Each

Methods

each :: Traversal ByteString ByteString a b

BufferedIO (InputStream ByteString) 
Instance details

Defined in System.IO.Streams.Internal

BufferedIO (OutputStream ByteString) 
Instance details

Defined in System.IO.Streams.Internal

BufferedIO (StreamPair ByteString) 
Instance details

Defined in System.IO.Streams.Internal

IODevice (InputStream ByteString) 
Instance details

Defined in System.IO.Streams.Internal

Methods

ready :: InputStream ByteString -> Bool -> Int -> IO Bool #

close :: InputStream ByteString -> IO () #

isTerminal :: InputStream ByteString -> IO Bool #

isSeekable :: InputStream ByteString -> IO Bool #

seek :: InputStream ByteString -> SeekMode -> Integer -> IO Integer #

tell :: InputStream ByteString -> IO Integer #

getSize :: InputStream ByteString -> IO Integer #

setSize :: InputStream ByteString -> Integer -> IO () #

setEcho :: InputStream ByteString -> Bool -> IO () #

getEcho :: InputStream ByteString -> IO Bool #

setRaw :: InputStream ByteString -> Bool -> IO () #

devType :: InputStream ByteString -> IO IODeviceType #

dup :: InputStream ByteString -> IO (InputStream ByteString) #

dup2 :: InputStream ByteString -> InputStream ByteString -> IO (InputStream ByteString) #

IODevice (OutputStream ByteString) 
Instance details

Defined in System.IO.Streams.Internal

Methods

ready :: OutputStream ByteString -> Bool -> Int -> IO Bool #

close :: OutputStream ByteString -> IO () #

isTerminal :: OutputStream ByteString -> IO Bool #

isSeekable :: OutputStream ByteString -> IO Bool #

seek :: OutputStream ByteString -> SeekMode -> Integer -> IO Integer #

tell :: OutputStream ByteString -> IO Integer #

getSize :: OutputStream ByteString -> IO Integer #

setSize :: OutputStream ByteString -> Integer -> IO () #

setEcho :: OutputStream ByteString -> Bool -> IO () #

getEcho :: OutputStream ByteString -> IO Bool #

setRaw :: OutputStream ByteString -> Bool -> IO () #

devType :: OutputStream ByteString -> IO IODeviceType #

dup :: OutputStream ByteString -> IO (OutputStream ByteString) #

dup2 :: OutputStream ByteString -> OutputStream ByteString -> IO (OutputStream ByteString) #

IODevice (StreamPair ByteString) 
Instance details

Defined in System.IO.Streams.Internal

Methods

ready :: StreamPair ByteString -> Bool -> Int -> IO Bool #

close :: StreamPair ByteString -> IO () #

isTerminal :: StreamPair ByteString -> IO Bool #

isSeekable :: StreamPair ByteString -> IO Bool #

seek :: StreamPair ByteString -> SeekMode -> Integer -> IO Integer #

tell :: StreamPair ByteString -> IO Integer #

getSize :: StreamPair ByteString -> IO Integer #

setSize :: StreamPair ByteString -> Integer -> IO () #

setEcho :: StreamPair ByteString -> Bool -> IO () #

getEcho :: StreamPair ByteString -> IO Bool #

setRaw :: StreamPair ByteString -> Bool -> IO () #

devType :: StreamPair ByteString -> IO IODeviceType #

dup :: StreamPair ByteString -> IO (StreamPair ByteString) #

dup2 :: StreamPair ByteString -> StreamPair ByteString -> IO (StreamPair ByteString) #

RawIO (InputStream ByteString) 
Instance details

Defined in System.IO.Streams.Internal

Methods

read :: InputStream ByteString -> Ptr Word8 -> Word64 -> Int -> IO Int #

readNonBlocking :: InputStream ByteString -> Ptr Word8 -> Word64 -> Int -> IO (Maybe Int) #

write :: InputStream ByteString -> Ptr Word8 -> Word64 -> Int -> IO () #

writeNonBlocking :: InputStream ByteString -> Ptr Word8 -> Word64 -> Int -> IO Int #

RawIO (OutputStream ByteString) 
Instance details

Defined in System.IO.Streams.Internal

Methods

read :: OutputStream ByteString -> Ptr Word8 -> Word64 -> Int -> IO Int #

readNonBlocking :: OutputStream ByteString -> Ptr Word8 -> Word64 -> Int -> IO (Maybe Int) #

write :: OutputStream ByteString -> Ptr Word8 -> Word64 -> Int -> IO () #

writeNonBlocking :: OutputStream ByteString -> Ptr Word8 -> Word64 -> Int -> IO Int #

RawIO (StreamPair ByteString) 
Instance details

Defined in System.IO.Streams.Internal

Methods

read :: StreamPair ByteString -> Ptr Word8 -> Word64 -> Int -> IO Int #

readNonBlocking :: StreamPair ByteString -> Ptr Word8 -> Word64 -> Int -> IO (Maybe Int) #

write :: StreamPair ByteString -> Ptr Word8 -> Word64 -> Int -> IO () #

writeNonBlocking :: StreamPair ByteString -> Ptr Word8 -> Word64 -> Int -> IO Int #

Stream (NoShareInput ByteString) 
Instance details

Defined in Text.Megaparsec.Stream

Associated Types

type Token (NoShareInput ByteString) 
Instance details

Defined in Text.Megaparsec.Stream

type Token (NoShareInput ByteString) = Word8
type Tokens (NoShareInput ByteString) 
Instance details

Defined in Text.Megaparsec.Stream

type Tokens (NoShareInput ByteString) = ByteString

Methods

tokenToChunk :: Proxy (NoShareInput ByteString) -> Token (NoShareInput ByteString) -> Tokens (NoShareInput ByteString)

tokensToChunk :: Proxy (NoShareInput ByteString) -> [Token (NoShareInput ByteString)] -> Tokens (NoShareInput ByteString)

chunkToTokens :: Proxy (NoShareInput ByteString) -> Tokens (NoShareInput ByteString) -> [Token (NoShareInput ByteString)]

chunkLength :: Proxy (NoShareInput ByteString) -> Tokens (NoShareInput ByteString) -> Int

chunkEmpty :: Proxy (NoShareInput ByteString) -> Tokens (NoShareInput ByteString) -> Bool

take1_ :: NoShareInput ByteString -> Maybe (Token (NoShareInput ByteString), NoShareInput ByteString)

takeN_ :: Int -> NoShareInput ByteString -> Maybe (Tokens (NoShareInput ByteString), NoShareInput ByteString)

takeWhile_ :: (Token (NoShareInput ByteString) -> Bool) -> NoShareInput ByteString -> (Tokens (NoShareInput ByteString), NoShareInput ByteString)

Stream (ShareInput ByteString) 
Instance details

Defined in Text.Megaparsec.Stream

Associated Types

type Token (ShareInput ByteString) 
Instance details

Defined in Text.Megaparsec.Stream

type Token (ShareInput ByteString) = Word8
type Tokens (ShareInput ByteString) 
Instance details

Defined in Text.Megaparsec.Stream

type Tokens (ShareInput ByteString) = ByteString

Methods

tokenToChunk :: Proxy (ShareInput ByteString) -> Token (ShareInput ByteString) -> Tokens (ShareInput ByteString)

tokensToChunk :: Proxy (ShareInput ByteString) -> [Token (ShareInput ByteString)] -> Tokens (ShareInput ByteString)

chunkToTokens :: Proxy (ShareInput ByteString) -> Tokens (ShareInput ByteString) -> [Token (ShareInput ByteString)]

chunkLength :: Proxy (ShareInput ByteString) -> Tokens (ShareInput ByteString) -> Int

chunkEmpty :: Proxy (ShareInput ByteString) -> Tokens (ShareInput ByteString) -> Bool

take1_ :: ShareInput ByteString -> Maybe (Token (ShareInput ByteString), ShareInput ByteString)

takeN_ :: Int -> ShareInput ByteString -> Maybe (Tokens (ShareInput ByteString), ShareInput ByteString)

takeWhile_ :: (Token (ShareInput ByteString) -> Bool) -> ShareInput ByteString -> (Tokens (ShareInput ByteString), ShareInput ByteString)

type Item ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

type Index ByteString 
Instance details

Defined in Control.Lens.At

type Index ByteString = Int
type IxValue ByteString 
Instance details

Defined in Control.Lens.At

type IxValue ByteString = Word8
type Token ByteString 
Instance details

Defined in Text.Megaparsec.Stream

type Token ByteString = Token (ShareInput ByteString)
type Tokens ByteString 
Instance details

Defined in Text.Megaparsec.Stream

type Tokens ByteString = Tokens (ShareInput ByteString)
type Token (NoShareInput ByteString) 
Instance details

Defined in Text.Megaparsec.Stream

type Token (NoShareInput ByteString) = Word8
type Token (ShareInput ByteString) 
Instance details

Defined in Text.Megaparsec.Stream

type Token (ShareInput ByteString) = Word8
type Tokens (NoShareInput ByteString) 
Instance details

Defined in Text.Megaparsec.Stream

type Tokens (NoShareInput ByteString) = ByteString
type Tokens (ShareInput ByteString) 
Instance details

Defined in Text.Megaparsec.Stream

type Tokens (ShareInput ByteString) = ByteString