jack-0.7.2.2: Bindings for the JACK Audio Connection Kit

Safe HaskellNone
LanguageHaskell98

Sound.JACK

Contents

Description

The Jack module defines types and functions that allows you to use the JACK Audio Connection Kit.

Synopsis

general stuff

newtype Client Source #

Handles of Jack clients

Constructors

Client (Ptr Client) 

newClient Source #

Arguments

:: ThrowsStatus e 
=> String

name of the JACK server

-> String

name of the client

-> ExceptionalT e IO Client 

Constructs a new Jack client.

newClientDefault Source #

Arguments

:: ThrowsStatus e 
=> String

name of the client

-> ExceptionalT e IO Client 

Creates a new JACK client with the default server

withClient Source #

Arguments

:: ThrowsStatus e 
=> String

name of the JACK server

-> String

name of the client

-> (Client -> ExceptionalT e IO a) 
-> ExceptionalT e IO a 

Run a block of code with a newly allocated client. Do not use the client outside the block.

withClientDefault Source #

Arguments

:: ThrowsStatus e 
=> String

name of the client

-> (Client -> ExceptionalT e IO a) 
-> ExceptionalT e IO a 

clientClose :: ThrowsErrno e => Client -> PortSet -> ExceptionalT e IO () Source #

closes the given Jack client without causing any trouble (hopefully)

activate :: ThrowsErrno e => Client -> ExceptionalT e IO () Source #

activates the given Jack client

class PortType typ Source #

Jack Port Type

Minimal complete definition

switchPortType

Instances
PortType CFloat Source # 
Instance details

Defined in Sound.JACK.Private

Methods

switchPortType :: f CFloat -> f EventBuffer -> f CFloat

class Direction dir Source #

Minimal complete definition

switchDir

Instances
Direction Output Source # 
Instance details

Defined in Sound.JACK

Methods

switchDir :: f Input -> f Output -> f Output

Direction Input Source # 
Instance details

Defined in Sound.JACK

Methods

switchDir :: f Input -> f Output -> f Input

data Input Source #

Type argument for Jack input ports

Instances
Direction Input Source # 
Instance details

Defined in Sound.JACK

Methods

switchDir :: f Input -> f Output -> f Input

data Output Source #

Type argument for Jack output ports

Instances
Direction Output Source # 
Instance details

Defined in Sound.JACK

Methods

switchDir :: f Input -> f Output -> f Output

data UnknownType Source #

Type argument for Jack ports where the type of samples transported by the port is unknown.

data UnknownDirection Source #

Type argument for Jack ports where we do not know whether it is an input or an output port.

newtype Port typ dir Source #

Constructors

Port (Ptr (Port typ)) 

newPort Source #

Arguments

:: (PortType typ, Direction dir, ThrowsPortRegister e) 
=> Client

Jack client

-> String

name of the input port

-> ExceptionalT e IO (Port typ dir) 

Better use withPort that also handles freeing the port.

disposePort :: (PortType typ, Direction dir, ThrowsErrno e) => Client -> Port typ dir -> ExceptionalT e IO () Source #

withPort Source #

Arguments

:: (PortType typ, Direction dir, ThrowsPortRegister e, ThrowsErrno e) 
=> Client

Jack client

-> String

name of the input port

-> (Port typ dir -> ExceptionalT e IO a) 
-> ExceptionalT e IO a 

Creates a new port for the given client and delete it after usage. The port manages audio or MIDI data in input or output direction depending on the Port type. Usually the required port type can be inferred from following actions that use that port.

Do not use the port outside the enclosed block.

data PortSet Source #

A collection of mixed types of ports. It is mainly needed for freeing all allocated ports.

Instances
Semigroup PortSet Source # 
Instance details

Defined in Sound.JACK

Monoid PortSet Source # 
Instance details

Defined in Sound.JACK

setOfPort :: (PortType typ, Direction dir) => Port typ dir -> PortSet Source #

setOfPorts :: (PortType typ, Direction dir) => [Port typ dir] -> PortSet Source #

type Process arg = NFrames -> Ptr arg -> IO Errno Source #

withProcess :: ThrowsErrno e => Client -> (NFrames -> ExceptionalT Errno IO ()) -> ExceptionalT e IO a -> ExceptionalT e IO a Source #

