module Graphics.Rendering.Plot.Light.PlotTypes.TimeSeries where import GHC.Real import Data.Fixed (Pico) import Data.Time import qualified Data.Text as T import Graphics.Rendering.Plot.Light.Internal import Graphics.Rendering.Plot.Light.Internal.Types import Data.TimeSeries.Forex -- | Create a Tick from valid (year, month, day, hour, minute, second) mkTick :: Integer -> Int -> Int -> Int -> Int -> Pico -> Maybe Tick mkTick yy mm dd hr mi se = do tim <- makeTimeOfDayValid hr mi se let d = fromGregorian yy mm dd return $ Tick d tim -- | Map a Tick onto the rationals fromTick :: Tick -> Rational fromTick (Tick d t) = fromIntegral (toModifiedJulianDay d) + timeOfDayToDayFraction t -- | Transform the time coordinate of a timeseries point mapToViewbox :: FigureData (Ratio Integer) d -> Tick -- | Lower bound -> Tick -- | Upper bound -> TsPoint a -- | A point in the timeseries -> LabeledPoint (Ratio Integer) Tick a mapToViewbox fd tmin tmax p = LabeledPoint t' (_tick p) (_val p) where t' = toViewboxRange fd tmin tmax p toViewboxRange :: FigureData Rational d -> Tick -> Tick -> TsPoint a -> Rational toViewboxRange fd tmin tmax p = affine (_xmin fd) (_xmax fd) (fromTick tmin) (fromTick tmax) (fromTick $ _tick p) -- SVG with text -- -- -- -- Example text01 - 'Hello, out there' in blue -- -- Hello, out there -- -- -- --