| Safe Haskell | None |
|---|---|
| Language | GHC2021 |
Telescope.Fits.Types
Synopsis
- data Fits = Fits {
- primaryHDU :: PrimaryHDU
- extensions :: [Extension]
- data PrimaryHDU = PrimaryHDU {}
- data ImageHDU = ImageHDU {}
- data BinTableHDU = BinTableHDU {}
- data DataArray = DataArray {}
- data Extension
- type Axis = Int
- newtype Axes (a :: Major) = Axes {}
- data Major
- data BitPix
- bitPixBits :: BitPix -> Int
- newtype Header = Header {
- _records :: [HeaderRecord]
- getKeywords :: Header -> [KeywordRecord]
- data HeaderRecord
- data KeywordRecord = KeywordRecord {}
- data Value
- data LogicalConstant
- hduBlockSize :: Int
- emptyDataArray :: DataArray
- class IsBitPix (a :: k) where
Documentation
Constructors
| Fits | |
Fields
| |
data PrimaryHDU Source #
Constructors
| PrimaryHDU | |
Instances
| Show PrimaryHDU Source # | |
Defined in Telescope.Fits.Types Methods showsPrec :: Int -> PrimaryHDU -> ShowS # show :: PrimaryHDU -> String # showList :: [PrimaryHDU] -> ShowS # | |
data BinTableHDU Source #
Constructors
| BinTableHDU | |
Instances
| Show BinTableHDU Source # | |
Defined in Telescope.Fits.Types Methods showsPrec :: Int -> BinTableHDU -> ShowS # show :: BinTableHDU -> String # showList :: [BinTableHDU] -> ShowS # | |
Raw HDU Data. See DataArray
Constructors
| Image ImageHDU | |
| BinTable BinTableHDU |
bitPixBits :: BitPix -> Int Source #
The header part of the HDU is vital carrying not only authorship
metadata, but also specifying how to make sense of the binary payload
that starts 2,880 bytes after the start of the HeaderData.
Constructors
| Header | |
Fields
| |
getKeywords :: Header -> [KeywordRecord] #
Return all KeywordRecords from the header, filtering out full-line comments and blanks
data HeaderRecord #
Headers contain lines that are any of the following
KEYWORD = VALUE / inline comment COMMENT full line comment (blank)
Constructors
| Keyword KeywordRecord | |
| Comment Text | |
| BlankLine |
Instances
| Show HeaderRecord | |
Defined in Data.Fits Methods showsPrec :: Int -> HeaderRecord -> ShowS # show :: HeaderRecord -> String # showList :: [HeaderRecord] -> ShowS # | |
| Eq HeaderRecord | |
Defined in Data.Fits | |
data KeywordRecord #
A single 80 character header keyword line of the form: KEYWORD = VALUE / comment KEYWORD=VALUE
Instances
| Show KeywordRecord | |
Defined in Data.Fits Methods showsPrec :: Int -> KeywordRecord -> ShowS # show :: KeywordRecord -> String # showList :: [KeywordRecord] -> ShowS # | |
| Eq KeywordRecord | |
Defined in Data.Fits Methods (==) :: KeywordRecord -> KeywordRecord -> Bool # (/=) :: KeywordRecord -> KeywordRecord -> Bool # | |
Value datatype for discriminating valid FITS KEYWORD=VALUE types in an HDU.
data LogicalConstant #
Instances
| Show LogicalConstant | |
Defined in Data.Fits Methods showsPrec :: Int -> LogicalConstant -> ShowS # show :: LogicalConstant -> String # showList :: [LogicalConstant] -> ShowS # | |
| Eq LogicalConstant | |
Defined in Data.Fits Methods (==) :: LogicalConstant -> LogicalConstant -> Bool # (/=) :: LogicalConstant -> LogicalConstant -> Bool # | |
hduBlockSize :: Int #
The size of an HDU block is fixed at thirty-six eighty byte words. In other words 2,880 bytes. These blocks are padded with zeros to this boundary.
class IsBitPix (a :: k) where Source #
Instances
| IsBitPix Int16 Source # | |
Defined in Telescope.Fits.Types | |
| IsBitPix Int32 Source # | |
Defined in Telescope.Fits.Types | |
| IsBitPix Int64 Source # | |
Defined in Telescope.Fits.Types | |
| IsBitPix Int8 Source # | |
Defined in Telescope.Fits.Types | |
| IsBitPix Double Source # | |
Defined in Telescope.Fits.Types | |
| IsBitPix Float Source # | |
Defined in Telescope.Fits.Types | |