mathlink-0.1.0.2: Call Haskell from MathematicaSource codeContentsIndex
Foreign.MathLink.Types
Contents
Data marshaling
Execution
MathLink internal types
Synopsis
class Expressible a where
put :: a -> ML ()
get :: ML a
class Ix ix => Dimensional ix where
rank :: ix -> Int
dimensions :: (ix, ix) -> [Int]
fromDimensions :: [Int] -> (ix, ix)
data Expression
= ExInt Int
| ExReal Double
| ExString String
| ExSymbol String
| ExFunction String [Expression]
newtype ML a = ML {
runMLMonad :: ErrorT String (StateT State (ReaderT Config IO)) a
}
data Config = Config {
environment :: Environment
link :: Link
functionTable :: IntMap Function
}
data Function = Function {
callPattern :: String
argumentPattern :: String
function :: ML ()
}
data State = State {
abort :: Bool
done :: Bool
}
runML :: ML a -> State -> Config -> IO (Either String a)
newtype Link = Link (Ptr ())
newtype Environment = Environment (Ptr ())
data Type
= ErrorType
| IntType
| RealType
| StringType
| SymbolType
| FunctionType
| UnknownType Int
mkType :: Integral a => a -> Type
data Message
= TerminateMessage
| InterruptMessage
| AbortMessage
| EndPacketMessage
| SynchronizeMessage
| ImDyingMessage
| WaitingAcknowledgementMessage
| MarkTopLevelMessage
| LinkClosingMessage
| AuthenticateFailureMessage
| UserMessage Int
| UnknownMessage Int
mkMessage :: Integral a => a -> Message
data Error
= NoError
| DeadLnkError
| GetInconsistentError
| GetOutOfSeqError
| PutBadTokError
| PutOutOfSeqError
| PutTooBigError
| MachineOverflowError
| OutOfMemoryError
| SocketUnacceptedError
| UnconnectedError
| PutEndPacketError
| NextIncompleteCurrentPacketError
| NextUnknownPacketError
| GetEndPacketError
| AbortError
| ClosedError
| InitError
| ArgvError
| ProtocolError
| ModeError
| LaunchError
| RelaunchError
| LaunchSpaceError
| NoParentError
| NameTakenError
| NoListenError
| BadNameError
| BadHostError
| LaunchFailedError
| LaunchNameError
| PutConvertError
| GetConvertError
| PutBadEncodingError
| UnknownError Int
mkError :: Integral a => a -> Error
data Packet
= IllegalPacket
| CallPacket
| EvaluatePacket
| ReturnPacket
| InputNamePacket
| EnterTextPacket
| EnterExpressionPacket
| OutputNamePacket
| ReturnTextPacket
| ReturnExpressionPacket
| DisplayPacket
| DisplayEndPacket
| MessagePacket
| TextPacket
| InputPacket
| InputStringPacket
| MenuPacket
| SyntaxPacket
| SuspendPacket
| ResumePacket
| BeginDialogPacket
| EndDialogPacket
| UserPacket Int
| UnknownPacket Int
mkPacket :: Integral a => a -> Packet
Data marshaling
class Expressible a whereSource
Instances of Expressible are precisely the data types that can be marshaled to and from Mathematica.
Methods
put :: a -> ML ()Source
Send a value to Mathematica.
get :: ML aSource
Receive a value from Mathematica.
show/hide Instances
class Ix ix => Dimensional ix whereSource
Arrays to be marshaled to and from Mathematica require indices that are instances of Dimensional.
Methods
rank :: ix -> IntSource

The number of dimensions.

Shouldn't examine its argument.

dimensions :: (ix, ix) -> [Int]Source
The dimensions
fromDimensions :: [Int] -> (ix, ix)Source

The array bounds implied by a list of dimensions

NB: a (very) partial function! Fails if the length of the given list is different from the result of rank.

