module Fit.Internal.FitFile (
Fit(..),
FitHeader(..),
Message(..),
msgLmt,
MessageDefinition(..),
FieldDef(..),
Field(..),
Value(..),
Array(..),
MessageHeader(..),
LocalMessageType(..),
mkLocalMessageType,
unLocalMessageType,
TimeOffset(..),
mkTimeOffset,
Timestamp(..),
BaseType(..),
btSize
) where
import Fit.Internal.Architecture
import Data.Bits (Bits, (.&.))
import Data.ByteString (ByteString)
import Data.Int (Int8, Int16, Int32)
import Data.Sequence (Seq)
import Data.Text (Text)
import Data.Word (Word8, Word16, Word32)
data Fit = Fit {
fHeader :: FitHeader,
fMessages :: [Message]
} deriving (Show)
data FitHeader = FH {
fhSize :: !Word8,
fhProtocolVersion :: !Word8,
fhProfileVersion :: !Word16,
fhDataSize :: !Word32,
fhDataType :: ByteString,
fhCrc :: !(Maybe Word16)
} deriving (Show)
data Message = DefM MessageDefinition
| DataM !LocalMessageType !Int [Field]
deriving (Show)
msgLmt :: Message -> LocalMessageType
msgLmt (DefM (MessageDef lmt _ _ _)) = lmt
msgLmt (DataM lmt _ _) = lmt
data MessageDefinition = MessageDef {
defLocalType :: !LocalMessageType,
defGlobalType :: !Int,
defArch :: !Arch,
defFields :: [FieldDef]
} deriving (Show, Eq)
data FieldDef = FieldDef {
fdNum :: !Int,
fdSize :: !Int,
fdBaseType :: !BaseType
} deriving (Show, Eq)
data Field = SingletonField !Int Value
| ArrayField !Int Array
deriving (Show)
data Value = EnumValue !Word8
| SInt8Value !Int8
| UInt8Value !Word8
| SInt16Value !Int16
| UInt16Value !Word16
| SInt32Value !Int32
| UInt32Value !Word32
| StringValue Text
| Float32Value !Float
| Float64Value !Double
| UInt8ZValue !Word8
| UInt16ZValue !Word16
| UInt32ZValue !Word32
| ByteValue !Word8
deriving (Show)
data Array = EnumArray (Seq Word8)
| SInt8Array (Seq Int8)
| UInt8Array (Seq Word8)
| SInt16Array (Seq Int16)
| UInt16Array (Seq Word16)
| SInt32Array (Seq Int32)
| UInt32Array (Seq Word32)
| Float32Array (Seq Float)
| Float64Array (Seq Double)
| UInt8ZArray (Seq Word8)
| UInt16ZArray (Seq Word16)
| UInt32ZArray (Seq Word32)
| ByteArray (Seq Word8)
deriving (Show)
data MessageHeader = DefHeader !LocalMessageType
| DataHeader !LocalMessageType
| CTDataHeader !LocalMessageType !TimeOffset
deriving (Show)
newtype LocalMessageType = LMT { unLmt :: Int8 } deriving (Show, Eq)
mkLocalMessageType :: (Integral a, Bits a) => a -> LocalMessageType
mkLocalMessageType = LMT . fromIntegral . ((.&.) 0xF)
unLocalMessageType :: Integral a => LocalMessageType -> a
unLocalMessageType = fromIntegral . unLmt
newtype TimeOffset = TO { unTo :: Word8 } deriving (Show)
mkTimeOffset :: (Integral a, Bits a) => a -> TimeOffset
mkTimeOffset = TO . fromIntegral . ((.&.) 0x1F)
newtype Timestamp = Timestamp { unTimestamp :: Word32 } deriving (Show, Eq)
data BaseType = FitEnum
| FitSInt8
| FitUInt8
| FitSInt16
| FitUInt16
| FitSInt32
| FitUInt32
| FitString
| FitFloat32
| FitFloat64
| FitUInt8Z
| FitUInt16Z
| FitUInt32Z
| FitByte
deriving (Show, Eq)
btSize :: BaseType -> Int
btSize bt = case bt of
FitEnum -> 1
FitSInt8 -> 1
FitUInt8 -> 1
FitSInt16 -> 2
FitUInt16 -> 2
FitSInt32 -> 4
FitUInt32 -> 4
FitString -> 1
FitFloat32 -> 4
FitFloat64 -> 8
FitUInt8Z -> 1
FitUInt16Z -> 2
FitUInt32Z -> 4
FitByte -> 1