Skip to content

Commit

Permalink
lentille - log invalid gitlab date
Browse files Browse the repository at this point in the history
  • Loading branch information
TristanCacqueray committed Jan 28, 2025
1 parent 8ffa58d commit 5173aae
Show file tree
Hide file tree
Showing 3 changed files with 19 additions and 24 deletions.
26 changes: 10 additions & 16 deletions src/Lentille/GitLab/Adapter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ module Lentille.GitLab.Adapter where
import Data.Morpheus.Client
import Data.Text qualified as TE
import Data.Time.Clock
import Data.Time.Format (defaultTimeLocale, formatTime, parseTimeOrError)
import Data.Time.Format (defaultTimeLocale, formatTime)
import Google.Protobuf.Timestamp qualified as T
import Lentille (ghostIdent, nobody, toIdent)
import Monocle.Config qualified as Config
Expand Down Expand Up @@ -55,27 +55,21 @@ data MRComment = MRComment

-- Some default data

commitFormatString :: Maybe String
commitFormatString = Just "%FT%X%EZ"

defaultTimestamp :: Time
defaultTimestamp = Time "1970-01-01T00:00:00+00:00"

-- Generic utility fonction
fromMTtoLT :: From s LText => Maybe s -> LText
fromMTtoLT = maybe "" from

timeToTimestamp :: Maybe String -> Time -> T.Timestamp
timeToTimestamp formatStringE = T.fromUTCTime . timeToUTCTime formatStringE
timeToTimestamp :: Time -> T.Timestamp
timeToTimestamp = T.fromUTCTime . timeToUTCTime

timeToUTCTime :: Maybe String -> Time -> UTCTime
timeToUTCTime formatStringE t =
let Time tt = t
in parseTimeOrError
False
defaultTimeLocale
(fromMaybe "%FT%XZ" formatStringE)
$ from tt
timeToUTCTime :: Time -> UTCTime
timeToUTCTime (Time t) =
case parseDateValue (from t) of
Nothing -> error $ "Unknown time format: " <> from tt
Just utc -> utc

cleanMaybeMNodes :: Maybe [Maybe a] -> [a]
cleanMaybeMNodes nodes = catMaybes $ fromMaybe [] nodes
Expand Down Expand Up @@ -104,8 +98,8 @@ toCommit host cb MRCommit {..} =
(from sha)
(Just . toIdent' $ getAuthor cauthor)
(Just . toIdent' $ getAuthor cauthor)
(Just . timeToTimestamp commitFormatString $ fromMaybe defaultTimestamp authoredDate)
(Just . timeToTimestamp commitFormatString $ fromMaybe defaultTimestamp authoredDate)
(Just . timeToTimestamp $ fromMaybe defaultTimestamp authoredDate)
(Just . timeToTimestamp $ fromMaybe defaultTimestamp authoredDate)
0
0
(from $ fromMaybe "" ctitle)
Expand Down
16 changes: 8 additions & 8 deletions src/Lentille/GitLab/MergeRequests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ module Lentille.GitLab.MergeRequests where
import Data.Morpheus.Client
import Data.Text qualified as TE
import Data.Time.Clock
import Data.Time.Format (defaultTimeLocale, formatTime, parseTimeOrError)
import Data.Time.Format (defaultTimeLocale, formatTime)
import Data.Vector qualified as V
import Google.Protobuf.Timestamp qualified as T
import Lentille
Expand Down Expand Up @@ -212,21 +212,21 @@ transformResponse host getIdentIdCB result =
changeOptionalMergedCommitSha = Nothing
changeBranch = from sourceBranch
changeTargetBranch = from targetBranch
changeCreatedAt = (Just $ timeToTimestamp Nothing createdAt)
changeOptionalMergedAt = (ChangeOptionalMergedAtMergedAt . timeToTimestamp Nothing <$> mergedAt)
changeUpdatedAt = (Just $ timeToTimestamp Nothing updatedAt)
changeCreatedAt = (Just $ timeToTimestamp createdAt)
changeOptionalMergedAt = (ChangeOptionalMergedAtMergedAt . timeToTimestamp <$> mergedAt)
changeUpdatedAt = (Just $ timeToTimestamp updatedAt)
-- No closedAt attribute for a MR then use updatedAt when the MR is closed state
changeOptionalClosedAt =
if isClosed $ toState state
then Just . ChangeOptionalClosedAtClosedAt $ timeToTimestamp Nothing updatedAt
then Just . ChangeOptionalClosedAtClosedAt $ timeToTimestamp updatedAt
else Nothing
changeState = toState state
changeOptionalDuration = case mergedAt of
Just merged_ts ->
Just
. ChangeOptionalDurationDuration
. from
$ diffTimeSec (timeToUTCTime Nothing merged_ts) (timeToUTCTime Nothing createdAt)
$ diffTimeSec (timeToUTCTime merged_ts) (timeToUTCTime createdAt)
Nothing -> Nothing

-- TODO(fbo) Use the merge status : https://docs.gitlab.com/ee/api/graphql/reference/index.html#mergestatus
Expand Down Expand Up @@ -350,7 +350,7 @@ transformResponse host getIdentIdCB result =
{ changeEventId = "ChangeCommentedEvent-" <> changeId change <> "-" <> from coId
, changeEventType = Just $ ChangeEventTypeChangeCommented ChangeCommentedEvent
, changeEventAuthor = Just coAuthor
, changeEventCreatedAt = Just $ timeToTimestamp Nothing coAuthoredAt
, changeEventCreatedAt = Just $ timeToTimestamp coAuthoredAt
}

getChangeReviewedEvent :: Change -> [MRComment] -> [ChangeEvent]
Expand All @@ -369,5 +369,5 @@ transformResponse host getIdentIdCB result =
. ChangeReviewedEvent
$ fromList [from approval]
, changeEventAuthor = Just coAuthor
, changeEventCreatedAt = Just $ timeToTimestamp Nothing coAuthoredAt
, changeEventCreatedAt = Just $ timeToTimestamp coAuthoredAt
}
1 change: 1 addition & 0 deletions src/Monocle/Prelude.hs
Original file line number Diff line number Diff line change
Expand Up @@ -445,6 +445,7 @@ parseDateValue str =
tryParse "%F"
<|> tryParse "%F %T %Z"
<|> tryParse "%FT%XZ"
<|> tryParse "%FT%X%EZ"
where
tryParse fmt = parseTimeM False defaultTimeLocale fmt str

Expand Down

0 comments on commit 5173aae

Please sign in to comment.