NXT-0.2.3: A Haskell interface to Lego Mindstorms NXT

Safe HaskellNone

Robotics.NXT

Contents

Description

This module defines an interface over Bluetooth to a NXT brick as defined in Lego Mindstorms NXT Bluetooth Developer Kit, Appendix 1 - Communication protocol and Appendix 2 - Direct commands. It also defines some additional functions not available directly otherwise.

Synopsis

Initialization

withNXT :: FilePath -> NXT a -> IO aSource

Function which initializes and terminates Bluetooth connection to the NXT brick (using initialize and terminate) and in-between runs given computation. It terminates Bluetooth connection on an exception, too, rethrowing it afterwards.

defaultDevice :: FilePathSource

Default Bluetooth serial device filename for current operating system. Currently always /dev/rfcomm0.

Motors

setOutputState :: OutputPort -> OutputPower -> [OutputMode] -> RegulationMode -> TurnRatio -> RunState -> TachoLimit -> NXT ()Source

Sets output port (motor) state. This is the main function for controlling a motor.

setOutputStateConfirm :: OutputPort -> OutputPower -> [OutputMode] -> RegulationMode -> TurnRatio -> RunState -> TachoLimit -> NXT ()Source

Same as setOutputState but also request a confirmation. Useful to assure the command was really accepted. In a case of an error it throws a NXTException.

Confirmation requires a change of the direction of NXT Bluetooth communication which takes around 30 ms.

getOutputState :: OutputPort -> NXT OutputStateSource

Gets output port (motor) current state. In additional to values used with setOutputState also TachoCount, BlockTachoCount and RotationCount values are available which tell you current position of a motor.

resetMotorPosition :: OutputPort -> MotorReset -> NXT ()Source

Resets one of three position counters for a given output port.

Sensors

setInputMode :: InputPort -> SensorType -> SensorMode -> NXT ()Source

Sets input port (sensor) type and mode.

setInputModeConfirm :: InputPort -> SensorType -> SensorMode -> NXT ()Source

Same as setInputMode but also request a confirmation. Useful to assure the command was really accepted. In a case of an error it throws a NXTException.

Confirmation requires a change of the direction of NXT Bluetooth communication which takes around 30 ms.

getInputValues :: InputPort -> NXT InputValueSource

Gets input port (sensor) values. This is the main function for reading a sensor.

resetInputScaledValue :: InputPort -> NXT ()Source

Resets input port (sensor) scaled value.

Miscellaneous

getVersion :: NXT VersionSource

Gets firmware and protocol versions of the NXT brick.

getDeviceInfo :: NXT DeviceInfoSource

Gets device (the NXT brick) information: name, Bluetooth 48 bit address in the string format, strength of Bluetooth signal (not implemented in current NXT firmware versions, use bluetoothRSSI or bluetoothLinkQuality as an alternative), free space on flash.

getBatteryLevel :: NXT VoltageSource

Gets current battery level (in volts).

isBatteryRechargeable :: NXT BoolSource

Is battery used in the NXT brick rechargeable?

keepAlive :: NXT ()Source

Sends a keep alive (turned on) packet. It prevents the NXT brick from automatically powering off. Other commands do not prevent that from hapenning so it is useful to send this packet from time to time if you want to prevent powering off.

keepAliveConfirm :: NXT ()Source

Same as keepAlive but also request a confirmation. Useful to assure the command was really accepted. In a case of an error it throws a NXTException.

Confirmation requires a change of the direction of NXT Bluetooth communication which takes around 30 ms.

getSleepTimeout :: NXT DurationSource

Gets current sleep timeout setting (in seconds) after which the NXT brick automatically powers off if not prevented with a keep alive packet (use keepAlive to send one). This setting is cached.

getLastKeepAliveTime :: NXT (Maybe POSIXTime)Source

When was a last keep alive packet send?

stopEverything :: NXT ()Source

Helper function which stops all NXT brick activities: stops motors and disables sensors.

shutdown :: NXT ()Source

