Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- newtype Header = Header {
- _records :: [HeaderRecord]
- data Value
- keyword :: Text -> Value -> Maybe Text -> HeaderRecord
- addComment :: Text -> KeywordRecord -> KeywordRecord
- class FromHeader a where
- class FromKeyword a where
- class ToHeader a where
- class ToKeyword a where
- toKeywordValue :: a -> Value
- toKeywordRecord :: Text -> a -> KeywordRecord
- parseKeyword :: forall a (es :: [Effect]). (FromKeyword a, Parser :> es) => Text -> Header -> Eff es a
- lookupKeyword :: Text -> Header -> Maybe Value
- findKeyword :: (KeywordRecord -> Bool) -> Header -> Maybe Value
- isKeyword :: Text -> KeywordRecord -> Bool
- newtype HeaderFor a = HeaderFor a
- data LogicalConstant
- getKeywords :: Header -> [KeywordRecord]
- data HeaderRecord
- data KeywordRecord = KeywordRecord {}
Documentation
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
.
Header | |
|
Value
datatype for discriminating valid FITS KEYWORD=VALUE types in an HDU.
addComment :: Text -> KeywordRecord -> KeywordRecord Source #
Set the comment of a KeywordRecrod
Parsing Headers
class FromHeader a where Source #
Nothing
class FromKeyword a where Source #
Instances
FromKeyword CType Source # | |
Defined in Telescope.Fits.Header.Class | |
FromKeyword CUnit Source # | |
Defined in Telescope.Fits.Header.Class | |
FromKeyword Text Source # | |
Defined in Telescope.Fits.Header.Class | |
FromKeyword Bool Source # | |
Defined in Telescope.Fits.Header.Class | |
FromKeyword Float Source # | |
Defined in Telescope.Fits.Header.Class | |
FromKeyword Int Source # | |
Defined in Telescope.Fits.Header.Class |
Creating Headers
class ToHeader a where Source #
Nothing
class ToKeyword a where Source #
toKeywordValue :: a -> Value Source #
toKeywordRecord :: Text -> a -> KeywordRecord Source #
default toKeywordRecord :: Text -> a -> KeywordRecord Source #
Instances
ToKeyword CType Source # | |
Defined in Telescope.Fits.Header.Class toKeywordValue :: CType -> Value Source # toKeywordRecord :: Text -> CType -> KeywordRecord Source # | |
ToKeyword CUnit Source # | |
Defined in Telescope.Fits.Header.Class toKeywordValue :: CUnit -> Value Source # toKeywordRecord :: Text -> CUnit -> KeywordRecord Source # | |
ToKeyword Text Source # | |
Defined in Telescope.Fits.Header.Class toKeywordValue :: Text -> Value Source # toKeywordRecord :: Text -> Text -> KeywordRecord Source # | |
ToKeyword Bool Source # | |
Defined in Telescope.Fits.Header.Class toKeywordValue :: Bool -> Value Source # toKeywordRecord :: Text -> Bool -> KeywordRecord Source # | |
ToKeyword Float Source # | |
Defined in Telescope.Fits.Header.Class toKeywordValue :: Float -> Value Source # toKeywordRecord :: Text -> Float -> KeywordRecord Source # | |
ToKeyword Int Source # | |
Defined in Telescope.Fits.Header.Class toKeywordValue :: Int -> Value Source # toKeywordRecord :: Text -> Int -> KeywordRecord Source # |
parseKeyword :: forall a (es :: [Effect]). (FromKeyword a, Parser :> es) => Text -> Header -> Eff es a Source #
Keyword Lookup
findKeyword :: (KeywordRecord -> Bool) -> Header -> Maybe Value Source #
Re-exports
data LogicalConstant #
Instances
Show LogicalConstant | |
Defined in Data.Fits showsPrec :: Int -> LogicalConstant -> ShowS # show :: LogicalConstant -> String # showList :: [LogicalConstant] -> ShowS # | |
Eq LogicalConstant | |
Defined in Data.Fits (==) :: LogicalConstant -> LogicalConstant -> Bool # (/=) :: LogicalConstant -> LogicalConstant -> Bool # |
getKeywords :: Header -> [KeywordRecord] #
Return all KeywordRecord
s 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)
Instances
Show HeaderRecord | |
Defined in Data.Fits showsPrec :: Int -> HeaderRecord -> ShowS # show :: HeaderRecord -> String # showList :: [HeaderRecord] -> ShowS # | |
Eq HeaderRecord | |
Defined in Data.Fits (==) :: HeaderRecord -> HeaderRecord -> Bool # (/=) :: HeaderRecord -> HeaderRecord -> Bool # |
data KeywordRecord #
A single 80 character header keyword line of the form: KEYWORD = VALUE / comment KEYWORD=VALUE
Instances
Show KeywordRecord | |
Defined in Data.Fits showsPrec :: Int -> KeywordRecord -> ShowS # show :: KeywordRecord -> String # showList :: [KeywordRecord] -> ShowS # | |
Eq KeywordRecord | |
Defined in Data.Fits (==) :: KeywordRecord -> KeywordRecord -> Bool # (/=) :: KeywordRecord -> KeywordRecord -> Bool # |