Copyright | (c) Zac Slade 2023 |
---|---|
License | BSD2 |
Maintainer | krakrjak@gmail.com |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Definitions for the data types needed to parse an HDU in a FITS block.
Synopsis
- parsePix :: Int -> BitPixFormat -> ByteString -> IO [Pix]
- pixsUnwrapI :: BitPixFormat -> [Pix] -> [Int]
- pixsUnwrapD :: BitPixFormat -> [Pix] -> [Double]
- data HeaderDataUnit = HeaderDataUnit {}
- dimensions :: Lens' HeaderDataUnit Dimensions
- header :: Lens' HeaderDataUnit Header
- extension :: Lens' HeaderDataUnit Extension
- mainData :: Lens' HeaderDataUnit ByteString
- data Pix
- newtype Header = Header {}
- keywords :: Lens' Header (Map Keyword Value)
- data Extension
- lookup :: Keyword -> Header -> Maybe Value
- newtype Keyword = Keyword Text
- data Value
- toInt :: Value -> Maybe Int
- toFloat :: Value -> Maybe Float
- toText :: Value -> Maybe Text
- data LogicalConstant
- data Dimensions = Dimensions {
- _bitpix :: BitPixFormat
- _axes :: Axes
- axes :: Lens' Dimensions Axes
- bitpix :: Lens' Dimensions BitPixFormat
- newtype Comment = Comment Text
- data SimpleFormat
- data BitPixFormat
- type Axes = [Int]
- isBitPixInt :: BitPixFormat -> Bool
- isBitPixFloat :: BitPixFormat -> Bool
- bitPixToWordSize :: BitPixFormat -> Int
- bitPixToByteSize :: BitPixFormat -> Int
- pixDimsByCol :: Axes -> [Int]
- pixDimsByRow :: Axes -> [Int]
- hduRecordLength :: Int
- hduMaxRecords :: Int
- hduBlockSize :: Int
Data payload functions
parsePix :: Int -> BitPixFormat -> ByteString -> IO [Pix] Source #
This is the main low-level function which parses the data portion of an HDU. You need and element count, a format and a bytestring. The resulting list is produced in column-row major order as specified in the standard.
pixsUnwrapI :: BitPixFormat -> [Pix] -> [Int] Source #
Remove the Pix wrapper for integer Pix
lists.
pixsUnwrapD :: BitPixFormat -> [Pix] -> [Double] Source #
Main data types
data HeaderDataUnit Source #
The HeaderDataUnit
is the full HDU. Both the header information is
encoded alongside the data payload.
HeaderDataUnit | |
|
Instances
Show HeaderDataUnit Source # | |
Defined in Data.Fits showsPrec :: Int -> HeaderDataUnit -> ShowS # show :: HeaderDataUnit -> String # showList :: [HeaderDataUnit] -> ShowS # |
Following BitPixFormat
we have a tag for integer and floating point
values. We box them up to ease parsing.
Header Data Types
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
.
Primary | Any header data unit can use the primary format. The first MUST be Primary. This is equivalent to having no extension |
Image | An encoded image. PCOUNT and GCOUNT are required but irrelevant |
BinTable | A Binary table. PCOUNT is the number of bytes that follow the data
in the |
|
The Text
wrapper for HDU the keyword data for lines of the form:
KEYWORD=VALUE
Value
datatype for discriminating valid FITS KEYWORD=VALUE types in an HDU.
data LogicalConstant Source #
Instances
Show LogicalConstant Source # | |
Defined in Data.Fits showsPrec :: Int -> LogicalConstant -> ShowS # show :: LogicalConstant -> String # showList :: [LogicalConstant] -> ShowS # | |
Eq LogicalConstant Source # | |
Defined in Data.Fits (==) :: LogicalConstant -> LogicalConstant -> Bool # (/=) :: LogicalConstant -> LogicalConstant -> Bool # |
data Dimensions Source #
When we load a header, we parse the BITPIX and NAXIS(N) keywords so we - can know how long the data array is
Dimensions | |
|
Instances
Show Dimensions Source # | |
Defined in Data.Fits showsPrec :: Int -> Dimensions -> ShowS # show :: Dimensions -> String # showList :: [Dimensions] -> ShowS # | |
Eq Dimensions Source # | |
Defined in Data.Fits (==) :: Dimensions -> Dimensions -> Bool # (/=) :: Dimensions -> Dimensions -> Bool # |
data SimpleFormat Source #
The standard defines two possible values for the SIMPLE keyword, T and
F. The T refers to a Conformant
format while F refers to
a NonConformant
format. At this time only the Conformant
, T, format
is supported.
Instances
Show SimpleFormat Source # | Value of SIMPLE=T in the header. supported NonConformat ^ Value of SIMPLE=F in the header. unsupported |
Defined in Data.Fits showsPrec :: Int -> SimpleFormat -> ShowS # show :: SimpleFormat -> String # showList :: [SimpleFormat] -> ShowS # | |
Eq SimpleFormat Source # | |
Defined in Data.Fits (==) :: SimpleFormat -> SimpleFormat -> Bool # (/=) :: SimpleFormat -> SimpleFormat -> Bool # |
data BitPixFormat Source #
The BitPixFormat
is the nitty gritty of how the Axis
data is layed
out in the file. The standard recognizes six formats: unsigned 8 bit
integer, two's complement binary integers at 16, 32, and 64 bits along
with 32 and 64 bit IEEE floating point formats.
EightBitInt | BITPIX = 8; unsigned binary integer of 8 bits |
SixteenBitInt | BITPIX = 16; two's complement binary integer of 16 bits |
ThirtyTwoBitInt | BITPIX = 32; two's complement binary integer of 32 bits |
SixtyFourBitInt | BITPIX = 64; two's complement binary integer of 64 bits |
ThirtyTwoBitFloat | BITPIX = -32; IEEE single precision floating point of 32 bits |
SixtyFourBitFloat | BITPIX = -64; IEEE double precision floating point of 64 bits |
Instances
Show BitPixFormat Source # | |
Defined in Data.Fits showsPrec :: Int -> BitPixFormat -> ShowS # show :: BitPixFormat -> String # showList :: [BitPixFormat] -> ShowS # | |
Eq BitPixFormat Source # | |
Defined in Data.Fits (==) :: BitPixFormat -> BitPixFormat -> Bool # (/=) :: BitPixFormat -> BitPixFormat -> Bool # |
Axes
represents the combination of NAXIS + NAXISn. The spec supports up to 999 axes
Utility
isBitPixInt :: BitPixFormat -> Bool Source #
This utility functions quickly lets you know if you are dealing with integer data.
isBitPixFloat :: BitPixFormat -> Bool Source #
This utility functions quickly lets you know if you are dealing with floating point data.
bitPixToWordSize :: BitPixFormat -> Int Source #
This utility function can be used to get the word count for data in an HDU.
bitPixToByteSize :: BitPixFormat -> Int Source #
This utility function can be used to get the size in bytes of the - format.
pixDimsByCol :: Axes -> [Int] Source #
pixDimsByRow :: Axes -> [Int] Source #
Constants
hduRecordLength :: Int Source #
A single record in the HDU is an eighty byte word.
hduMaxRecords :: Int Source #
The maximum amount of eighty byte records is thirty-six per the standard.
hduBlockSize :: Int Source #
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.