Skip to content

Commit

Permalink
Remove more CPP stuff that is no longer needed.
Browse files Browse the repository at this point in the history
  • Loading branch information
augustss committed Dec 26, 2024
1 parent ec1de05 commit cd652ae
Show file tree
Hide file tree
Showing 14 changed files with 4 additions and 42 deletions.
3 changes: 0 additions & 3 deletions lib/Data/Time/Calendar/Gregorian.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE TypeSynonymInstances #-}

Expand Down Expand Up @@ -185,10 +184,8 @@ diffGregorianDurationRollOver day2 day1 =
instance Show Day where
show = showGregorian

#ifdef __GLASGOW_HASKELL__
-- orphan instance
instance DayPeriod Year where
periodFirstDay y = YearMonthDay y January 1
periodLastDay y = YearMonthDay y December 31
dayPeriod (YearMonthDay y _ _) = y
#endif
1 change: 0 additions & 1 deletion lib/Data/Time/Calendar/Julian.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

module Data.Time.Calendar.Julian (
Expand Down
1 change: 0 additions & 1 deletion lib/Data/Time/Calendar/Month.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

-- | An absolute count of common calendar months.
Expand Down
1 change: 0 additions & 1 deletion lib/Data/Time/Calendar/MonthDay.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

module Data.Time.Calendar.MonthDay (
Expand Down
1 change: 0 additions & 1 deletion lib/Data/Time/Calendar/OrdinalDate.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

-- | ISO 8601 Ordinal Date format
Expand Down
1 change: 0 additions & 1 deletion lib/Data/Time/Calendar/Quarter.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

-- | Year quarters.
Expand Down
1 change: 0 additions & 1 deletion lib/Data/Time/Calendar/Types.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

module Data.Time.Calendar.Types where
Expand Down
9 changes: 1 addition & 8 deletions lib/Data/Time/Calendar/WeekDate.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

-- | Week-based calendars
Expand All @@ -24,20 +23,14 @@ import Data.Time.Calendar.Days
import Data.Time.Calendar.OrdinalDate
import Data.Time.Calendar.Private
import Data.Time.Calendar.Week
#ifdef __GLASGOW_HASKELL__
import qualified Language.Haskell.TH.Syntax as TH
#endif

data FirstWeekType
= -- | first week is the first whole week of the year
FirstWholeWeek
| -- | first week is the first week with four days in the year
FirstMostWeek
deriving (Eq
#ifdef __GLASGOW_HASKELL__
, TH.Lift
#endif
)
deriving (Eq, TH.Lift)

firstDayOfWeekCalendar :: FirstWeekType -> DayOfWeek -> Year -> Day
firstDayOfWeekCalendar wt dow year =
Expand Down
9 changes: 1 addition & 8 deletions lib/Data/Time/Clock/Internal/AbsoluteTime.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

-- | TAI and leap-second maps for converting to UTC: most people won't need this module.
Expand All @@ -15,18 +14,12 @@ import Control.DeepSeq
import Data.Data
import Data.Time.Calendar.Days
import Data.Time.Clock.Internal.DiffTime
#ifdef __GLASGOW_HASKELL__
import qualified Language.Haskell.TH.Syntax as TH
#endif

-- | AbsoluteTime is TAI, time as measured by a clock.
newtype AbsoluteTime
= MkAbsoluteTime DiffTime
deriving (Eq, Ord, Data, Typeable
#ifdef __GLASGOW_HASKELL__
, TH.Lift
#endif
)
deriving (Eq, Ord, Data, Typeable, TH.Lift)

instance NFData AbsoluteTime where
rnf (MkAbsoluteTime a) = rnf a
Expand Down
2 changes: 1 addition & 1 deletion lib/Data/Time/Clock/Internal/DiffTime.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,8 +17,8 @@ import Data.Data
import Data.Fixed
#ifdef __GLASGOW_HASKELL__
import GHC.Read
import qualified Language.Haskell.TH.Syntax as TH
#endif
import qualified Language.Haskell.TH.Syntax as TH
import Text.Read
import Text.ParserCombinators.ReadP

Expand Down
2 changes: 1 addition & 1 deletion lib/Data/Time/Clock/Internal/NominalDiffTime.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,8 +16,8 @@ import Data.Data
import Data.Fixed
#ifdef __GLASGOW_HASKELL__
import GHC.Read
import qualified Language.Haskell.TH.Syntax as TH
#endif
import qualified Language.Haskell.TH.Syntax as TH
import Text.ParserCombinators.ReadP
import Text.ParserCombinators.ReadPrec

Expand Down
5 changes: 0 additions & 5 deletions lib/Data/Time/Clock/System.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

-- | Fast access to the system clock.
Expand Down Expand Up @@ -30,10 +29,8 @@ truncateSystemTimeLeapSecond t = t
systemToUTCTime :: SystemTime -> UTCTime
systemToUTCTime (MkSystemTime seconds nanoseconds) =
let
#ifdef __GLASGOW_HASKELL__
days :: Int64
timeSeconds :: Int64
#endif
(days, timeSeconds) = seconds `divMod` 86400
day :: Day
day = addDays (fromIntegral days) systemEpochDay
Expand All @@ -56,10 +53,8 @@ utcToSystemTime (UTCTime day time) =
timePicoseconds = fromIntegral $ diffTimeToPicoseconds time
timeNanoseconds :: Int64
timeNanoseconds = timePicoseconds `div` 1000
#ifdef __GLASGOW_HASKELL__
timeSeconds :: Int64
nanoseconds :: Int64
#endif
(timeSeconds, nanoseconds) =
if timeNanoseconds >= 86400000000000
then (86399, timeNanoseconds - 86399000000000)
Expand Down
7 changes: 0 additions & 7 deletions lib/Data/Time/Format/Format/Instances.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

{-# OPTIONS -fno-warn-orphans #-}
Expand Down Expand Up @@ -112,7 +111,6 @@ instance FormatTime DayOfWeek where
formatCharacter _ _ = Nothing

instance FormatTime Month where
#ifdef __GLASGOW_HASKELL__
-- Year Count
formatCharacter _ 'Y' = Just $ formatNumber False 4 '0' $ \(YearMonth y _) -> y
formatCharacter _ 'y' = Just $ formatNumber True 2 '0' $ \(YearMonth y _) -> mod100 y
Expand All @@ -125,7 +123,6 @@ instance FormatTime Month where
formatCharacter _ 'h' =
Just $ formatString $ \locale (YearMonth _ my) -> snd $ (months locale) !! (my - 1)
formatCharacter _ 'm' = Just $ formatNumber True 2 '0' $ \(YearMonth _ m) -> m
#endif
-- Default
formatCharacter _ _ = Nothing

Expand All @@ -135,7 +132,6 @@ instance FormatTime Day where
formatCharacter _ 'F' = Just $ formatString $ \locale -> formatTime locale "%Y-%m-%d"
formatCharacter _ 'x' = Just $ formatString $ \locale -> formatTime locale (dateFmt locale)
-- Day of Month
#ifdef __GLASGOW_HASKELL__
formatCharacter _ 'd' = Just $ formatNumber True 2 '0' $ \(YearMonthDay _ _ dm) -> dm
formatCharacter _ 'e' = Just $ formatNumber True 2 ' ' $ \(YearMonthDay _ _ dm) -> dm
-- Day of Year
Expand All @@ -146,17 +142,14 @@ instance FormatTime Day where
formatCharacter _ 'f' = Just $ formatNumber False 2 '0' $ \(YearWeekDay y _ _) -> div100 y
formatCharacter _ 'V' = Just $ formatNumber True 2 '0' $ \(YearWeekDay _ wy _) -> wy
formatCharacter _ 'u' = Just $ formatNumber True 1 '0' $ \(YearWeekDay _ _ dw) -> fromEnum dw
#endif
-- Day of week
formatCharacter _ 'a' = Just $ formatString $ \locale -> snd . ((wDays locale) !!) . snd . sundayStartWeek
formatCharacter _ 'A' = Just $ formatString $ \locale -> fst . ((wDays locale) !!) . snd . sundayStartWeek
formatCharacter _ 'U' = Just $ formatNumber True 2 '0' $ fst . sundayStartWeek
formatCharacter _ 'w' = Just $ formatNumber True 1 '0' $ snd . sundayStartWeek
formatCharacter _ 'W' = Just $ formatNumber True 2 '0' $ fst . mondayStartWeek
-- Default
#ifdef __GLASGOW_HASKELL__
formatCharacter alt c = mapFormatCharacter (\(MonthDay m _) -> m) $ formatCharacter alt c
#endif

instance FormatTime UTCTime where
formatCharacter alt c = mapFormatCharacter (utcToZonedTime utc) $ formatCharacter alt c
Expand Down
3 changes: 0 additions & 3 deletions lib/Data/Time/Format/Parse/Instances.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

{-# OPTIONS -fno-warn-orphans #-}
Expand Down Expand Up @@ -278,7 +277,6 @@ instance ParseTime DayOfWeek where
in
rest cs

#ifdef __GLASGOW_HASKELL__
dayMonth :: Day -> Month
dayMonth (MonthDay m _) = m

Expand All @@ -296,7 +294,6 @@ instance ParseTime Month where
rest (_ : xs) = rest xs
rest [] = fromYearMonthValid y 1
rest cs
#endif

mfoldl :: Monad m => (a -> b -> m a) -> m a -> [b] -> m a
mfoldl f =
Expand Down

0 comments on commit cd652ae

Please sign in to comment.