mcpi-0.0.0.2: Connect to MineCraft running on a Raspberry PI.

PortabilityHaskell 98
Stabilityexperimental
MaintainerDouglas Burke
Safe HaskellNone

Network.MineCraft.Pi.Client

Contents

Description

The main interface for connecting to the Raspberry-PI version of MineCraft. The Network.MineCraft.Pi.Client.Internal module provides lower-level access in case this module in insufficient.

There are two types of calls to MineCraft: "command" and "query". Commands change the state of the server and do not return anything, queries return information from the server, and presumably does not change the server state. This terminology may change. At present there is no check that the call succeeded.

Example:

In this example we move the player 10 tiles in the X direction, as long as the tile is empty (there is no check that there is anything to stand on).

 {-# LANGUAGE RecordWildCards #-}

 module Main where

 import Control.Monad (when)

 import Data.MineCraft.Pi.Block 
 import Data.MineCraft.Pi.Player
 import Data.MineCraft.Pi.Other
 import Data.MineCraft.Pi.Types

 import Network.MineCraft.Pi.Client

 -- | Move the player by 10 tiles in the X direction,
 --   if it is not filled.
 movePlayer :: MCPI ()
 movePlayer = do
     Pos {..} <- getPlayerTile
     let newPos = Pos (_x+10) _y _z
     bType <- getBlock newPos
     when (bType == air) $ do
       setPlayerTile newPos
       chatPost "*jump*"

 main :: IO ()
 main = runMCPI movePlayer

Synopsis

Documentation

type MCPI = ReaderT ConnInfo IOSource

Represent a program that communicates with a MineCraft PI server.

runMCPI :: MCPI a -> IO aSource

Run a Raspberry-PI program.

An exception is raised if the server is not running, or can not be contacted.

Conversion routines

I am not sure the use of the FromMineCraft and ToMineCraft type classes is justified, given that the API has a very limited set of types.

class FromMineCraft a whereSource

Convert the return value from MineCraft into a Haskell type.

Methods

fromMC :: String -> aSource

class ToMineCraft a whereSource

Convert a value into a form that can be sent to MineCraft.

Methods

toMC :: a -> StringSource

Utility routine

eRead :: Read a => String -> aSource

Convert a value, but error out if it can not be converted.