Shutdowns (powers off) the NXT brick. You have to manually turn it on again.

Remote Programs

It is possible to remotely run and control (with messages) programs on the NXT brick. Those here are low-level functions but check also high-level Robotics.NXT.Remote and Robotics.NXT.MotorControl modules.

startProgram :: FileName -> NXT ()Source

Starts a given program on the NXT brick.

startProgramConfirm :: FileName -> NXT ()Source

Same as startProgram but also request a confirmation. Useful to assure the command was really accepted, but this does not assure that the program has really started successfully (especially not that it is already running when the confirmation is received). Use ensureStartProgram for that. In a case of an error it throws a NXTException.

Confirmation requires a change of the direction of NXT Bluetooth communication which takes around 30 ms.

stopProgram :: NXT ()Source

Stops a currently running program.

stopProgramConfirm :: NXT ()Source

Same as stopProgram but also request a confirmation. Useful to assure the command was really accepted. In a case of an error it throws a NXTException.

Confirmation requires a change of the direction of NXT Bluetooth communication which takes around 30 ms.

stopProgramExisting :: NXT ()Source

Same as stopProgramConfirm but it also requires that the program was really running. It throws a NXTException otherwise.

ensureStartProgram :: FileName -> NXT ()Source

Helper function which first ensures that no other program is running and then ensures that a given program is really running before it returns.

getCurrentProgramName :: NXT (Maybe String)Source

Gets the name of the currently running program, if any.

Messages

It is possible to control programs on the NXT brick with messages. Those here are low-level functions but check also high-level Robotics.NXT.Remote and Robotics.NXT.MotorControl modules.

messageWrite :: Inbox -> String -> NXT ()Source

Writes a message to the given inbox queue of the running remote program. A message length is limited to 58 characters/bytes. A queue is limited to 5 messages.

messageWriteConfirm :: Inbox -> String -> NXT ()Source

Same as messageWrite but also request a confirmation. Useful to assure the command was really accepted. In a case of an error it throws a NXTException.

Confirmation requires a change of the direction of NXT Bluetooth communication which takes around 30 ms.

messageRead :: RemoteInbox -> RemoveMessage -> NXT StringSource

Reads a message from the currently running program from a given remote inbox queue. A queue is limited to 5 messages. It throws a NXTException if there is no message in a remote inbox queue.

maybeMessageRead :: RemoteInbox -> RemoveMessage -> NXT (Maybe String)Source

Same as messageWrite but returns Nothing if there is no message in a given remote inbox queue.

ensureMessageRead :: RemoteInbox -> RemoveMessage -> NXT StringSource

Same as messageWrite but if there is no message in a given remote inbox queue it retries until there is.

Sounds

playSoundFile :: LoopPlayback -> FileName -> NXT ()Source

Plays a given sound file.

playSoundFileConfirm :: LoopPlayback -> FileName -> NXT ()Source

Same as playSoundFile but also request a confirmation. Useful to assure the command was really accepted. In a case of an error it throws a NXTException.

Confirmation requires a change of the direction of NXT Bluetooth communication which takes around 30 ms.

playTone :: Frequency -> Duration -> NXT ()Source

Plays a tone with a given frequency (in hertz) for a given duration (in seconds).

stopSoundPlayback :: NXT ()Source

Stops current sound file playback.

stopSoundPlaybackConfirm :: NXT ()Source

Same as stopSoundPlayback but also request a confirmation. Useful to assure the command was really accepted. In a case of an error it throws a NXTException.

Confirmation requires a change of the direction of NXT Bluetooth communication which takes around 30 ms.

Low Speed (I2C)

With those low-level functions it is possible to communicate with digital sensors attached to the NXT brick. But check also high-level Robotics.NXT.Sensor.Ultrasonic and Robotics.NXT.Sensor.Compass modules.

lowspeedGetStatus :: InputPort -> NXT IntSource

Gets number of bytes available to read.

lowspeedWrite :: InputPort -> RxDataLength -> TxData -> NXT ()Source

