1 patch for repository http://code.haskell.org/time:

Wed Nov 28 14:58:44 GMT Standard Time 2012  jpm@cs.ox.ac.uk
  * Derive Typeable instances

New patches:

[Derive Typeable instances
jpm@cs.ox.ac.uk**20121128145844
 Ignore-this: d301bb00a270f5c27cf9bffc27f85828
] {
hunk ./Data/Time/Calendar/Days.hs 21
 newtype Day = ModifiedJulianDay {toModifiedJulianDay :: Integer} deriving (Eq,Ord
 #if LANGUAGE_DeriveDataTypeable
 #if LANGUAGE_Rank2Types
-    ,Data
+    ,Data, Typeable
 #endif
 #endif
     )
hunk ./Data/Time/Calendar/Days.hs 29
 instance NFData Day where
 	rnf (ModifiedJulianDay a) = rnf a
 
-instance Typeable Day where
-	typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.Calendar.Days" "Day") []
-
 -- necessary because H98 doesn't have "cunning newtype" derivation
 instance Enum Day where
 	succ (ModifiedJulianDay a) = ModifiedJulianDay (succ a)
hunk ./Data/Time/Clock/Scale.hs 28
 newtype UniversalTime = ModJulianDate {getModJulianDate :: Rational} deriving (Eq,Ord
 #if LANGUAGE_DeriveDataTypeable
 #if LANGUAGE_Rank2Types
-    ,Data
+    ,Data, Typeable
 #endif
 #endif
     )
hunk ./Data/Time/Clock/Scale.hs 37
 instance NFData UniversalTime where
 	rnf (ModJulianDate a) = rnf a
 
-instance Typeable UniversalTime where
-	typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.Clock.Scale" "UniversalTime") []
-
 -- | This is a length of time, as measured by a clock.
 -- Conversion functions will treat it as seconds.
 -- It has a precision of 10^-12 s.
hunk ./Data/Time/Clock/Scale.hs 44
 #if LANGUAGE_DeriveDataTypeable
 #if LANGUAGE_Rank2Types
 #if HAS_DataPico
-    ,Data
+    ,Data, Typeable
 #else
 #endif
 #endif
hunk ./Data/Time/Clock/Scale.hs 54
 -- necessary because H98 doesn't have "cunning newtype" derivation
 instance NFData DiffTime -- FIXME: Data.Fixed had no NFData instances yet at time of writing
 
-instance Typeable DiffTime where
-	typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.Clock.Scale" "DiffTime") []
-
 -- necessary because H98 doesn't have "cunning newtype" derivation
 instance Enum DiffTime where
 	succ (MkDiffTime a) = MkDiffTime (succ a)
hunk ./Data/Time/Clock/TAI.hs 33
 #if LANGUAGE_DeriveDataTypeable
 #if LANGUAGE_Rank2Types
 #if HAS_DataPico
-    ,Data
+    ,Data, Typeable
 #endif
 #endif
 #endif
hunk ./Data/Time/Clock/TAI.hs 42
 instance NFData AbsoluteTime where
 	rnf (MkAbsoluteTime a) = rnf a
 
-instance Typeable AbsoluteTime where
-	typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.Clock.TAI" "AbsoluteTime") []
-
 instance Show AbsoluteTime where
 	show t = show (utcToLocalTime utc (taiToUTCTime (const 0) t)) ++ " TAI" -- ugly, but standard apparently
 
hunk ./Data/Time/Clock/UTC.hs 39
 #if LANGUAGE_DeriveDataTypeable
 #if LANGUAGE_Rank2Types
 #if HAS_DataPico
-    deriving (Data)
+    deriving (Data, Typeable)
 #endif
 #endif
 #endif
hunk ./Data/Time/Clock/UTC.hs 47
 instance NFData UTCTime where
 	rnf (UTCTime d t) = d `deepseq` t `deepseq` ()
 
-instance Typeable UTCTime where
-	typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.Clock.UTC" "UTCTime") []
-
 instance Eq UTCTime where
 	(UTCTime da ta) == (UTCTime db tb) = (da == db) && (ta == tb)
 
hunk ./Data/Time/Clock/UTC.hs 65
 #if LANGUAGE_DeriveDataTypeable
 #if LANGUAGE_Rank2Types
 #if HAS_DataPico
-    ,Data
+    ,Data, Typeable
 #endif
 #endif
 #endif
hunk ./Data/Time/Clock/UTC.hs 74
 -- necessary because H98 doesn't have "cunning newtype" derivation
 instance NFData NominalDiffTime -- FIXME: Data.Fixed had no NFData instances yet at time of writing
 
-instance Typeable NominalDiffTime where
-	typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.Clock.UTC" "NominalDiffTime") []
-
 instance Enum NominalDiffTime where
 	succ (MkNominalDiffTime a) = MkNominalDiffTime (succ a)
 	pred (MkNominalDiffTime a) = MkNominalDiffTime (pred a)
hunk ./Data/Time/LocalTime/LocalTime.hs 37
 #if LANGUAGE_DeriveDataTypeable
 #if LANGUAGE_Rank2Types
 #if HAS_DataPico
-    ,Data
+    ,Data, Typeable
 #endif
 #endif
 #endif
hunk ./Data/Time/LocalTime/LocalTime.hs 46
 instance NFData LocalTime where
 	rnf (LocalTime d t) = d `deepseq` t `deepseq` ()
 
-instance Typeable LocalTime where
-	typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.LocalTime.LocalTime" "LocalTime") []
-
 instance Show LocalTime where
 	show (LocalTime d t) = (showGregorian d) ++ " " ++ (show t)
 
hunk ./Data/Time/LocalTime/LocalTime.hs 78
 #if LANGUAGE_DeriveDataTypeable
 #if LANGUAGE_Rank2Types
 #if HAS_DataPico
-    deriving (Data)
+    deriving (Data, Typeable)
 #endif
 #endif
 #endif
hunk ./Data/Time/LocalTime/LocalTime.hs 86
 instance NFData ZonedTime where
 	rnf (ZonedTime lt z) = lt `deepseq` z `deepseq` ()
 
-instance Typeable ZonedTime where
-	typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.LocalTime.LocalTime" "ZonedTime") []
-
 utcToZonedTime :: TimeZone -> UTCTime -> ZonedTime
 utcToZonedTime zone time = ZonedTime (utcToLocalTime zone time) zone
 
hunk ./Data/Time/LocalTime/TimeOfDay.hs 36
 #if LANGUAGE_DeriveDataTypeable
 #if LANGUAGE_Rank2Types
 #if HAS_DataPico
-    ,Data
+    ,Data, Typeable
 #endif
 #endif
 #endif
hunk ./Data/Time/LocalTime/TimeOfDay.hs 45
 instance NFData TimeOfDay where
 	rnf (TimeOfDay h m s) = h `deepseq` m `deepseq` s `seq` () -- FIXME: Data.Fixed had no NFData instances yet at time of writing
 
-instance Typeable TimeOfDay where
-	typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.LocalTime.TimeOfDay" "TimeOfDay") []
-
 -- | Hour zero
 midnight :: TimeOfDay
 midnight = TimeOfDay 0 0 0
hunk ./Data/Time/LocalTime/TimeZone.hs 39
 } deriving (Eq,Ord
 #if LANGUAGE_DeriveDataTypeable
 #if LANGUAGE_Rank2Types
-    ,Data
+    ,Data, Typeable
 #endif
 #endif
     )
hunk ./Data/Time/LocalTime/TimeZone.hs 47
 instance NFData TimeZone where
 	rnf (TimeZone m so n) = m `deepseq` so `deepseq` n `deepseq` ()
 
-instance Typeable TimeZone where
-	typeOf _ = mkTyConApp (mkTyCon3 "time" "Data.Time.LocalTime.TimeZone" "TimeZone") []
-
 -- | Create a nameless non-summer timezone for this number of minutes
 minutesToTimeZone :: Int -> TimeZone
 minutesToTimeZone m = TimeZone m False ""
}

Context:

[TAG 1.4.0.2
Ashley Yakeley <ashley@semantic.org>**20121125114638
 Ignore-this: 98e1ea7dd0be75c1634ebdbb185bed02
] 
Patch bundle hash:
e8297b4500b3440c0d023a7e1cac847a6d76b612
