{-# LANGUAGE CPP #-} {-# LANGUAGE ForeignFunctionInterface #-} {-# OPTIONS_HADDOCK not-home #-} #include "cdio/compat/version.h" {-| Description: c2hs-generated types for re-export by more relevant modules. Copyright: (c) 2018-2021 Sam May License: GPL-3.0-or-later Maintainer: ag@eitilt.life Stability: stable Portability: non-portable (requires libcdio) Many of the enums in the C library are large things with explicit numeric representation, and maintaining them in pure Haskell would be a nightmare. On the other hand, keeping them in their natural modules means those can never be analyzed for coverage. Splitting the former out here allows the best of both worlds — losing typeclass coverage reports on the enums is a small price. Just note that since this isn't exposed, it /can not/ be used directly by any other c2hs-generated modules. -} module Foreign.Libcdio.Types.Enums ( -- * "Foreign.Libcdio.CdText" CField , Field ( .. ) , CGenre , Genre ( .. ) , CLanguage , Language ( .. ) -- * "Foreign.Libcdio.CdTypes" , Filesystem_ ( .. ) , FilesystemClass ( .. ) -- * "Foreign.Libcdio.Device" , DriveCapabilityMisc ( .. ) , DriveCapabilityRead ( .. ) , DriveCapabilityWrite ( .. ) , CDriverId , DriverId ( .. ) , CDriverReturnCode , DriverReturnCode ( .. ) -- * "Foreign.Libcdio.Disc" , CDiscMode , DiscMode ( .. ) -- * "Foreign.Libcdio.Logging" , CLogLevel , LogLevel ( .. ) -- * "Foreign.Libcdio.Read" , ReadMode ( .. ) , Whence ( .. ) -- * "Foreign.Libcdio.Sector" , SubchannelData ( .. ) , Flag ( .. ) -- * "Foreign.Libcdio.Track" , CTrackFormat , TrackFormat ( .. ) , TrackFlagStatus ( .. ) ) where import Data.Ix ( Ix ) #include "cdio/compat/cdtext.h" -- | The underlying type of the C @cdtext_field_t@, i.e. 'Field'. type CField = {#type cdtext_field_t#} -- | Descriptions of the content contained in an associated CD Text field. {#enum cdtext_field_t as Field { underscoreToCase , CDTEXT_FIELD_DISCID as DiscId , CDTEXT_FIELD_GENRE as GenreName } omit ( CDTEXT_FIELD_INVALID ) with prefix = "cdtext_field" deriving ( Eq, Show, Read, Ord, Bounded ) #} -- | The underlying type of the C @cdtext_genre_t@, i.e. 'Genre'. type CGenre = {#type cdtext_genre_t#} -- | Genres recognized in the CD Text standard. {#enum cdtext_genre_t as Genre { underscoreToCase , CDTEXT_GENRE_ADULT_CONTEMP as AdultContemporary , CDTEXT_GENRE_CHRIST_CONTEMP as ChristianContemporary , CDTEXT_GENRE_HIPHOP as HipHop , CDTEXT_GENRE_LATIN as LatinMusic , CDTEXT_GENRE_NEWAGE as NewAge , CDTEXT_GENRE_RYTHMANDBLUES as RhythmAndBlues , CDTEXT_GENRE_SOUNDEFFECTS as SoundEffects } omit ( CDTEXT_GENRE_UNUSED ) with prefix = "cdtext_genre" deriving ( Eq, Show, Read, Ord, Bounded ) #} -- | The underlying type of the C @cdtext_lang_t@, i.e. 'Language'. type CLanguage = {#type cdtext_lang_t#} -- | Written languages recognized in the CD Text standard. #if LIBCDIO_SINCE_VERSION_2_1 {#enum cdtext_lang_t as Language { underscoreToCase , CDTEXT_LANGUAGE_UNKNOWN as UnknownLanguage , CDTEXT_LANGUAGE_SERBO_CROAT as SerboCroatian , CDTEXT_LANGUAGE_SRANANTONGO as SrananTongo } omit ( CDTEXT_LANGUAGE_INVALID , CDTEXT_LANGUAGE_BLOCK_UNUSED ) with prefix = "cdtext_language" deriving ( Eq, Show, Read, Ord, Bounded ) #} #else {#enum cdtext_lang_t as Language { underscoreToCase , CDTEXT_LANGUAGE_UNKNOWN as UnknownLanguage , CDTEXT_LANGUAGE_SERBO_CROAT as SerboCroatian , CDTEXT_LANGUAGE_SRANANTONGO as SrananTongo } with prefix = "cdtext_language" deriving ( Eq, Show, Read, Ord, Bounded ) #} #endif #include "cdio/compat/cd_types.h" -- | Internal filesystem type, including ones that conflate -- 'Foreign.Libcdio.CdTypes.Filesystem' with -- 'Foreign.Libcdio.CdTypes.IsoAnalysis'; these are separated in -- 'Foreign.Libcdio.CdTypes.cdType'. {#enum cdio_fs_t as Filesystem_ {underscoreToCase} with prefix = "cdio" deriving ( Eq, Show, Read, Ord, Bounded ) #} -- | Higher-level descriptions of discs/filesystems. {#enum fs_cap_t as FilesystemClass { underscoreToCase , FS_ANAL_CDTV as CommodoreCdtv , FS_ANAL_VIDEOCD as VideoCd , FS_ANAL_ROCKRIDGE as RockRidge , FS_ANAL_SVCD as SuperVideoCd , FS_ANAL_CVD as ChoijiVideoCd , FS_ANAL_XISO as XboxIsoClass , FS_ANAL_ISO9660_ANY as Iso9660Class } with prefix = "fs_anal" deriving ( Eq, Show, Read, Ord, Bounded, Ix ) #} #include "cdio/compat/device.h" -- | Miscellaneous properties a device can have, typically describing hardware -- features, which are collected in 'Foreign.Libcdio.Device.DriveMiscCaps'. {#enum cdio_drive_cap_misc_t as DriveCapabilityMisc { underscoreToCase } omit ( CDIO_DRIVE_CAP_ERROR , CDIO_DRIVE_CAP_UNKNOWN ) with prefix = "cdio_drive_cap" deriving ( Eq, Show, Read, Ord, Bounded, Ix ) #} -- | Read-related properties a device can have, mostly describing what formats -- it understands, which are collected in 'Foreign.Libcdio.Device.DriveReadCaps'. -- -- The difference between 'ReadAnalogAudio' and 'ReadDigitalAudio' is poorly -- documented in libcdio; they have been named here according to their assumed -- meanings (see ), but that pattern -- may not be completely accurate. {#enum cdio_drive_cap_read_t as DriveCapabilityRead { underscoreToCase , CDIO_DRIVE_CAP_READ_AUDIO as ReadAnalogAudio , CDIO_DRIVE_CAP_READ_CD_DA as ReadDigitalAudio , CDIO_DRIVE_CAP_READ_CD_G as ReadCdGraphics , CDIO_DRIVE_CAP_READ_CD_R as ReadCdRecordable , CDIO_DRIVE_CAP_READ_CD_RW as ReadCdReWritable , CDIO_DRIVE_CAP_READ_DVD_R as ReadDvdRecordable , CDIO_DRIVE_CAP_READ_DVD_PR as ReadDvdPlusRecordable , CDIO_DRIVE_CAP_READ_DVD_RW as ReadDvdReWritable , CDIO_DRIVE_CAP_READ_DVD_RPW as ReadDvdPlusReWritable , CDIO_DRIVE_CAP_READ_C2_ERRS as ReadC2ErrorCorrection } with prefix = "cdio_drive_cap" deriving ( Eq, Show, Read, Ord, Bounded, Ix ) #} -- | Write-related properties a device can have, mostly describing what formats -- it can burn, which are collected in 'Foreign.Libcdio.Device.DriveWriteCaps'. {#enum cdio_drive_cap_write_t as DriveCapabilityWrite { underscoreToCase , CDIO_DRIVE_CAP_WRITE_CD_R as WriteCdRecordable , CDIO_DRIVE_CAP_WRITE_CD_RW as WriteCdReWritable , CDIO_DRIVE_CAP_WRITE_DVD_R as WriteDvdRecordable , CDIO_DRIVE_CAP_WRITE_DVD_PR as WriteDvdPlusRecordable , CDIO_DRIVE_CAP_WRITE_DVD_RW as WriteDvdReWritable , CDIO_DRIVE_CAP_WRITE_DVD_RPW as WriteDvdPlusReWritable } omit ( CDIO_DRIVE_CAP_WRITE_CD , CDIO_DRIVE_CAP_WRITE_DVD , CDIO_DRIVE_CAP_WRITE ) with prefix = "cdio_drive_cap" deriving ( Eq, Show, Read, Ord, Bounded, Ix ) #} {- Barely even used internally. -- | Different types of device that can be read, which are collected in -- 'Foreign.Libcdio.Device.SrcCategories'. {#enum cdio_src_category_mask_t as SrcCategoryMask {underscoreToCase} with prefix = "cdio" deriving ( Eq, Show, Read, Ord, Bounded, Ix ) #} -} -- | The underlying type of the C @driver_id_t@, i.e. 'DriverId'. type CDriverId = {#type driver_id_t#} -- | Devices or file types supported by the library. {#enum define DriverId { DRIVER_UNKNOWN as DriverUnknown , DRIVER_AIX as DriverAix , DRIVER_BSDI as DriverBsdi , DRIVER_FREEBSD as DriverFreeBsd , DRIVER_NETBSD as DriverNetBsd , DRIVER_LINUX as DriverLinux , DRIVER_SOLARIS as DriverSolaris , DRIVER_OS2 as DriverOs2 , DRIVER_OSX as DriverOsX , DRIVER_WIN32 as DriverWin32 , DRIVER_CDRDAO as DriverCdrDao , DRIVER_BINCUE as DriverBinCue , DRIVER_NRG as DriverNrg , DRIVER_DEVICE as DriverDevice } deriving ( Eq, Show, Read, Ord, Bounded ) #} -- | The underlying type of the C @driver_return_code_t@, i.e. -- 'DriverReturnCode'. type CDriverReturnCode = {#type driver_return_code_t#} -- | Descriptions of various error states which may be returned by driver -- functions. {#enum driver_return_code_t as DriverReturnCode { underscoreToCase , DRIVER_OP_ERROR as DriverError , DRIVER_OP_UNINIT as Uninitialized } with prefix = "driver_op" deriving ( Eq, Show, Read, Ord, Bounded ) #} #include "cdio/compat/disc.h" -- | The underlying type of the C @discmode_t@, i.e. 'DiscMode'. type CDiscMode = {#type discmode_t#} -- | Different types of disc. Modes are combined from several sources, along -- with some libcdio-specific additions: -- -- * MMC-5 6.33.3.13 (Send CUESHEET) -- * MMC-5 Table 400 "DVD Book" -- * GNU/Linux @\/usr\/include\/linux\/cdrom.h@ -- -- As C2HS and Haddock don't yet interact well enough to document Enum fields, -- some of the less obvious mappings include: -- -- * 'DataCdMode': CD-ROM form 1 -- * 'MixedCdMode': some combination of 'AudioCdMode', 'DataCdMode', and 'XaCdMode' -- * 'DvdPlusRecordableMode': DVD+R -- * 'DvdPlusReWritableMode': DVD+RW {#enum discmode_t as DiscMode { underscoreToCase , CDIO_DISC_MODE_CD_DA as AudioCdMode , CDIO_DISC_MODE_CD_DATA as DataCdMode , CDIO_DISC_MODE_CD_XA as XaCdMode , CDIO_DISC_MODE_CD_MIXED as MixedCdMode , CDIO_DISC_MODE_DVD_ROM as DvdRomMode , CDIO_DISC_MODE_DVD_RAM as DvdRamMode , CDIO_DISC_MODE_DVD_R as DvdRecordableMode , CDIO_DISC_MODE_DVD_RW as DvdReWritableMode , CDIO_DISC_MODE_HD_DVD_ROM as HighDefinitionDvdRomMode , CDIO_DISC_MODE_HD_DVD_RAM as HighDefinitionDvdRamMode , CDIO_DISC_MODE_HD_DVD_R as HighDefinitionDvdRecordableMode , CDIO_DISC_MODE_DVD_PR as DvdPlusRecordableMode , CDIO_DISC_MODE_DVD_PRW as DvdPlusReWritableMode , CDIO_DISC_MODE_DVD_PR_DL as DoubleLayerDvdPlusRecordableMode , CDIO_DISC_MODE_DVD_PRW_DL as DoubleLayerDvdPlusReWritableMode , CDIO_DISC_MODE_DVD_OTHER as OtherDvdMode , CDIO_DISC_MODE_NO_INFO as NoModeInfo , CDIO_DISC_MODE_CD_I as CdIMode } omit ( CDIO_DISC_MODE_ERROR ) with prefix = "cdio_disc_mode" deriving ( Eq, Show, Read, Ord, Bounded ) #} #include "cdio/compat/logging.h" -- | The underlying type of the C @cdio_log_level_t@, i.e. 'LogLevel'. type CLogLevel = {#type cdio_log_level_t#} -- | How much detail should be recorded in the logs. {#enum cdio_log_level_t as LogLevel {underscoreToCase} with prefix = "cdio" deriving ( Eq, Show, Read, Ord, Bounded ) #} #include "cdio/compat/read.h" -- | How data is laid out on a disc. {#enum cdio_read_mode_t as ReadMode { underscoreToCase , CDIO_READ_MODE_AUDIO as AudioMode , CDIO_READ_MODE_M1F1 as Mode1Form1 , CDIO_READ_MODE_M1F2 as Mode1Form2 , CDIO_READ_MODE_M2F1 as Mode2Form1 , CDIO_READ_MODE_M2F2 as Mode2Form2 } with prefix = "cdio_read_mode" deriving ( Eq, Show, Read, Ord, Bounded ) #} -- | Which location an offset passed to 'Foreign.Libcdio.Read.seek' should be -- based on. {#enum whence_t as Whence {underscoreToCase} with prefix = "whence" deriving ( Eq, Show, Read, Ord, Bounded ) #} #include "cdio/compat/sector.h" -- | Types of information stored on disc subchannels. {#enum cdio_subchannel as SubchannelData { underscoreToCase , CDIO_SUBCHANNEL_SUBQ_DATA as QChannelData } with prefix = "cdio_subchannel" deriving ( Eq, Show, Read, Ord, Bounded ) #} -- | Metadata describing the layout or type of data on a track. {#enum flag_t as Flag { underscoreToCase , DATA as DataTrack , SCMS as SerialCopyManagement } omit ( NONE ) deriving ( Eq, Show, Read, Ord, Bounded, Ix ) #} {- Not actually an 'Enum', but rather shortcuts for basic multiplications. -- | How many sectors are contained in various lengths of disc. {#enum cdio_cd_minutes_sectors as CdMinutesSectors {underscoreToCase} with prefix = "cdio" deriving ( Eq, Show, Read, Ord, Bounded ) #} -} #include "cdio/compat/track.h" -- | The underlying type of the C @track_format_t@, i.e. 'TrackFormat'. type CTrackFormat = {#type track_format_t#} -- | The structure in which data is stored on a segment of a disc. The exact -- representation of these values is discussed in "Foreign.Libcdio.Sector". {#enum track_format_t as TrackFormat { underscoreToCase , TRACK_FORMAT_CDI as FormatCdI , TRACK_FORMAT_PSX as FormatPlaystation } omit ( TRACK_FORMAT_ERROR ) with prefix = "track" deriving ( Eq, Show, Read, Ord, Bounded ) #} {- Barely even used internally. -- | The block format in which the data is saved in a track on disc. {#enum trackmode_t as TrackMode {underscoreToCase} deriving ( Eq, Show, Read, Ord, Bounded ) #} -} -- | Whether a track has a particular flag specified. {#enum track_flag_t as TrackFlagStatus {underscoreToCase} with prefix = "cdio_track" deriving ( Eq, Show, Read, Ord, Bounded ) #} #include "cdio/util.h" {- Similar semantics from 'Maybe Bool'. -- | A version of 'Bool' which also provides a third, non-definitive state. {#enum bool_3way_t as Bool3 {nope as No, yep as Yes, dunno as Unknown} deriving ( Eq, Show, Read, Ix ) #} -- Need to explicitly instance Ord and Bounded as the below is the logical -- order, but @dunno@ is assigned @3@ in the C code. instance Ord Bool3 where No <= _ = True _ <= Yes = True Unknown <= Unknown = True _ <= _ = False instance Bounded Bool3 where minBound = No maxBound = Yes -- Needs: Bits, FiniteBits, Generic, Rep, Data, Storable for parity with Bool -}