hscdio-0.1.0.0: Haskell bindings to the libcdio disc-reading library.
Copyright(c) 2019-2021 Sam May
LicenseGPL-3.0-or-later
Maintainerag@eitilt.life
Stabilitystable
Portabilitynon-portable (requires libcdio)
Safe HaskellNone
LanguageHaskell2010

Sound.Libcdio

Description

One of the goals of these bindings is to make it not only possible to interface with the libcdio library, but to do so as comfortably and safely as possible. In that, the Foreign.Libcdio interface is a bit lacking, due to its mutable state and requirement of threading IO through computations. The modules in this namespace provide an alternative which builds on that base, with a more native style. As a general rule, a project should only import modules from the Sound or the Foreign namespaces, not both, as while the types can often be interchanged, several function names have been reused and so may collide.

Synopsis

Types

Session

data Cdio a Source #

A computation within the environment of the data (music or file) stored on a CD. The options for affecting that environment from within are limited by design, as this library is intended for reading discs rather than authoring them.

Instances

Instances details
Monad Cdio Source # 
Instance details

Defined in Sound.Libcdio.Types.Cdio

Methods

(>>=) :: Cdio a -> (a -> Cdio b) -> Cdio b #

(>>) :: Cdio a -> Cdio b -> Cdio b #

return :: a -> Cdio a #

Functor Cdio Source # 
Instance details

Defined in Sound.Libcdio.Types.Cdio

Methods

fmap :: (a -> b) -> Cdio a -> Cdio b #

(<$) :: a -> Cdio b -> Cdio a #

MonadFail Cdio Source #

Wraps the text in a FreeformCdioError, for recovery with catchError.

Instance details

Defined in Sound.Libcdio.Types.Cdio

Methods

fail :: String -> Cdio a #

Applicative Cdio Source # 
Instance details

Defined in Sound.Libcdio.Types.Cdio

Methods

pure :: a -> Cdio a #

(<*>) :: Cdio (a -> b) -> Cdio a -> Cdio b #

liftA2 :: (a -> b -> c) -> Cdio a -> Cdio b -> Cdio c #

(*>) :: Cdio a -> Cdio b -> Cdio b #

(<*) :: Cdio a -> Cdio b -> Cdio a #

Alternative Cdio Source #

empty fails with CdioEmpty.

Instance details

Defined in Sound.Libcdio.Types.Cdio

Methods

empty :: Cdio a #

(<|>) :: Cdio a -> Cdio a -> Cdio a #

some :: Cdio a -> Cdio [a] #

many :: Cdio a -> Cdio [a] #

LibcdioLogger Cdio Source # 
Instance details

Defined in Sound.Libcdio.Types.Cdio

MonadError CdioError Cdio Source # 
Instance details

Defined in Sound.Libcdio.Types.Cdio

Methods

throwError :: CdioError -> Cdio a #

catchError :: Cdio a -> (CdioError -> Cdio a) -> Cdio a #

data CdioError Source #

Associates a well-typed error with human-readable context information.

Instances

Instances details
Eq CdioError Source # 
Instance details

Defined in Sound.Libcdio.Types.Cdio

Read CdioError Source # 
Instance details

Defined in Sound.Libcdio.Types.Cdio

Show CdioError Source # 
Instance details

Defined in Sound.Libcdio.Types.Cdio

MonadError CdioError Cdio Source # 
Instance details

Defined in Sound.Libcdio.Types.Cdio

Methods

throwError :: CdioError -> Cdio a #

catchError :: Cdio a -> (CdioError -> Cdio a) -> Cdio a #

data CdioErrorType Source #

Potential situations which may cause a computation to fail.

Constructors

DriverError

A requested operation failed for some unknown reason, or the operating system doesn't support the DriverId in use.

BadParameter

Some value passed to a requested operation was rejected as nonsensical or otherwise breaking the value-level invariants.

NotPermitted