Writes data. At most 16 bytes can be written at a time.

Reply data length must be specified in the write command since reading from the device is done on a master-slave basis.

lowspeedWriteConfirm :: InputPort -> RxDataLength -> TxData -> NXT ()Source

Same as lowspeedWrite but also request a confirmation. Useful to assure the command was really accepted. In a case of an error it throws a NXTException.

Confirmation requires a change of the direction of NXT Bluetooth communication which takes around 30 ms.

lowspeedRead :: InputPort -> NXT RxDataSource

Reads data. The protocol does not support variable-length return packages so the response always contains 16 data bytes with invalid data padded with zeros.

Filesystem

openWrite :: FileName -> FileSize -> NXT FileHandleSource

Opens a given file for writing as a linked list of flash sectors.

openWriteLinear :: FileName -> FileSize -> NXT FileHandleSource

Opens a given file for writing as a linear contiguous block of flash memory (required for user programs and certain data files).

write :: FileHandle -> FileData -> NXT ()Source

Writes data to a file. At most 61 bytes can be written at a time.

writeConfirm :: FileHandle -> FileData -> NXT ()Source

Same as write but also request a confirmation. Useful to assure the command was really accepted. In a case of an error it throws a NXTException.

Confirmation requires a change of the direction of NXT Bluetooth communication which takes around 30 ms.

close :: FileHandle -> NXT ()Source

Closes a file.

closeConfirm :: FileHandle -> NXT ()Source

Same as close but also request a confirmation. Useful to assure the command was really accepted. In a case of an error it throws a NXTException.

Confirmation requires a change of the direction of NXT Bluetooth communication which takes around 30 ms.

delete :: FileName -> NXT ()Source

Deletes a given file.

deleteConfirm :: FileName -> NXT ()Source

Same as delete but also request a confirmation. Useful to assure the command was really accepted. In a case of an error it throws a NXTException.

Confirmation requires a change of the direction of NXT Bluetooth communication which takes around 30 ms.

deleteExisting :: FileName -> NXT ()Source

Same as deleteConfirm but it also requires that the file exists before deletion. It throws a NXTException otherwise.

IO Map

