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

Foreign.Libcdio.Util

Description

Most functions defined by the C header either encapsulate math to perform on an object or the system state, or edit Strings in some (barring allocations) pure manner, including a few with general utility rather than being specific to libcdio. However, most are also restricted to internal use, and not provided as symbols exported by the library itself; those internal functions are still present in the Haskell source as well, for anyone interested. As such, this module and the functions it provides should rarely need to be used.

util.h

Defines

  • CDIO_FREE_IF_NOT_NULL (removed; Haskell handles its own memory management)
  • CLAMP (removed; preprocessor logic isn't required in Haskell)
  • IN (removed; preprocessor logic isn't required in Haskell)
  • MAX (removed; preprocessor logic isn't required in Haskell)
  • MAX (removed; preprocessor logic isn't required in Haskell)

Symbols

  • _cdio_strfreev (removed; list is automatically freed)
  • _cdio_strsplit -> strsplit
  • cdio_from_bcd8 -> fromBcd8
  • cdio_realpath -> realpath
  • cdio_to_bcd8 -> toBcd8
Synopsis

Documentation

data Bcd Source #

A bitwise encoding where the lower four bits encode a number modulo 10, and the upper encode the same divided by 10.

Instances

Instances details
Bounded Bcd Source #
>>> map fromBcd8 [minBound, maxBound]
[0, 159]
Instance details

Defined in Foreign.Libcdio.Util

Methods

minBound :: Bcd #

maxBound :: Bcd #

Enum Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Methods

succ :: Bcd -> Bcd #

pred :: Bcd -> Bcd #

toEnum :: Int -> Bcd #

fromEnum :: Bcd -> Int #

enumFrom :: Bcd -> [Bcd] #

enumFromThen :: Bcd -> Bcd -> [Bcd] #

enumFromTo :: Bcd -> Bcd -> [Bcd] #

enumFromThenTo :: Bcd -> Bcd -> Bcd -> [Bcd] #

Eq Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Methods

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

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

Integral Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Methods

quot :: Bcd -> Bcd -> Bcd #

rem :: Bcd -> Bcd -> Bcd #

div :: Bcd -> Bcd -> Bcd #

mod :: Bcd -> Bcd -> Bcd #

quotRem :: Bcd -> Bcd -> (Bcd, Bcd) #

divMod :: Bcd -> Bcd -> (Bcd, Bcd) #

toInteger :: Bcd -> Integer #

Num Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Methods

(+) :: Bcd -> Bcd -> Bcd #

(-) :: Bcd -> Bcd -> Bcd #

(*) :: Bcd -> Bcd -> Bcd #

negate :: Bcd -> Bcd #

abs :: Bcd -> Bcd #

signum :: Bcd -> Bcd #

fromInteger :: Integer -> Bcd #

Ord Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Methods

compare :: Bcd -> Bcd -> Ordering #

(<) :: Bcd -> Bcd -> Bool #

(<=) :: Bcd -> Bcd -> Bool #

(>) :: Bcd -> Bcd -> Bool #

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

max :: Bcd -> Bcd -> Bcd #

min :: Bcd -> Bcd -> Bcd #

Read Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Real Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Methods

toRational :: Bcd -> Rational #

Show Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Methods

showsPrec :: Int -> Bcd -> ShowS #

show :: Bcd -> String #

showList :: [Bcd] -> ShowS #

Ix Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Methods

range :: (Bcd, Bcd) -> [Bcd] #

index :: (Bcd, Bcd) -> Bcd -> Int #

unsafeIndex :: (Bcd, Bcd) -> Bcd -> Int #

inRange :: (Bcd, Bcd) -> Bcd -> Bool #

rangeSize :: (Bcd, Bcd) -> Int #

unsafeRangeSize :: (Bcd, Bcd) -> Int #

PrintfArg Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Storable Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Methods

sizeOf :: Bcd -> Int #

alignment :: Bcd -> Int #

peekElemOff :: Ptr Bcd -> Int -> IO Bcd #

pokeElemOff :: Ptr Bcd -> Int -> Bcd -> IO () #

peekByteOff :: Ptr b -> Int -> IO Bcd #

pokeByteOff :: Ptr b -> Int -> Bcd -> IO () #

peek :: Ptr Bcd -> IO Bcd #

poke :: Ptr Bcd -> Bcd -> IO () #

toBcd8 :: Word -> Bcd Source #

Encode a number according to the libcdio BCD encoding. If the value is greater than maxBound :: Bcd, it wraps back around to 0.

fromBcd8 :: Bcd -> Word Source #

Decode a number in the libcdio BCD encoding.

strsplit :: String -> Char -> IO [String] Source #

Return the substrings between a given delimiter, dropping any empty ones.

The Haskell repositories provide this via split.

strsplit str d == Data.List.Split.wordsBy (== d) str

realpath :: String -> IO (Maybe String) Source #

Same as POSIX.1-2001 realpath, if the system provides it. If not, libcdio's "poor-man's simulation" of its behavior.

The Haskell repositories provide a similar alternative in System.Directory.canonicalizePath from directory.