The ability to perform a requested operation has been restricted (e.g., the user doesn't have permission to access the disc drive).

SessionClosed

The underlying library closed the Cdio session prematurely.

Unsupported

A requested operation isn't available with driver used by the Cdio session. Refer to capabilities and deviceCapabilities to reduce these.

CdioEmpty

empty was called and no better alternative was encountered.

FreeformCdioError Text

Escape hatch from structured typing to allow user-specified (and user-triggered) errors.

data SessionArg Source #

Metadata about the session in the form of (often freeform) text, providing a type-safe index to getArg. Note that not every driver type supports every item.

The key "access-mode" is handled separately by getAccessMode, to better reflect its restricted outputs.

Constructors

Source 
Cue 
ScsiTuple 
MmcSupported 

Instances

Instances details
Bounded SessionArg Source # 
Instance details

Defined in Foreign.Libcdio.Device

Enum SessionArg Source # 
Instance details

Defined in Foreign.Libcdio.Device

Eq SessionArg Source # 
Instance details

Defined in Foreign.Libcdio.Device

Ord SessionArg Source # 
Instance details

Defined in Foreign.Libcdio.Device

Read SessionArg Source # 
Instance details

Defined in Foreign.Libcdio.Device

Show SessionArg Source # 
Instance details

Defined in Foreign.Libcdio.Device

Storable SessionArg Source # 
Instance details

Defined in Foreign.Libcdio.Device

data AccessMode Source #

Which instruction set should be used to communicate with the driver, providing a type-safe input for session initialization. Note that not every driver type supports every item.

Constructors

Image 
Ioctl

The DriverLinux and DriverBsdi drivers use a different internal representation for Ioctl_.

Ioctl_

The DriverFreeBsd and DriverWin32 drivers use a different internal representation for Ioctl.

Aspi 
Atapi 
Cam 
Scsi 
ReadCd 
Read10 
MmcReadWrite 
MmcReadWriteExclusive 

Instances

Instances details
Bounded AccessMode Source # 
Instance details

Defined in Foreign.Libcdio.Device

Enum AccessMode Source # 
Instance details

Defined in Foreign.Libcdio.Device

Eq AccessMode Source # 
Instance details

Defined in Foreign.Libcdio.Device

Ord AccessMode Source # 
Instance details

Defined in Foreign.Libcdio.Device

Read AccessMode Source # 
Instance details

Defined in Foreign.Libcdio.Device

Show AccessMode Source # 
Instance details

Defined in Foreign.Libcdio.Device

Storable AccessMode Source # 
Instance details

Defined in Foreign.Libcdio.Device

Version

data Version #

A Version represents the version of a software entity.

An instance of Eq is provided, which implements exact equality modulo reordering of the tags in the versionTags field.

An instance of Ord is also provided, which gives lexicographic ordering on the versionBranch fields (i.e. 2.1 > 2.0, 1.2.3 > 1.2.2, etc.). This is expected to be sufficient for many uses, but note that you may need to use a more specific ordering for your versioning scheme. For example, some versioning schemes may include pre-releases which have tags "pre1", "pre2", and so on, and these would need to be taken into account when determining ordering. In some cases, date ordering may be more appropriate, so the application would have to look for date tags in the versionTags field and compare those. The bottom line is, don't always assume that compare and other Ord operations are the right thing for every Version.

Similarly, concrete representations of versions may differ. One possible concrete representation is provided (see showVersion and parseVersion), but depending on the application a different concrete representation may be more appropriate.

Instances

Instances details
IsList Version

Since: base-4.8.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item Version #

Eq Version

Since: base-2.1

Instance details

Defined in Data.Version

Methods

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

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

Ord Version

Since: base-2.1

Instance details

Defined in Data.Version

Read Version

Since: base-2.1

Instance details

Defined in Data.Version

Show Version

Since: base-2.1

Instance details

Defined in Data.Version

Generic Version

Since: base-4.9.0.0

Instance details

Defined in Data.Version

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

type Rep Version 
Instance details

Defined in Data.Version

type Rep Version = D1 ('MetaData "Version" "Data.Version" "base" 'False) (C1 ('MetaCons "Version" 'PrefixI 'True) (S1 ('MetaSel ('Just "versionBranch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int]) :*: S1 ('MetaSel ('Just "versionTags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])))
type Item Version 
Instance details

Defined in GHC.Exts

makeVersion :: [Int] -> Version #

Construct tag-less Version

Since: base-4.8.0.0

Evaluation

open Source #

Arguments

:: Maybe FilePath 
-> Bool

Whether the disc should be ejected after the computation.

-> Cdio a 
-> IO (Either CdioError a) 

Open a session to read data from the disc drive/image at the given location. If passed Nothing instead, uses the path considered "default"; on operating systems with a concept of numbered devices (e.g., Window's D: drive, FreeBSD's /dev/cd0) will usually return the first such device found to be suitable.

openMode Source #

Arguments

:: AccessMode 
-> Maybe FilePath 
-> Bool

Whether the disc should be ejected after the computation.

-> Cdio a 
-> IO (Either CdioError a) 

Open a session to read data from the disc drive/image at the given location, using a specific instruction set. If passed Nothing instead, uses the path considered "default"; on operating systems with a concept of numbered devices (e.g., Window's D: drive, FreeBSD's /dev/cd0) will usually return the first such device found to be suitable.

runCdio :: Cdio -> Cdio a -> IO (Either CdioError a) Source #

Use a C-style Foreign.Libcdio.Cdio object as the base to run a Haskell-style Sound.Libcdio.Cdio computation.

Note that some invariants of the monadic interface may not work as expected when used with the mutable objects.

getArg :: SessionArg -> Cdio (Maybe Text) Source #

Retrieve the session value associated with the given key. The particular case of "access-mode" is instead handled by getAccessMode.

getAccessMode :: Cdio (Maybe AccessMode) Source #

Check what instruction set is in use for reading the disc. Other session values are handled by getArg.

Library data

cdioVersionString :: String Source #

The value of the preprocessor macro CDIO_VERSION, listing both the SemVar-style version of libcdio and the full architecture of the system which compiled it (e.g. 2.0.0 x86_64-pc-linux-gnu).

libcdioVersionNum :: Version Source #

The value of the preprocessor macro LIBCDIO_VERSION_NUM, containing a numeric representation of the version suitable for arithmetic testing.

apiVersion :: Word Source #

The value of the preprocessor macro CDIO_API_VERSION, containing a single, monotonically increasing constant representing changes to the public interface. However, as it's somewhat unclear what changes warrant bumping this number, it is typically better to use libcdioVersionNum instead.