[phylo] minutely phylo works now

parent d3692c15
Pipeline #7834 failed with stages
in 15 minutes and 2 seconds
...@@ -176,6 +176,7 @@ timeToLabel config = case (timeUnit config) of ...@@ -176,6 +176,7 @@ timeToLabel config = case (timeUnit config) of
Week p s f -> ("time_weeks" <> "_" <> (show p) <> "_" <> (show s) <> "_" <> (show f)) Week p s f -> ("time_weeks" <> "_" <> (show p) <> "_" <> (show s) <> "_" <> (show f))
Day p s f -> ("time_days" <> "_" <> (show p) <> "_" <> (show s) <> "_" <> (show f)) Day p s f -> ("time_days" <> "_" <> (show p) <> "_" <> (show s) <> "_" <> (show f))
Hour _p _s _f -> panicTrace "hours not implemented" Hour _p _s _f -> panicTrace "hours not implemented"
Minute _p _s _f -> panicTrace "minutes not implemented"
seaToLabel :: PhyloConfig -> [Char] seaToLabel :: PhyloConfig -> [Char]
......
...@@ -10,8 +10,6 @@ Portability : POSIX ...@@ -10,8 +10,6 @@ Portability : POSIX
-} -}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
module Gargantext.API.Context module Gargantext.API.Context
where where
...@@ -21,7 +19,7 @@ import Gargantext.API.Admin.Auth.Types (PathId(..), AuthenticatedUser) ...@@ -21,7 +19,7 @@ import Gargantext.API.Admin.Auth.Types (PathId(..), AuthenticatedUser)
import Gargantext.API.Prelude (IsGargServer) import Gargantext.API.Prelude (IsGargServer)
import Gargantext.API.Routes.Named.Context qualified as Named import Gargantext.API.Routes.Named.Context qualified as Named
import Gargantext.Database.Admin.Types.Node (ContextId, contextId2NodeId) import Gargantext.Database.Admin.Types.Node (ContextId, contextId2NodeId)
import Gargantext.Database.Prelude import Gargantext.Database.Prelude ( JSONB, runDBQuery )
import Gargantext.Database.Query.Table.Context (getContextWith) import Gargantext.Database.Query.Table.Context (getContextWith)
import Gargantext.Prelude import Gargantext.Prelude
import Servant.Server.Generic (AsServerT) import Servant.Server.Generic (AsServerT)
......
...@@ -139,6 +139,10 @@ data TimeUnit = ...@@ -139,6 +139,10 @@ data TimeUnit =
{ _hour_period :: Int { _hour_period :: Int
, _hour_step :: Int , _hour_step :: Int
, _hour_matchingFrame :: Int } , _hour_matchingFrame :: Int }
| Minute
{ _minute_period :: Int
, _minute_step :: Int
, _minute_matchingFrame :: Int }
deriving (Show,Generic,Eq,NFData,ToExpr) deriving (Show,Generic,Eq,NFData,ToExpr)
instance ToSchema TimeUnit where instance ToSchema TimeUnit where
......
...@@ -207,7 +207,10 @@ toDays y m d = fromIntegral ...@@ -207,7 +207,10 @@ toDays y m d = fromIntegral
$ diffDays (fromGregorian y m d) (fromGregorian 0001 1 1) $ diffDays (fromGregorian y m d) (fromGregorian 0001 1 1)
toHours :: UTCTimeR -> Date toHours :: UTCTimeR -> Date
toHours utcTimeR = floor diffSeconds `div` 3600 toHours utcTimeR = toMinutes utcTimeR `div` 60
toMinutes :: UTCTimeR -> Date
toMinutes utcTimeR = floor diffSeconds `div` 60
where where
diffSeconds = diffUTCTime (toUTCTime utcTimeR) (toUTCTime defUTCTimeR) diffSeconds = diffUTCTime (toUTCTime utcTimeR) (toUTCTime defUTCTimeR)
...@@ -219,6 +222,7 @@ toPhyloDate utcTimeR@(UTCTimeR { .. }) tu = case tu of ...@@ -219,6 +222,7 @@ toPhyloDate utcTimeR@(UTCTimeR { .. }) tu = case tu of
Week {} -> div (toDays (Prelude.toInteger year) month day) 7 Week {} -> div (toDays (Prelude.toInteger year) month day) 7
Day {} -> toDays (Prelude.toInteger year) month day Day {} -> toDays (Prelude.toInteger year) month day
Hour {} -> toHours utcTimeR Hour {} -> toHours utcTimeR
Minute {} -> toMinutes utcTimeR
_ -> panic "[G.C.V.P.API.Tools] toPhyloDate" _ -> panic "[G.C.V.P.API.Tools] toPhyloDate"
toPhyloDate' :: UTCTimeR -> TimeUnit -> Text toPhyloDate' :: UTCTimeR -> TimeUnit -> Text
......
...@@ -176,6 +176,7 @@ getTimeScale p = case timeUnit $ getConfig p of ...@@ -176,6 +176,7 @@ getTimeScale p = case timeUnit $ getConfig p of
Week {} -> "week" Week {} -> "week"
Day {} -> "day" Day {} -> "day"
Hour {} -> "hour" Hour {} -> "hour"
Minute {} -> "minute"
-- | Get a regular & ascendante timeScale from a given list of dates -- | Get a regular & ascendante timeScale from a given list of dates
...@@ -193,6 +194,7 @@ getTimeStep time = case time of ...@@ -193,6 +194,7 @@ getTimeStep time = case time of
Week { .. } -> _week_step Week { .. } -> _week_step
Day { .. } -> _day_step Day { .. } -> _day_step
Hour { .. } -> _hour_step Hour { .. } -> _hour_step
Minute { .. } -> _minute_step
getTimePeriod :: TimeUnit -> Int getTimePeriod :: TimeUnit -> Int
getTimePeriod time = case time of getTimePeriod time = case time of
...@@ -202,6 +204,7 @@ getTimePeriod time = case time of ...@@ -202,6 +204,7 @@ getTimePeriod time = case time of
Week { .. } -> _week_period Week { .. } -> _week_period
Day { .. } -> _day_period Day { .. } -> _day_period
Hour { .. } -> _hour_period Hour { .. } -> _hour_period
Minute { .. } -> _minute_period
getTimeFrame :: TimeUnit -> Int getTimeFrame :: TimeUnit -> Int
getTimeFrame time = case time of getTimeFrame time = case time of
...@@ -211,6 +214,7 @@ getTimeFrame time = case time of ...@@ -211,6 +214,7 @@ getTimeFrame time = case time of
Week { .. } -> _week_matchingFrame Week { .. } -> _week_matchingFrame
Day { .. } -> _day_matchingFrame Day { .. } -> _day_matchingFrame
Hour { .. } -> _hour_matchingFrame Hour { .. } -> _hour_matchingFrame
Minute { .. } -> _minute_matchingFrame
------------- -------------
-- | Fis | -- -- | Fis | --
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment