hemokit-0.6.0: Haskell port of the Emokit EEG project

Safe HaskellNone

Hemokit

Contents

Description

A library for reading from an Emotic EPOC EEG.

Synopsis

Opening and reading from EEGs

_EMOTIV_VENDOR_ID :: VendorID

The USB vendor ID of the Emotiv EPOC.

_EMOTIV_PRODUCT_ID :: ProductID

The USB product ID of the Emotiv EPOC.

data EmotivDeviceInfo

Identifies an Emotiv device.

Constructors

EmotivDeviceInfo 

Fields

hidapiDeviceInfo :: DeviceInfo

The hidapi device info.

data EmotivRawDevice

An open data source to read bytes from.

Constructors

HidapiDevice 

Fields

hidapiDevice :: Device

The open hidapi device.

HandleDevice 

Fields

handleDevice :: Handle

A conventional Handle, e.g. an open file.

Instances

Generic EmotivRawDevice 

data EmotivDevice

Identifies an open Emotiv device. Also contains the cumulative EmotivState of the EEG.

Constructors

EmotivDevice 

Fields

rawDevice :: EmotivRawDevice

Where we get our data from, some form of open handle.

serial :: SerialNumber

The EEG's serial.

emotivModel :: EmotivModel

Whether the EEG is a consumer or developer model.

stateRef :: IORef (Maybe EmotivState)

The EEG's cumulative state.

Instances

Generic EmotivDevice 

getEmotivDevices :: IO [EmotivDeviceInfo]

Lists all EPOC devices, ordered by interface number. If you do not actively choose amongst them, the last one is usually the one you want (especially if only 1 EEG is connected).

openEmotivDevice :: EmotivModel -> EmotivDeviceInfo -> IO EmotivDevice

Opens a given Emotiv device. Returns an EmotivDevice to read from with readEmotiv.

openEmotivDeviceFile :: EmotivModel -> SerialNumber -> String -> IO EmotivDevice

Creates an EmotivDevice device from a path, e.g. a device like devhidraw1 or a normal file containing dumped binary data.

openEmotivDeviceHandle :: EmotivModel -> SerialNumber -> Handle -> IO EmotivDevice

Creates an EmotivDevice device from an open file handle.

readEmotiv :: EmotivDevice -> IO (Maybe (EmotivState, EmotivPacket))

Reads one 32 byte packet from the device, parses the raw bytes into an EmotivPacket and updates the cumulative EmotivState that we maintain for that device.

Returns both the packet read from the device and the updated state.

Returns Nothing on end of input (or if there are < 32 bytes before it).

Note that if the EEG is (turned) off, this function block until it is turned on again.

data EmotivException

Emotiv related errors.

Constructors

InvalidSerialNumber SerialNumber

Serial does not have right format.

CouldNotReadSerial DevicePath

We could not read the serial from the device.

OtherEmotivException String 

data SerialNumber

A valid Emotiv serial number. 16 bytes.

Instances

makeSerialNumber :: ByteString -> Maybe SerialNumber

Checks an Emotiv serial, returning a SerialNumber if it's valid.

makeSerialNumberFromString :: String -> Maybe SerialNumber

Like makeSerialNumber, using a String.

deviceInfoSerial :: EmotivDeviceInfo -> Maybe SerialNumber

Conveniently expose the serial number of a device.

data EmotivModel

Whether the EPOC is a consumer or developer model.

This affects how the EEG data is to be decrypted.

You can check if you are using the correct model by seeing if the packet counter increases from 0 until 128 on subsequent packets.

Constructors

Consumer 
Developer 

Instances

EEG data

data EmotivPacket

Contains the data of a single packet sent from the device. Accumulated data (the current state) is available in EmotivState.

Constructors

EmotivPacket 

Fields

packetCounter :: Int

counts up from 0 to 127 (128 Hz)

packetBattery :: Maybe Int

the current battery percentage

packetGyroX :: Int

