Skip to content

Commit

Permalink
Merge pull request #264 from augustss/master
Browse files Browse the repository at this point in the history
Revert some MicroHs changes
  • Loading branch information
AshleyYakeley authored Nov 18, 2024
2 parents 7ed8fc1 + 6e90e84 commit 17878bc
Show file tree
Hide file tree
Showing 15 changed files with 13 additions and 102 deletions.
2 changes: 1 addition & 1 deletion .github/workflows/ci.mhs.yml
Original file line number Diff line number Diff line change
Expand Up @@ -43,4 +43,4 @@ jobs:
./ShowTime
- name: cleanup
run: |
rm -rf $HOME/.cabal
rm -rf $HOME/.mcabal
5 changes: 0 additions & 5 deletions lib/Data/Time/Calendar/CalendarDiffDays.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

module Data.Time.Calendar.CalendarDiffDays (
Expand All @@ -8,10 +7,8 @@ module Data.Time.Calendar.CalendarDiffDays (

import Control.DeepSeq
import Data.Data
#ifdef __GLASGOW_HASKELL__
import GHC.Generics
import qualified Language.Haskell.TH.Syntax as TH
#endif

data CalendarDiffDays = CalendarDiffDays
{ cdMonths :: Integer
Expand All @@ -23,12 +20,10 @@ data CalendarDiffDays = CalendarDiffDays
Data
, -- | @since 1.9.2
Typeable
#ifdef __GLASGOW_HASKELL__
, -- | @since 1.14
TH.Lift
, -- | @since 1.14
Generic
#endif
)

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

module Data.Time.Calendar.Days (
Expand All @@ -19,20 +18,14 @@ module Data.Time.Calendar.Days (
import Control.DeepSeq
import Data.Data
import Data.Ix
#ifdef __GLASGOW_HASKELL__
import GHC.Generics
import qualified Language.Haskell.TH.Syntax as TH
#endif

-- | The Modified Julian Day is a standard count of days, with zero being the day 1858-11-17.
newtype Day = ModifiedJulianDay
{ toModifiedJulianDay :: Integer
}
deriving (Eq, Ord, Data, Typeable
#ifdef __GLASGOW_HASKELL__
, TH.Lift, Generic
#endif
)
deriving (Eq, Ord, Data, Typeable, TH.Lift, Generic)

instance NFData Day where
rnf (ModifiedJulianDay a) = rnf a
Expand Down
8 changes: 1 addition & 7 deletions lib/Data/Time/Calendar/Month.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,20 +21,14 @@ import Data.Ix
import Data.Time.Calendar.Days
import Data.Time.Calendar.Gregorian
import Data.Time.Calendar.Private
#if __GLASGOW_HASKELL__
import GHC.Generics
import qualified Language.Haskell.TH.Syntax as TH
#endif
import Text.ParserCombinators.ReadP
import Text.Read

-- | An absolute count of common calendar months.
-- Number is equal to @(year * 12) + (monthOfYear - 1)@.
newtype Month = MkMonth Integer deriving (Eq, Ord, Data, Typeable
#if __GLASGOW_HASKELL__
, TH.Lift, Generic
#endif
)
newtype Month = MkMonth Integer deriving (Eq, Ord, Data, Typeable, TH.Lift, Generic)

instance NFData Month where
rnf (MkMonth m) = rnf m
Expand Down
14 changes: 2 additions & 12 deletions lib/Data/Time/Calendar/Quarter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,19 +29,13 @@ import Data.Time.Calendar.Days
import Data.Time.Calendar.Month
import Data.Time.Calendar.Private
import Data.Time.Calendar.Types
#ifdef __GLASGOW_HASKELL__
import GHC.Generics
import qualified Language.Haskell.TH.Syntax as TH
#endif
import Text.ParserCombinators.ReadP
import Text.Read

-- | Quarters of each year. Each quarter corresponds to three months.
data QuarterOfYear = Q1 | Q2 | Q3 | Q4 deriving (Eq, Ord, Data, Typeable, Read, Show, Ix
#ifdef __GLASGOW_HASKELL__
, TH.Lift, Generic
#endif
)
data QuarterOfYear = Q1 | Q2 | Q3 | Q4 deriving (Eq, Ord, Data, Typeable, Read, Show, Ix, TH.Lift, Generic)

-- | maps Q1..Q4 to 1..4
instance Enum QuarterOfYear where
Expand All @@ -68,11 +62,7 @@ instance NFData QuarterOfYear where

-- | An absolute count of year quarters.
-- Number is equal to @(year * 4) + (quarterOfYear - 1)@.
newtype Quarter = MkQuarter Integer deriving (Eq, Ord, Data, Typeable
#ifdef __GLASGOW_HASKELL__
, Generic
#endif
)
newtype Quarter = MkQuarter Integer deriving (Eq, Ord, Data, Typeable, Generic)

instance NFData Quarter where
rnf (MkQuarter m) = rnf m
Expand Down
9 changes: 1 addition & 8 deletions lib/Data/Time/Calendar/Week.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

module Data.Time.Calendar.Week (
Expand All @@ -17,10 +16,8 @@ import Data.Data
import Data.Fixed
import Data.Ix
import Data.Time.Calendar.Days
#ifdef __GLASGOW_HASKELL__
import GHC.Generics
import qualified Language.Haskell.TH.Syntax as TH
#endif

data DayOfWeek
= Monday
Expand All @@ -30,11 +27,7 @@ data DayOfWeek
| Friday
| Saturday
| Sunday
deriving (Eq, Show, Read, Data, Typeable, Ord, Ix
#ifdef __GLASGOW_HASKELL__
, TH.Lift, Generic
#endif
)
deriving (Eq, Show, Read, Data, Typeable, Ord, Ix, TH.Lift, Generic)

instance NFData DayOfWeek where
rnf Monday = ()
Expand Down
1 change: 0 additions & 1 deletion lib/Data/Time/Clock/Internal/DiffTime.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,6 @@ import qualified Language.Haskell.TH.Syntax as TH
#endif
import Text.Read
import Text.ParserCombinators.ReadP
import Text.ParserCombinators.ReadPrec

-- | This is a length of time, as measured by a clock.
-- Conversion functions such as 'fromInteger' and 'realToFrac' will treat it as seconds.
Expand Down
8 changes: 1 addition & 7 deletions lib/Data/Time/Clock/Internal/SystemTime.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,10 +22,8 @@ import Data.Data
import Data.Int (Int64)
import Data.Time.Clock.Internal.DiffTime
import Data.Word
#ifdef __GLASGOW_HASKELL__
import GHC.Generics
import qualified Language.Haskell.TH.Syntax as TH
#endif

#ifdef mingw32_HOST_OS
import qualified System.Win32.Time as Win32
Expand All @@ -45,11 +43,7 @@ data SystemTime = MkSystemTime
{ systemSeconds :: {-# UNPACK #-} !Int64
, systemNanoseconds :: {-# UNPACK #-} !Word32
}
deriving (Eq, Ord, Show, Data, Typeable
#ifdef __GLASGOW_HASKELL__
, TH.Lift, Generic
#endif
)
deriving (Eq, Ord, Show, Data, Typeable, TH.Lift, Generic)

instance NFData SystemTime where
rnf a = a `seq` ()
Expand Down
9 changes: 1 addition & 8 deletions lib/Data/Time/Clock/Internal/UTCTime.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

module Data.Time.Clock.Internal.UTCTime (
Expand All @@ -19,10 +18,8 @@ import Control.DeepSeq
import Data.Data
import Data.Time.Calendar.Days
import Data.Time.Clock.Internal.DiffTime
#ifdef __GLASGOW_HASKELL__
import GHC.Generics
import qualified Language.Haskell.TH.Syntax as TH
#endif

-- | This is the simplest representation of UTC.
-- It consists of the day number, and a time offset from midnight.
Expand All @@ -33,11 +30,7 @@ data UTCTime = UTCTime
, utctDayTime :: DiffTime
-- ^ the time from midnight, 0 <= t < 86401s (because of leap-seconds)
}
deriving (Data, Typeable
#ifdef __GLASGOW_HASKELL__
, TH.Lift, Generic
#endif
)
deriving (Data, Typeable, TH.Lift, Generic)

instance NFData UTCTime where
rnf (UTCTime d t) = rnf d `seq` rnf t `seq` ()
Expand Down
9 changes: 1 addition & 8 deletions lib/Data/Time/Clock/Internal/UniversalTime.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

module Data.Time.Clock.Internal.UniversalTime (
Expand All @@ -10,21 +9,15 @@ module Data.Time.Clock.Internal.UniversalTime (

import Control.DeepSeq
import Data.Data
#ifdef __GLASGOW_HASKELL__
import GHC.Generics
import qualified Language.Haskell.TH.Syntax as TH
#endif

-- | The Modified Julian Date is the day with the fraction of the day, measured from UT midnight.
-- It's used to represent UT1, which is time as measured by the earth's rotation, adjusted for various wobbles.
newtype UniversalTime = ModJulianDate
{ getModJulianDate :: Rational
}
deriving (Eq, Ord, Data, Typeable
#ifdef __GLASGOW_HASKELL__
, TH.Lift, Generic
#endif
)
deriving (Eq, Ord, Data, Typeable, TH.Lift, Generic)

instance NFData UniversalTime where
rnf (ModJulianDate a) = rnf a
5 changes: 0 additions & 5 deletions lib/Data/Time/LocalTime/Internal/CalendarDiffTime.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

module Data.Time.LocalTime.Internal.CalendarDiffTime (
Expand All @@ -10,9 +9,7 @@ import Control.DeepSeq
import Data.Data
import Data.Time.Calendar.CalendarDiffDays
import Data.Time.Clock.Internal.NominalDiffTime
#ifdef __GLASGOW_HASKELL__
import GHC.Generics
#endif

data CalendarDiffTime = CalendarDiffTime
{ ctMonths :: Integer
Expand All @@ -24,9 +21,7 @@ data CalendarDiffTime = CalendarDiffTime
Data
, -- | @since 1.9.2
Typeable
#ifdef __GLASGOW_HASKELL__
, Generic
#endif
)

instance NFData CalendarDiffTime where
Expand Down
9 changes: 1 addition & 8 deletions lib/Data/Time/LocalTime/Internal/LocalTime.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

{-# OPTIONS -fno-warn-orphans #-}
Expand All @@ -25,9 +24,7 @@ import Data.Time.Clock.Internal.UTCTime
import Data.Time.Clock.Internal.UniversalTime
import Data.Time.LocalTime.Internal.TimeOfDay
import Data.Time.LocalTime.Internal.TimeZone
#ifdef __GLASGOW_HASKELL__
import GHC.Generics
#endif

-- | A simple day and time aggregate, where the day is of the specified parameter,
-- and the time is a TimeOfDay.
Expand All @@ -37,11 +34,7 @@ data LocalTime = LocalTime
{ localDay :: Day
, localTimeOfDay :: TimeOfDay
}
deriving (Eq, Ord, Data, Typeable
#ifdef __GLASGOW_HASKELL__
, Generic
#endif
)
deriving (Eq, Ord, Data, Typeable, Generic)

instance NFData LocalTime where
rnf (LocalTime d t) = rnf d `seq` rnf t `seq` ()
Expand Down
9 changes: 1 addition & 8 deletions lib/Data/Time/LocalTime/Internal/TimeOfDay.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

module Data.Time.LocalTime.Internal.TimeOfDay (
Expand Down Expand Up @@ -26,9 +25,7 @@ import Data.Time.Calendar.Private
import Data.Time.Clock.Internal.DiffTime
import Data.Time.Clock.Internal.NominalDiffTime
import Data.Time.LocalTime.Internal.TimeZone
#ifdef __GLASGOW_HASKELL__
import GHC.Generics
#endif

-- | Time of day as represented in hour, minute and second (with picoseconds), typically used to express local time of day.
--
Expand All @@ -43,11 +40,7 @@ data TimeOfDay = TimeOfDay
-- ^ Note that 0 <= 'todSec' < 61, accomodating leap seconds.
-- Any local minute may have a leap second, since leap seconds happen in all zones simultaneously
}
deriving (Eq, Ord, Data, Typeable
#ifdef __GLASGOW_HASKELL__
, Generic
#endif
)
deriving (Eq, Ord, Data, Typeable, Generic)

instance NFData TimeOfDay where
rnf (TimeOfDay h m s) = rnf h `seq` rnf m `seq` rnf s `seq` ()
Expand Down
9 changes: 1 addition & 8 deletions lib/Data/Time/LocalTime/Internal/TimeZone.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE Safe #-}

Expand All @@ -24,9 +23,7 @@ import Data.Time.Clock.POSIX
import Data.Time.Clock.System
import Foreign
import Foreign.C
#ifdef __GLASGOW_HASKELL__
import GHC.Generics
#endif

-- | A TimeZone is a whole number of minutes offset from UTC, together with a name and a \"just for summer\" flag.
data TimeZone = TimeZone
Expand All @@ -37,11 +34,7 @@ data TimeZone = TimeZone
, timeZoneName :: String
-- ^ The name of the zone, typically a three- or four-letter acronym.
}
deriving (Eq, Ord, Data, Typeable
#ifdef __GLASGOW_HASKELL__
, Generic
#endif
)
deriving (Eq, Ord, Data, Typeable, Generic)

instance NFData TimeZone where
rnf (TimeZone m so n) = rnf m `seq` rnf so `seq` rnf n `seq` ()
Expand Down
9 changes: 1 addition & 8 deletions lib/Data/Time/LocalTime/Internal/ZonedTime.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

{-# OPTIONS -fno-warn-orphans #-}
Expand All @@ -17,9 +16,7 @@ import Data.Time.Clock.Internal.UTCTime
import Data.Time.Clock.POSIX
import Data.Time.LocalTime.Internal.LocalTime
import Data.Time.LocalTime.Internal.TimeZone
#ifdef __GLASGOW_HASKELL__
import GHC.Generics
#endif

-- | A local time together with a time zone.
--
Expand All @@ -30,11 +27,7 @@ data ZonedTime = ZonedTime
{ zonedTimeToLocalTime :: LocalTime
, zonedTimeZone :: TimeZone
}
deriving (Data, Typeable
#ifdef __GLASGOW_HASKELL__
, Generic
#endif
)
deriving (Data, Typeable, Generic)

instance NFData ZonedTime where
rnf (ZonedTime lt z) = rnf lt `seq` rnf z `seq` ()
Expand Down

0 comments on commit 17878bc

Please sign in to comment.