Copyright | (c) Eric Sessoms 2008 (c) Artúr Poór 2015 |
---|---|
License | GPL3 |
Maintainer | gombocarti@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
Foreign.Erlang
Contents
Description
Speaks the Erlang network protocol and impersonates an Erlang node on the network. Fully capable of bi-directional communication with Erlang. Erlang types are, as far as reasonable, mapped to Haskell types. Messages to Erlang are just function calls in Haskell, and messages from Erlang are delivered to MVars.
Synopsis
- type HostName = String
- data Node
- type Name = String
- type ErlRecv = IO (Maybe ErlType, Maybe ErlType)
- type ErlSend = (Maybe ErlType, Maybe ErlType) -> IO ()
- epmdGetNames :: IO [String]
- epmdGetPort :: Node -> IO Int
- epmdGetPortR4 :: String -> String -> IO (Int, Int, Int, Int, Int, String, String)
- genCall :: Erlang a => MBox -> Node -> Pid -> a -> IO ErlType
- genCast :: Erlang a => MBox -> Node -> Pid -> a -> IO ()
- rpcCall :: MBox -> Node -> String -> String -> [ErlType] -> IO ErlType
- rpcCast :: MBox -> Node -> String -> String -> [ErlType] -> IO ()
- backup :: MBox -> Node -> String -> IO ErlType
- dirtyAllKeys :: MBox -> Node -> String -> IO ErlType
- dirtyFirst :: MBox -> Node -> String -> IO ErlType
- dirtyNext :: MBox -> Node -> String -> ErlType -> IO ErlType
- dirtyLast :: MBox -> Node -> String -> IO ErlType
- dirtyPrev :: MBox -> Node -> String -> ErlType -> IO ErlType
- dirtyMatchObject :: MBox -> Node -> ErlType -> IO ErlType
- dirtyRead :: MBox -> Node -> String -> ErlType -> IO ErlType
- dirtySelect :: MBox -> Node -> String -> ErlType -> IO ErlType
- data Self
- createSelf :: String -> IO Self
- data MBox
- createMBox :: Self -> IO MBox
- mboxRef :: MBox -> IO ErlType
- mboxSelf :: MBox -> ErlType
- type Pid = Either ErlType String
- mboxRecv :: MBox -> IO ErlType
- mboxRecv' :: MBox -> ErlType -> IO ErlType
- mboxSend :: Erlang a => MBox -> Node -> Pid -> a -> IO ()
- class Erlang a where
- data ErlType
- nth :: Erlang a => Int -> ErlType -> a
- erlangTimeToSeconds :: Integral a => ErlType -> a
- secondsToErlangTime :: Integral a => a -> ErlType
Documentation
Either a host name e.g., "haskell.org"
or a numeric host
address string consisting of a dotted decimal IPv4 address or an
IPv6 address e.g., "192.168.0.1"
.
Representation of an Erlang node on the network.
epmdGetNames :: IO [String] Source #
Return the names and addresses of registered local Erlang nodes.
epmdGetPortR4 :: String -> String -> IO (Int, Int, Int, Int, Int, String, String) Source #
Returns (port, nodeType, protocol, vsnMax, vsnMin, name, extra)
High-level communication
rpcCall :: MBox -> Node -> String -> String -> [ErlType] -> IO ErlType Source #
rpc:call(Node, Module, Function, Arguments)
rpcCast :: MBox -> Node -> String -> String -> [ErlType] -> IO () Source #
rpc:cast(Node, Module, Function, Arguments)
Mnesia database methods
Low-level communication
Representation of a Haskell node (program)
createSelf :: String -> IO Self Source #
Instantiate a Haskell node. This initializes the FFI.
Node name should be a 'long name' e.g. "haskell@localhost"
.
Representation of a Haskell process (thread)
Haskell threads don't natively have Erlang process IDs. Instead, we use a mailbox abstraction that we can assign PIDs to for communication with Erlang.
createMBox :: Self -> IO MBox Source #
Create a new process on the Haskell side. Usually corresponds to a thread but doesn't need to.
Representation of Erlang nodes and processes
type Pid = Either ErlType String Source #
Represents a foreign (Erlang) process. A process can be identified either by its low-level ID (Left pid) or by its registered name (Right name).
Communication to and from Erlang
mboxRecv' :: MBox -> ErlType -> IO ErlType Source #
Receive a reply message. That is, looks for the next message identified by the given reference.
mboxSend :: Erlang a => MBox -> Node -> Pid -> a -> IO () Source #
Send an arbitrary message to the specified node and process. It is equivalent in Erlang to
{Node, Pid} ! Msg.
Minimal complete definition
Instances
Erlang Bool Source # | |
Erlang Double Source # | |
Erlang Float Source # | |
Erlang Int Source # | |
Erlang Integer Source # | |
Erlang String Source # | |
Erlang ErlType Source # | |
Erlang Node Source # | |
Erlang a => Erlang [a] Source # | |
Defined in Foreign.Erlang.Types | |
Erlang [ErlType] Source # | |
(Erlang a, Erlang b) => Erlang (a, b) Source # | |
Defined in Foreign.Erlang.Types | |
(Erlang a, Erlang b, Erlang c) => Erlang (a, b, c) Source # | |
Defined in Foreign.Erlang.Types | |
(Erlang a, Erlang b, Erlang c, Erlang d) => Erlang (a, b, c, d) Source # | |
Defined in Foreign.Erlang.Types | |
(Erlang a, Erlang b, Erlang c, Erlang d, Erlang e) => Erlang (a, b, c, d, e) Source # | |
Defined in Foreign.Erlang.Types |
Constructors
Miscellaneous utilities
erlangTimeToSeconds :: Integral a => ErlType -> a Source #
Convert a tuple (from erlang:now()
) to seconds from Jan 1, 1970.
secondsToErlangTime :: Integral a => a -> ErlType Source #
Convert seconds to an Erlang tuple representing time.