libmodbus-1.1.1: Haskell bindings to the C modbus library

Safe HaskellNone
LanguageHaskell98

System.Modbus

Contents

Description

Haskell bindings to the C modbus library https://libmodbus.org/

Synopsis

Equivilance to the C library

Functions in this module are named the same as those in the C library, but without the leading "modbus_". You may wish to import this module qualified as Modbus to make the names match up.

See the C library documentation for details about the use of any function. https://libmodbus.org/documentation/

When a function in the C library returns a special value on error, this module will instead throw an exception.

This module has been tested with version 3.1.4 of the C library. It may also work with other versions.

Example

This example reads some of the registers of an Epever solar charge controller. It shows how the binary library can be used to decode the modbus registers into a haskell data structure.

 import System.Modbus
 import Data.Binary.Get
 
 main = do
 	mb <- new_rtu "/dev/ttyS1" (Baud 115200) ParityNone (DataBits 8) (StopBits 1)
 	set_slave mb (DeviceAddress 1)
 	connect mb
 	regs <- mkRegisterVector 5
 	b <- read_input_registers mb (Addr 0x3100) regs
 	print $ runGet getEpever b
 
 data Epever = Epever
 	{ pv_array_voltage :: Float
 	, pv_array_current :: Float
 	, pv_array_power :: Float
 	, battery_voltage :: Float
 	} deriving (Show)
 
 getEpever :: Get Epever
 getEpever = Epever
	<$> epeverfloat  -- register 0x3100
 	<*> epeverfloat  -- register 0x3101
	<*> epeverfloat2 -- register 0x3102 (low) and 0x3103 (high)
 	<*> epeverfloat  -- register 0x3104
  where
	 epeverfloat = decimals 2 <$> getWord16host
	 epeverfloat2 = do
	 	l <- getWord16host
	 	h <- getWord16host
	 	return (decimals 2 (l + h*2^16))
 	 decimals n v = fromIntegral v / (10^n)

Core data types

data Context Source #

A modbus device context.

The context will automatically be closed and freed when it is garbage collected.

newtype Addr Source #

An address on a modbus device.

Constructors

Addr Int 
Instances
Eq Addr Source # 
Instance details

Defined in System.Modbus

Methods

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

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

Show Addr Source # 
Instance details

Defined in System.Modbus

Methods

showsPrec :: Int -> Addr -> ShowS #

show :: Addr -> String #

showList :: [Addr] -> ShowS #

RTU Context

newtype Baud Source #

Constructors

Baud Int 
Instances
Eq Baud Source # 
Instance details

Defined in System.Modbus

Methods

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

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

Show Baud Source # 
Instance details

Defined in System.Modbus

Methods

showsPrec :: Int -> Baud -> ShowS #

show :: Baud -> String #

showList :: [Baud] -> ShowS #

data Parity Source #

Instances
Eq Parity Source # 
Instance details

Defined in System.Modbus

Methods

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

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

Show Parity Source # 
Instance details

Defined in System.Modbus

newtype DataBits Source #

Constructors

DataBits Int 
Instances
Eq DataBits Source # 
Instance details

Defined in System.Modbus

Show DataBits Source # 
Instance details

Defined in System.Modbus

newtype StopBits Source #

Constructors

StopBits Int 
Instances
Eq StopBits Source # 
Instance details

Defined in System.Modbus

Show StopBits Source # 
Instance details

Defined in System.Modbus

new_rtu :: FilePath -> Baud -> Parity -> DataBits -> StopBits -> IO Context Source #

Create a modbus Remote Terminal Unit context.

The FilePath is the serial device to connect to.

data SerialMode Source #

Constructors

RTU_RS232 
RTU_RS485 
Instances
Eq SerialMode Source # 
Instance details

Defined in System.Modbus

Show SerialMode Source # 
Instance details

Defined in System.Modbus

data RTS Source #

Instances
Eq RTS Source # 
Instance details

Defined in System.Modbus

Methods

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

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

Show RTS Source # 
Instance details

Defined in System.Modbus

Methods

showsPrec :: Int -> RTS -> ShowS #

show :: RTS -> String #

showList :: [RTS] -> ShowS #

TCP (IPv4) Context

data IPAddress Source #

IPv4 address to connect to. In server mode, use AnyAddress to listen to any addresses.

Constructors

IPAddress String 
AnyAddress 
Instances
Eq IPAddress Source # 
Instance details