turning left gives positive numbers

packetGyroY :: Int

turning down gives positive numbers

packetSensors :: Vector Int

EEG sensor values

packetQuality :: Maybe (Sensor, Int)

EEG sensor-to-skin connectivity

data EmotivState

Contains the current state of the EEG, cumulateively updated by incoming EmotivPackets.

Constructors

EmotivState 

Fields

counter :: Int

counts up from 0 to 127 (128 Hz)

battery :: Int

the current battery percentage

gyroX :: Int

turning left gives positive numbers

gyroY :: Int

turning down gives positive numbers

sensors :: Vector Int

EEG sensor values

qualities :: Vector Int

EEG sensor-to-skin connectivity

data Sensor

The sensors of an Emotiv EPOC. Uses the names from the International 10-20 system.

Constructors

F3 
FC5 
AF3 
F7 
T7 
P7 
O1 
O2 
P8 
T8 
F8 
AF4 
FC6 
F4 

Instances

Bounded Sensor 
Enum Sensor 
Eq Sensor 
Ord Sensor 
Show Sensor 
Generic Sensor 
NFData Sensor 

allSensors :: [Sensor]

Contains all Sensors.

Dealing with (decrypted) raw data

newtype EmotivRawData

Wraps (unencrypted) Emotiv raw data. Ensures that it is 32 bytes.

Constructors

EmotivRawData 

Fields

emotivRawDataBytes :: ByteString
 

readEmotivRaw :: EmotivDevice -> IO (Maybe EmotivRawData)

Reads one 32 byte packet from the device and decrypts it to raw data.

Returns Nothing on end of input (or if there are < 32 bytes before it).

Note that if the EEG is (turned) off, this function block until it is turned on again.

makeEmotivRawData :: ByteString -> EmotivRawData

Treat a ByteString as Emotiv raw data. Errors if the input is non 32 bytes.

parsePacket :: EmotivRawData -> EmotivPacket

Parses an EmotivPacket from raw bytes.

updateEmotivState :: EmotivDevice -> EmotivRawData -> IO (EmotivState, EmotivPacket)

Given a device and a Emotiv raw data, parses the raw data into an EmotivPacket and updates the cumulative EmotivState that we maintain for that device.

Care should be taken that raw data is fed into this function in the right order (e.g. respecting the EEG's increasing sequence numbers and quality updates).

This function is only neededif you want to obtain both raw data and parsed packages. If you are not interested in raw data, use readEmotiv instead.

Returns both the packet read from the device and the updated state.

Encrypted raw data

decrypt :: SerialNumber -> EmotivModel -> ByteString -> EmotivRawData

Takes a 32 bytes encrypted EEG data, returns 32 bytes decrypted EEG data.

Internals

newtype BitMask

Describes the indices of bits to make up a certain value.

Constructors

BitMask [Word8] 

Instances

Eq BitMask 
Ord BitMask 
Show BitMask 

getSensorMask :: Sensor -> BitMask

Describes which bits in a raw data packet make up the given sensor.

qualityMask :: BitMask

Describes which bits in a raw data packat make up a sensor quality value.

getLevel :: EmotivRawData -> BitMask -> Int

Extracts the sensor value for the given sensor from Emotiv raw data.

batteryValue :: Word8 -> Int

Parses a battery percentage value from a byte.

qualitySensorFromByte0 :: Word8 -> Maybe Sensor

Which sensor's quality is transmitted in the packet (depends on first byte, the packet counter).

Interactive use

withDataFromLastEEG :: EmotivModel -> ((EmotivState, EmotivPacket) -> IO ()) -> IO ()

Opens and reads from the last available device, giving all data from it to the given function. Stops if end of input is reached.

Intended for use with ghci.

Examples:

withDataFromLastEEG Consumer print
withDataFromLastEEG Consumer (print . packetQuality . snd)
withDataFromLastEEG Consumer (putStrLn . unwords . map show . V.toList . qualities . fst)