The callback function must respond in real-time, i.e. in a bounded amout of time. That is, strictly spoken it must not wait for anything, e.g. it must not wait for locks and it must not allocate memory. In Haskell this is practically impossible because even simplest operations allocate memory. If the callback needs to much time, JACK will shut down your client. The best you can do is to hope that nothing evil happens.

type Freewheel arg = CInt -> Ptr arg -> IO () Source #

type BufferSize arg = NFrames -> Ptr arg -> IO Errno Source #

type SampleRate arg = NFrames -> Ptr arg -> IO Errno Source #

type PortRename arg = PortId -> PortName -> PortName -> Ptr arg -> IO () Source #

type GraphOrder arg = Ptr arg -> IO Errno Source #

type XRun arg = Ptr arg -> IO Errno Source #

makeXRun :: XRun arg -> IO (FunPtr (XRun arg)) Source #

setXRun :: ThrowsErrno e => Client -> FunPtr (XRun arg) -> Ptr arg -> ExceptionalT e IO () Source #

type Latency arg = LatencyCallbackMode -> Ptr arg -> IO () Source #

type ClientRegistration arg = CString -> CInt -> Ptr arg -> IO () Source #

makeClientRegistration :: ClientRegistration arg -> IO (FunPtr (ClientRegistration arg)) Source #

Create a client registration callback FunPtr.

setClientRegistration :: ThrowsErrno e => Client -> FunPtr (ClientRegistration arg) -> Ptr arg -> ExceptionalT e IO () Source #

Set the client registration callback.

data PortId Source #

Instances
Eq PortId Source # 
Instance details

Defined in Sound.JACK.FFI

Methods

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

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

Ord PortId Source # 
Instance details

Defined in Sound.JACK.FFI

Show PortId Source # 
Instance details

Defined in Sound.JACK.FFI

makePortRegistration :: PortRegistration arg -> IO (FunPtr (PortRegistration arg)) Source #

Create a port registration callback FunPtr.

setPortRegistration :: ThrowsErrno e => Client -> FunPtr (PortRegistration arg) -> Ptr arg -> ExceptionalT e IO () Source #

Set the port registration callback.

type PortConnect arg = PortId -> PortId -> CInt -> Ptr arg -> IO () Source #

makePortConnect :: PortConnect arg -> IO (FunPtr (PortConnect arg)) Source #

Create a port connect callback FunPtr.

setPortConnect :: ThrowsErrno e => Client -> FunPtr (PortConnect arg) -> Ptr arg -> ExceptionalT e IO () Source #

Set the port connect callback.

portName :: Port typ dir -> IO String Source #

Return the full port name, including the client_name: prefix.

portShortName :: Port typ dir -> IO String Source #

Return the short port name, not including the client_name: prefix.

portAliases :: Port typ dir -> IO [String] Source #

Return the port aliases, including the client_name: prefixes.

This is especially useful for external midi devices, as the alias names are usually more descriptive than system:midi_capture_1.

getPorts Source #

Arguments

:: Client

the Jack client

-> IO [String]

the names as a list of strings

Returns the names of all existing ports.

portGetAllConnections :: Client -> Port typ dir -> IO [String] Source #

Return all the port names a given port is connected to.

This function must not be called from a JACK event callback.

newtype NFrames Source #

represents absolute frame time

Constructors

NFrames Word32 
Instances
Eq NFrames Source # 
Instance details

Defined in Sound.JACK.FFI

Methods

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

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

Ord NFrames Source # 
Instance details

Defined in Sound.JACK.FFI

Show NFrames Source # 
Instance details

Defined in Sound.JACK.FFI

Ix NFrames Source # 
Instance details

Defined in Sound.JACK.FFI

Semigroup NFrames Source # 
Instance details

Defined in Sound.JACK.FFI

Monoid NFrames Source # 
Instance details

Defined in Sound.JACK.FFI

Storable NFrames Source # 
Instance details

Defined in Sound.JACK.FFI

C NFrames Source # 
Instance details

Defined in Sound.JACK.FFI

Methods

split :: NFrames -> NFrames -> (NFrames, (Bool, NFrames)) #

quit :: MVar () -> Client -> PortSet -> IO () Source #

Deprecated: Write your own function instead.

waitForBreakAndClose :: Client -> PortSet -> IO () Source #

Deprecated: Write your own function instead.

Exceptions