Defined in System.Modbus

Show IPAddress Source # 
Instance details

Defined in System.Modbus

newtype Port Source #

Constructors

Port Int 
Instances
Eq Port Source # 
Instance details

Defined in System.Modbus

Methods

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

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

Show Port Source # 
Instance details

Defined in System.Modbus

Methods

showsPrec :: Int -> Port -> ShowS #

show :: Port -> String #

showList :: [Port] -> ShowS #

Default Port Source # 
Instance details

Defined in System.Modbus

Methods

def :: Port

new_tcp :: IPAddress -> Port -> IO Context Source #

Create a modbus TCP/IPv4 context.

TCP PI (IPv4 and IPv6) Context

data Node Source #

Host name or IP address to connect to. In server mode, use AnyNode to listen to any addresses.

Constructors

Node String 
AnyNode 
Instances
Eq Node Source # 
Instance details

Defined in System.Modbus

Methods

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

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

Show Node Source # 
Instance details

Defined in System.Modbus

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

newtype Service Source #

Service name/port number to connect to.

Constructors

Service String 
Instances
Eq Service Source # 
Instance details

Defined in System.Modbus

Methods

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

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

Show Service Source # 
Instance details

Defined in System.Modbus

Default Service Source # 
Instance details

Defined in System.Modbus

Methods

def :: Service

Configuration

newtype DeviceAddress Source #

The address of a modbus device.

Constructors

DeviceAddress Int 
Instances
Eq DeviceAddress Source # 
Instance details

Defined in System.Modbus

Show DeviceAddress Source # 
Instance details

Defined in System.Modbus

set_slave :: Context -> DeviceAddress -> IO () Source #

Set the address of the modbus device that the Context should communicate with.

data Timeout Source #

Constructors

Timeout 

Fields

Instances
Eq Timeout Source # 
Instance details

Defined in System.Modbus

Methods

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

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

Show Timeout Source # 
Instance details

Defined in System.Modbus

data ErrorRecoveryMode Source #

Constructors

ErrorRecoveryNone 
ErrorRecoveryLink

Reconnect after response timeout.

ErrorRecoveryProtocol

Clean up ongoing communication.

ErrorRecoveryLinkProtocol

Combine both.

Accessing registers

type RegisterVector = IOVector Word16 Source #

A mutable vector that is used as a buffer when reading or writing registers of a modbus device.

mkRegisterVector :: Int -> IO RegisterVector Source #

Allocates a vector holding the contents of a specified number of registers.

The values are initialized to 0 to start.

class RegisterData t where Source #

Types that can hold modbus register data.

Of these, RegisterVector is the most efficient as it avoids allocating new memory on each read or write. But it can be more useful to get a ByteString and use a library such as cereal or binary to parse the contents of the modbus registers.

read_registers :: RegisterData t => Context -> Addr -> RegisterVector -> IO t Source #

Reads the holding registers from the modbus device, starting at the Addr, into the RegisterVector buffer.

read_input_registers :: RegisterData t => Context -> Addr -> RegisterVector -> IO t Source #

Reads the input registers from the modbus device, starting at the Addr, into the RegisterVector buffer.

write_registers :: Context -> Addr -> RegisterVector -> IO () Source #

Writes the registers to the modbus device, starting at the Addr.

write_and_read_registers Source #

Arguments

:: Context 
-> Addr

address to write to

-> RegisterVector

data to write

-> Addr

address to read from

-> RegisterVector

data to read

-> IO () 

Accessing bits/coils

type BitVector = IOVector Bit Source #

A mutable vector that is used as a buffer when reading or writing bits (coils) of a modbus device.

mkBitVector :: Int -> IO BitVector Source #

Allocates a vector holding the specified number of bits.

The bits are set to start.

class BitData t where Source #

Types that can hold modbus bit data.

Of these, BitVector is the most efficient as it avoids allocating new memory on each read or write. But it can be easier to use a Vector of Bool.

type Bit = Word8 Source #

read_bits :: BitData t => Context -> Addr -> BitVector -> IO t Source #

Reads the bits (coils) from the modbus device, starting at the Addr, into the BitVector.

read_input_bits :: BitData t => Context -> Addr -> BitVector -> IO t Source #

Reads the input bits from the modbus device, starting at the Addr, into the BitVector.

write_bits :: Context -> Addr -> BitVector -> IO () Source #

Writes the bits (coils) of the modbus device, starting at the Addr.