{-# LANGUAGE PartialTypeSignatures, DataKinds, ExistentialQuantification
, ScopedTypeVariables, GADTs
, OverloadedStrings, TypeOperators, TypeFamilies #-}
module Data.Fits
(
parsePix
, pixsUnwrapI
, pixsUnwrapD
, HeaderDataUnit(..)
, HeaderData(..)
, BitPixFormat(..)
, Pix(..)
, SimpleFormat(..)
, Axis(..)
, StringType(..)
, StringValue(..)
, NumberType(..)
, NumberModifier(..)
, NumberValue(..)
, isBitPixInt
, isBitPixFloat
, bitPixToWordSize
, hduRecordLength
, hduMaxRecords
, hduBlockSize
) where
import qualified Data.Text as T
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BL
import Numeric.Natural ( Natural )
import GHC.TypeNats (KnownNat, Nat)
import Data.Text ( Text )
import Data.ByteString ( ByteString )
import Data.Default( Default, def )
import Data.Binary
import Data.Binary.Get
hduRecordLength :: Int
hduRecordLength = 80
hduMaxRecords :: Int
hduMaxRecords = 36
hduBlockSize :: Int
hduBlockSize = hduRecordLength * hduMaxRecords
data StringType = NullString
| EmptyString
| DataString
instance Show StringType where
show NullString = "Null String"
show EmptyString = "Empty quoted String"
show DataString = "String"
data StringValue = StringValue
{ stringType :: StringType
, stringValue :: Maybe Text
}
instance Default StringValue where
def = StringValue NullString Nothing
instance Show StringValue where
show (StringValue NullString _) = show NullString
show (StringValue EmptyString _) = show EmptyString
show (StringValue DataString Nothing) = "No good " ++ show DataString
show (StringValue DataString (Just s)) = show DataString ++ T.unpack s
data NumberType =
IntegerType
| RealType
| ComplexType
data NumberModifier =
Positive
| Negative
| Zero
data NumberValue = NumberValue
{ numberType :: NumberType
, realModifier :: NumberModifier
, realPart :: Text
, imaginaryModifier :: Maybe NumberModifier
, imaginaryPart :: Maybe Text
, exponentModifier :: Maybe NumberModifier
, exponent :: Maybe Int
}
instance Default NumberValue where
def = NumberValue IntegerType Zero "0" Nothing Nothing Nothing Nothing
data SimpleFormat = Conformant
| NonConformant
data Axis = Axis
{ axisNumber :: Int
, axisElementCount :: Int
}
instance Default Axis where
def = Axis 0 0
data BitPixFormat =
EightBitInt
| SixteenBitInt
| ThirtyTwoBitInt
| SixtyFourBitInt
| ThirtyTwoBitFloat
| SixtyFourBitFloat
instance Show BitPixFormat where
show EightBitInt = "8 bit unsigned integer"
show SixteenBitInt = "16 bit signed integer"
show ThirtyTwoBitInt = "32 bit signed integer"
show SixtyFourBitInt = "64 bit signed interger"
show ThirtyTwoBitFloat = "32 bit IEEE single precision float"
show SixtyFourBitFloat = "64 bit IEEE double precision float"
bitPixToWordSize :: BitPixFormat -> Natural
bitPixToWordSize EightBitInt = 8
bitPixToWordSize SixteenBitInt = 16
bitPixToWordSize ThirtyTwoBitInt = 32
bitPixToWordSize ThirtyTwoBitFloat = 32
bitPixToWordSize SixtyFourBitInt = 64
bitPixToWordSize SixtyFourBitFloat = 64
bitPixToByteSize :: BitPixFormat -> Natural
bitPixToByteSize EightBitInt = 1
bitPixToByteSize SixteenBitInt = 2
bitPixToByteSize ThirtyTwoBitInt = 4
bitPixToByteSize ThirtyTwoBitFloat = 4
bitPixToByteSize SixtyFourBitInt = 8
bitPixToByteSize SixtyFourBitFloat = 8
isBitPixInt :: BitPixFormat -> Bool
isBitPixInt EightBitInt = True
isBitPixInt SixteenBitInt = True
isBitPixInt ThirtyTwoBitInt = True
isBitPixInt SixtyFourBitInt = True
isBitPixInt _ = False
isBitPixFloat :: BitPixFormat -> Bool
isBitPixFloat ThirtyTwoBitFloat = True
isBitPixFloat SixtyFourBitFloat = True
isBitPixFloat _ = False
data Pix = PB Int | PI16 Int | PI32 Int | PI64 Int | PF Double | PD Double
unPixI :: Pix -> Int
unPixI (PB b) = b
unPixI (PI16 i) = i
unPixI (PI32 i) = i
unPixI (PI64 i) = i
unPixI _ = error "Pix are not stored as integers, invalid unpacking"
unPixD :: Pix -> Double
unPixD (PF d) = d
unPixD (PD d) = d
unPixD _ = error "Pix are not stored as floating point values, invalid unpacking"
pixsUnwrapI :: BitPixFormat -> [Pix] -> [Int]
pixsUnwrapI EightBitInt pxs = map unPixI pxs
pixsUnwrapI SixteenBitInt pxs = map unPixI pxs
pixsUnwrapI ThirtyTwoBitInt pxs = map unPixI pxs
pixsUnwrapI SixtyFourBitInt pxs = map unPixI pxs
pixsUnwrapI _ _ = error "BitPixFormat is not an integer type"
pixsUnwrapD :: BitPixFormat -> [Pix] -> [Double]
pixsUnwrapD ThirtyTwoBitFloat pxs = map unPixD pxs
pixsUnwrapD SixtyFourBitFloat pxs = map unPixD pxs
pixsUnwrapD _ _ = error "BitPixFormat is not a floating point type"
getPix :: BitPixFormat -> Get Pix
getPix EightBitInt = PB . fromIntegral <$> getInt8
getPix SixteenBitInt = PI16 . fromIntegral <$> getInt16be
getPix ThirtyTwoBitInt = PI32 . fromIntegral <$> getInt32be
getPix SixtyFourBitInt = PI64 . fromIntegral <$> getInt64be
getPix ThirtyTwoBitFloat = PF . realToFrac <$> getFloatbe
getPix SixtyFourBitFloat = PD . realToFrac <$> getDoublebe
getPixs :: Int -> BitPixFormat -> Get [Pix]
getPixs c bpf = do
empty <- isEmpty
if empty
then return []
else do
p <- getPix bpf
ps <- getPixs (c - 1) bpf
return (p:ps)
parsePix :: Int -> BitPixFormat -> BL.ByteString -> IO [Pix]
parsePix c bpf bs = return $ runGet (getPixs c bpf) bs
pixDimsByCol :: [Axis] -> [Int]
pixDimsByCol = map axisElementCount
pixDimsByRow :: [Axis] -> [Int]
pixDimsByRow = reverse . pixDimsByCol
data HeaderData = HeaderData
{ simpleFormat :: SimpleFormat
, bitPixFormat :: BitPixFormat
, axes :: [Axis]
, objectIdentifier :: StringValue
, observationDate :: StringValue
, originIdentifier :: StringValue
, telescopeIdentifier :: StringValue
, instrumentIdentifier :: StringValue
, observerIdentifier :: StringValue
, authorIdentifier :: StringValue
, referenceString :: StringValue
}
instance Default HeaderData where
def = HeaderData NonConformant EightBitInt []
(def :: StringValue) (def :: StringValue) (def :: StringValue)
(def :: StringValue) (def :: StringValue) (def :: StringValue)
(def :: StringValue) (def :: StringValue)
data HeaderDataUnit = HeaderDataUnit
{ headerData :: HeaderData
, payloadData :: ByteString
}