show/hide Instances
data Expression Source
Represents a general Mathematica expression.
Constructors
ExInt IntAn atomic value of integer type
ExReal DoubleAn atomic value of floating point type
ExString StringAn atomic value of string type
ExSymbol StringAn atomic value of symbol type
ExFunction String [Expression]A non-atomic value, with a head of type symbol and a list of arguments
show/hide Instances
Execution
newtype ML a Source
The monad in which functions exposed to Mathematica execute.
Constructors
ML
runMLMonad :: ErrorT String (StateT State (ReaderT Config IO)) a
show/hide Instances
data Config Source
Encapsulates the readable state associated with the ML monad.
Constructors
Config
environment :: Environment
link :: Link
functionTable :: IntMap Function
show/hide Instances
data Function Source
Encapsulates a description of a function callable from Mathematica
Constructors
Function
callPattern :: StringA string representing the Mathematica pattern whose match should result in a function call to the specified Haskell function. Analogous to the :Pattern: directive in an input to Mathematica's mprep utility.
argumentPattern :: StringA string representing the Mathematica pattern for the argument that will be marshaled from Mathematica to Haskell. Pattern variables appearing here are bound in the callPattern match. Analogous to the :Arguments: directive in an input to Mathematica's mprep utility.
function :: ML ()The Haskell function to be invoked.
show/hide Instances
data State Source
Encapsulates the read/write state associated with the ML monad.
Constructors
State
abort :: Bool
done :: Bool
show/hide Instances
runML :: ML a -> State -> Config -> IO (Either String a)Source
Runs the given ML computation with the given state and configuration.
MathLink internal types
newtype Link Source
A wrapped pointer to the MathLink link.
Constructors
Link (Ptr ())
show/hide Instances
newtype Environment Source
A wrapped pointer to the MathLink environment.
Constructors
Environment (Ptr ())
show/hide Instances
data Type Source
An enumeriation of possible return values from the MathLink functions MLGetNext or MLGetType.
Constructors
ErrorType
IntType
RealType
StringType
SymbolType
FunctionType
UnknownType Int
show/hide Instances
mkType :: Integral a => a -> TypeSource
data Message Source
An enumeration of MathLink message types.
Constructors
TerminateMessage
InterruptMessage
AbortMessage
EndPacketMessage
SynchronizeMessage
ImDyingMessage
WaitingAcknowledgementMessage
MarkTopLevelMessage
LinkClosingMessage
AuthenticateFailureMessage
UserMessage Int
UnknownMessage Int
show/hide Instances
mkMessage :: Integral a => a -> MessageSource
data Error Source
An enumeration of some error codes defined in mathlink.h.
Constructors
NoError
DeadLnkError
GetInconsistentError
GetOutOfSeqError
PutBadTokError
PutOutOfSeqError
PutTooBigError
MachineOverflowError
OutOfMemoryError
SocketUnacceptedError
UnconnectedError
PutEndPacketError
NextIncompleteCurrentPacketError
NextUnknownPacketError
GetEndPacketError
AbortError
ClosedError
InitError
ArgvError
ProtocolError
ModeError
LaunchError
RelaunchError
LaunchSpaceError
NoParentError
NameTakenError
NoListenError
BadNameError
BadHostError
LaunchFailedError
LaunchNameError
PutConvertError
GetConvertError
PutBadEncodingError
UnknownError Int
show/hide Instances
mkError :: Integral a => a -> ErrorSource
Turns an Integral into the corresponding Error.
data Packet Source
An enumeration of MathLink packet types
Constructors
IllegalPacket
CallPacket
EvaluatePacket
ReturnPacket
InputNamePacket
EnterTextPacket
EnterExpressionPacket
OutputNamePacket
ReturnTextPacket
ReturnExpressionPacket
DisplayPacket
DisplayEndPacket
MessagePacket
TextPacket
InputPacket
InputStringPacket
MenuPacket
SyntaxPacket
SuspendPacket
ResumePacket
BeginDialogPacket
EndDialogPacket
UserPacket Int
UnknownPacket Int
show/hide Instances
mkPacket :: Integral a => a -> PacketSource
Produced by Haddock version 2.3.0