module Fit.Internal.FitParser (
FitParser,
runFitParser,
FpState(..),
Definitions(..),
addMessageDef,
lookupMessageDef,
withArchitecture,
storeTimestamp,
updateTimestamp,
word8,
int8,
archWord16,
archWord32,
archWord64,
archInt16,
archInt32,
archInt64,
archFloat32,
archFloat64
) where
import Fit.Internal.Architecture
import Fit.Internal.FitFile
import qualified Fit.Internal.Numbers as N
import Control.Applicative ((<$>), (<*), (*>))
import Control.Monad.State.Class (get, modify)
import Control.Monad.State.Strict (StateT, evalStateT)
import Control.Monad.Trans (lift)
import Data.Attoparsec.ByteString (Parser)
import qualified Data.Attoparsec.ByteString as A (anyWord8)
import Data.Bits ((.&.))
import Data.Int (Int8, Int16, Int32, Int64)
import Data.IntMap.Strict (IntMap)
import qualified Data.IntMap.Strict as IntMap (insert, lookup, empty)
import Data.Word (Word8, Word16, Word32, Word64)
type FitParser a = StateT FpState Parser a
runFitParser :: FitParser a -> Parser a
runFitParser = flip evalStateT (FpState ArchLittle defEmpty Nothing)
withArchitecture :: Arch -> FitParser a -> FitParser a
withArchitecture arch action =
use fpArch >>= \old -> setArch arch *> action <* setArch old
setArch :: Arch -> FitParser ()
setArch = assign fpArch
addMessageDef :: MessageDefinition -> FitParser ()
addMessageDef def = fpMessageDefs %= (defAdd def)
lookupMessageDef :: LocalMessageType -> FitParser MessageDefinition
lookupMessageDef lmt = do
msgDefs <- use fpMessageDefs
case defLookup lmt msgDefs of
Just def -> return def
Nothing -> error $ "No definition for local type " ++ (show lmt)
storeTimestamp :: Timestamp -> FitParser ()
storeTimestamp t = fpLastTimestamp .= Just t
updateTimestamp :: TimeOffset -> FitParser Timestamp
updateTimestamp offset = do
previous <- use fpLastTimestamp
let new = addOffset offset previous
fpLastTimestamp .= Just new
return new
where addOffset _ Nothing = error "No base timestamp to update"
addOffset (TO off) (Just (Timestamp previous)) =
let off' = fromIntegral off
low5Prev = previous .&. 0x1F
high27Prev = previous .&. 0xFFFFFFE0
rollover = off' < low5Prev
in if rollover
then Timestamp $ high27Prev + 0x20 + off'
else Timestamp $ high27Prev + off'
data FpState = FpState {
_fpArch :: !Arch,
_fpMessageDefs :: Definitions,
_fpLastTimestamp :: !(Maybe Timestamp)
}
newtype Definitions = Defs { unDefs :: IntMap MessageDefinition }
fpArch :: Functor f => Lens f FpState Arch
fpArch f (FpState arch defs ts) = (\arch' -> FpState arch' defs ts) <$> (f arch)
fpMessageDefs :: Functor f => Lens f FpState Definitions
fpMessageDefs f (FpState arch defs ts) = (\defs' -> FpState arch defs' ts) <$> (f defs)
fpLastTimestamp :: Functor f => Lens f FpState (Maybe Timestamp)
fpLastTimestamp f (FpState arch defs ts) = (\ts' -> FpState arch defs ts') <$> (f ts)
defAdd :: MessageDefinition -> Definitions -> Definitions
defAdd md = Defs . (IntMap.insert lmt md) . unDefs
where lmt = unLocalMessageType . defLocalType $ md
defLookup :: LocalMessageType -> Definitions -> Maybe MessageDefinition
defLookup (LMT lmt) (Defs defs) = IntMap.lookup (fromIntegral lmt) defs
defEmpty :: Definitions
defEmpty = Defs (IntMap.empty)
word8 :: FitParser Word8
word8 = lift A.anyWord8
int8 :: FitParser Int8
int8 = fromIntegral <$> word8
archWord16 :: FitParser Word16
archWord16 = withArch N.word16le N.word16be
archWord32 :: FitParser Word32
archWord32 = withArch N.word32le N.word32be
archWord64 :: FitParser Word64
archWord64 = withArch N.word64le N.word64be
archInt16 :: FitParser Int16
archInt16 = withArch N.int16le N.int16be
archInt32 :: FitParser Int32
archInt32 = withArch N.int32le N.int32be
archInt64 :: FitParser Int64
archInt64 = withArch N.int64le N.int64be
archFloat32 :: FitParser Float
archFloat32 = withArch N.float32le N.float32be
archFloat64 :: FitParser Double
archFloat64 = withArch N.float64le N.float64be
withArch :: LittleEndian (Parser a) -> BigEndian (Parser a) -> FitParser a
withArch little big = use fpArch >>= \case
ArchLittle -> lift (unArch little)
ArchBig -> lift (unArch big)
view :: Getter s a -> s -> a
view l x = getConst $ l Const x
over :: Setter s a -> (a -> a) -> s -> s
over l f x = runIdentity $ l (Identity . f) x
set :: Setter s a -> a -> s -> s
set l x = over l (const x)
use :: (Monad m, Functor m) => Getter s a -> StateT s m a
use l = fmap (view l) get
assign :: (Monad m, Functor m) => Setter s a -> a -> StateT s m ()
assign l x = modify (set l x)
(.=) :: (Monad m, Functor m) => Setter s a -> a -> StateT s m ()
l .= x = assign l x
(%=) :: (Monad m, Functor m) => Setter s a -> (a -> a) -> StateT s m ()
l %= f = modify (over l f)
type Lens f s a = (a -> f a) -> s -> f s
type Getter s a = Lens (Const a) s a
type Setter s a = Lens Identity s a
newtype Identity a = Identity { runIdentity :: a }
instance Functor Identity where
fmap f (Identity a) = Identity (f a)
newtype Const a b = Const { getConst :: a }
instance Functor (Const a) where
fmap _ (Const x) = (Const x)