Interface to NXT firmware is based on internal IO map interface. All commands are in fact just pretty wrappers to this interface, but it is possible to use it directly and thus gain some additional possibilities which are not available otherwise (some of those are already wrapped in this interface's additional functions and feel free to suggest more if you need them).

getModuleID :: ModuleName -> NXT (Maybe ModuleID)Source

Helper function to get an ID of a module matching a given module name. Each module encompass some firmware functionality. Function caches IDs so it hopefully retrieves it from a cache of previous requests.

listModules :: ModuleName -> NXT [ModuleInfo]Source

Helper function to get information about all modules matching a given module name (which can be a wild card).

requestFirstModule :: ModuleName -> NXT (ModuleHandle, Maybe ModuleInfo)Source

Requests information about the first module matching a given module name (which can be a wild card). Returned module handle can be used for followup requests and has to be closed when not needed anymore.

requestNextModule :: ModuleHandle -> NXT (ModuleHandle, Maybe ModuleInfo)Source

Requests information about the next module matching previously requested module name (which can be a wild card). Returned module handle can be used for followup requests and has to be closed when not needed anymore.

closeModuleHandle :: ModuleHandle -> NXT ()Source

Closes module handle of previously requested module information.

closeModuleHandleConfirm :: ModuleHandle -> NXT ()Source

Same as closeModuleHandle but also request a confirmation. Useful to assure the command was really accepted. In a case of an error it throws a NXTException.

Confirmation requires a change of the direction of NXT Bluetooth communication which takes around 30 ms.

readIOMap :: ModuleID -> IOMapOffset -> IOMapLength -> NXT IOMapDataSource

Reads data from an IO map of a given module. At most 119 bytes can be read at a time.

You probably have to know what different values at different positions mean and control. The best way is to check NXT firmware source code.

writeIOMap :: ModuleID -> IOMapOffset -> IOMapData -> NXT ()Source

Writes data to an IO map of a given module. At most 54 bytes can be written at a time.

You probably have to know what different values at different positions mean and control. The best way is to check NXT firmware source code.

writeIOMapConfirm :: ModuleID -> IOMapOffset -> IOMapData -> NXT ()Source

Same as writeIOMap but also request a confirmation. Useful to assure the command was really accepted. In a case of an error it throws a NXTException.

Confirmation requires a change of the direction of NXT Bluetooth communication which takes around 30 ms.

Internals

Be careful when using those functions as you have to assure your program is well-behaved: you should see NXTInternals as a token you have to pass around in order, not reusing or copying values. (The only exception is that you can reuse the token initally returned by initialize in terminate call, even if you have used it in-between.) They are exposed so that you can decouple initalization, execution and termination phase. If you do not need that use withNXT.

initialize :: FilePath -> IO NXTInternalsSource

Opens and intializes a Bluetooth serial device communication.

terminate :: NXTInternals -> IO ()Source

Stops all NXT activities (by calling stopEverything) and closes the Bluetooth serial device communication. NXTInternals token must not be used after that anymore.

runNXT :: NXT a -> NXTInternals -> IO (a, NXTInternals)Source

Runs a computation in a context of a given NXTInternals token, returning a value and a new token.

execNXT :: NXT a -> NXTInternals -> IO NXTInternalsSource

Runs a computation in a context of a given NXTInternals token, returning just a new token.

Bluetooth utils

getDeviceInfo returns zero for Bluetooth signal strength as this is not implemented in current NXT firmware versions. Here are functions which retrieve that from a host (computer) Bluetooth stack.

bluetoothRSSI :: NXT IntSource

Gets received signal strength indicator (RSSI) of the Bluetooth connection to the NXT brick.

Currently supported only on Linux. It throws a NXTException otherwise.

bluetoothLinkQuality :: NXT IntSource

Gets link quality of the Bluetooth connection to the NXT brick.

Currently supported only on Linux. It throws a NXTException otherwise.

Types

data NXT a Source

Monad which encompasses interface to the NXT brick.

data Version Source

The format of version is "major.minor". To format it use printf "%d.%02d" major minor.

type Name = StringSource

Name of the NXT brick.

type BTAddress = StringSource

Bluetooth address of the NXT brick in the string format.

type BTStrength = Int64Source

Strength of the Bluetooth signal. Not implemented in current NXT firmware versions. Use bluetoothRSSI or bluetoothLinkQuality as an alternative.

type FlashFree = Int64Source

Free flash space on the NXT brick (in bytes).

data OutputPort Source

Constructors

A

Output port (motor) A.

B

Output port (motor) B.

C

Output port (motor) C.

type OutputPower = IntSource

Power and direction. In [-100, 100] range.

data OutputMode Source

Constructors

MotorOn

Enables PWM power according to speed.

Brake

Voltage is not allowed to float between PWM pulses, improves accuracy, uses more power.

Regulated

Required in conjunction with output regulation mode setting.

data RegulationMode Source

Constructors

RegulationModeIdle

Disables regulation.

RegulationModeMotorSpeed

Auto adjust PWM duty cycle if motor is affected by physical load. Really works only if there is room for that (not that motor is already running at the maximum power).

RegulationModeMotorSync

Attempts to keep rotation in sync with another motor that has this set. Also involves turn ratio.

type TurnRatio = IntSource

In regulated synced mode the difference between two motors. In [-100, 100] range.

data RunState Source

Constructors

MotorRunStateIdle

Disables power to motor.

MotorRunStateRampUp

Ramping to a new speed set-point that is greater than the current speed set-point.

MotorRunStateRunning

Enables power to motor.

MotorRunStateRampDown

Ramping to a new speed set-point that is less than the current speed set-point.

MotorRunStateHold

Hold at the current position.

type TachoLimit = Int64Source

Target tacho limit for a motor movement. 0 means no limit. It is an unsigned value (you select direction of motor movement with sign of OutputPower value).

type TachoCount = Int64Source

Internal (absolute) tacho counter. Number since the last reset of the motor tacho counter.

type BlockTachoCount = Int64Source

Block-relative position counter. Current position relative to the last programmed movement.

type RotationCount = Int64Source

Program-relative position counter. Current position relative to the last reset of the rotation sensor for this motor.

data MotorReset Source

Constructors

AbsolutePosition

Resets program-relative position counter (RotationCount).

RelativePosition

Resets block-relative position counter (BlockTachoCount)

InternalPosition

Resets internal movement counters (also TachoCount), cancels current goal and resets internal error-correction system.

data InputPort Source

Constructors

One

Input port (sensor) 1.

Two

Input port (sensor) 2.

Three

Input port (sensor) 3.

Four

Input port (sensor) 4.

type Valid = BoolSource

True if new data value should be seen as valid data.

type Calibrated = BoolSource

True if calibration file found and used for CalibratedValue.

data SensorMode Source

Constructors

RawMode

Reports scaled value equal to the raw value.

BooleanMode

Reports scaled value as 1 true or 0 false, false if raw value > 55% of total range, true if < 45%.

TransitionCntMode

Reports scaled value as number of transitions between true and false.

PeriodCounterMode

Reports scaled value as number of transitions from false to true, then back to false.

PctFullScaleMode

Reports scaled value as % of full scale reading for a configured sensor type.

CelsiusMode

For reporting temperature in celsius.

FahrenheitMode

For reporting temperature in fahrenheit.

AngleStepsMode

Reports scaled value as count of ticks on RCX-style rotation sensor.

type RawADValue = IntSource

Raw A/D value. Device dependent.

type NormalizedADValue = IntSource

Normalized A/D value. Type dependent. In [0, 1023] range.

type ScaledValue = IntSource

Scaled value. Mode dependent. In percent.

type CalibratedValue = IntSource

Value scaled according to calibration. Unused in current NXT firmware versions.

type Voltage = Ratio IntSource

Voltage value (in volts).

type Duration = NominalDiffTimeSource

Time duration (in seconds).

data Inbox Source

Inbox on the NXT brick into which the host (computer) queues messages for the program running there.

data RemoteInbox Source

Outbox on the NXT brick where the program running there queues messages for the host (computer). There is a convention that only RemoteInbox10 - RemoteInbox19 outboxes are used for this purpose so that lower ones can be used for inter-brick communication. But this convention is not really obeyed in practice.

type RemoveMessage = BoolSource

Should the message be remove from the queue once received?

type LoopPlayback = BoolSource

Loop playback of the sound file?

type Frequency = IntSource

Frequency of the played tone (in hertz).

type RxDataLength = IntSource

At most 16 data bytes can be read at a time.

type DeviceAddress = Word8Source

Address of the device (sensor) on the I2C bus.

type Command = Word8Source

I2C device command.

type Measurement = IntSource

I2C device measurement value.

type FileName = StringSource

Filename of the file on the NXT brick filesystem. In 15.3 format.

type FileSize = IntSource

Size of the file on the NXT brick filesystem.

type FileHandle = IntSource

Handle of the opened file on the NXT brick filesystem.

data ModuleInfo Source

Type of the IO map module information.

type ModuleName = StringSource

Module name extension is .mod. For some functions this can be also a wild card.

type ModuleHandle = IntSource

Handle for traversing of modules. Only one module handle can be opened at a time so be careful to close them when not needed anymore.

data TimeoutException Source

Timeout exception for NXT IO operations.

Constructors

TimoutException 

data NXTInternals Source

A token used for exposed internal functions.

Errors

Possible error codes and their descriptions are described in Lego Mindstorms NXT Bluetooth Developer Kit, Appendix 1 - Communication protocol and Appendix 2 - Direct commands.

data NXTException Source

Exception for NXT interface errors. Currently only one exception is defined which takes textual description as an argument.

Constructors

NXTException String