[commit: ghc] master: Eliminate some unsafeCoerce#s with deriving strategies (f547b44)

git at git.haskell.org git at git.haskell.org
Sun Oct 2 00:02:12 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/f547b444fdaf1c86abede42bf4c4b1037f50f588/ghc

>---------------------------------------------------------------

commit f547b444fdaf1c86abede42bf4c4b1037f50f588
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Sat Oct 1 17:58:27 2016 -0400

    Eliminate some unsafeCoerce#s with deriving strategies
    
    Currently, `Foreign.C.Types`, `Foreign.Ptr`, and `System.Posix.Types`
    define `Read` and `Show` instances for the newtypes in those modules by
    using `unsafeCoerce#`. We can clean up this hack by using the `newtype`
    deriving strategy.
    
    Reviewers: hvr, austin, bgamari
    
    Reviewed By: bgamari
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D2556


>---------------------------------------------------------------

f547b444fdaf1c86abede42bf4c4b1037f50f588
 libraries/base/Foreign/C/Types.hs    |  8 ++++++--
 libraries/base/Foreign/Ptr.hs        |  8 ++++++--
 libraries/base/System/Posix/Types.hs | 12 ++++++------
 libraries/base/include/CTypes.h      | 31 ++++++++-----------------------
 4 files changed, 26 insertions(+), 33 deletions(-)

diff --git a/libraries/base/Foreign/C/Types.hs b/libraries/base/Foreign/C/Types.hs
index 6d084bf..f76ff1c 100644
--- a/libraries/base/Foreign/C/Types.hs
+++ b/libraries/base/Foreign/C/Types.hs
@@ -1,6 +1,10 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE DerivingStrategies #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE StandaloneDeriving #-}
 {-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash, GeneralizedNewtypeDeriving,
-             StandaloneDeriving #-}
 {-# OPTIONS_GHC -Wno-unused-binds #-}
 -- XXX -Wno-unused-binds stops us warning about unused constructors,
 -- but really we should just remove them if we don't want them
diff --git a/libraries/base/Foreign/Ptr.hs b/libraries/base/Foreign/Ptr.hs
index 5e6bccf..45e6cf5 100644
--- a/libraries/base/Foreign/Ptr.hs
+++ b/libraries/base/Foreign/Ptr.hs
@@ -1,6 +1,10 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE DerivingStrategies #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE StandaloneDeriving #-}
 {-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash, GeneralizedNewtypeDeriving,
-             StandaloneDeriving #-}
 
 -----------------------------------------------------------------------------
 -- |
diff --git a/libraries/base/System/Posix/Types.hs b/libraries/base/System/Posix/Types.hs
index 52fce87..67c38aa 100644
--- a/libraries/base/System/Posix/Types.hs
+++ b/libraries/base/System/Posix/Types.hs
@@ -1,10 +1,10 @@
-{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE CPP
-           , NoImplicitPrelude
-           , MagicHash
-           , GeneralizedNewtypeDeriving
-  #-}
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE DerivingStrategies #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE NoImplicitPrelude #-}
 {-# LANGUAGE StandaloneDeriving #-}
+{-# LANGUAGE Trustworthy #-}
 
 -----------------------------------------------------------------------------
 -- |
diff --git a/libraries/base/include/CTypes.h b/libraries/base/include/CTypes.h
index d821d66..9cee4f7 100644
--- a/libraries/base/include/CTypes.h
+++ b/libraries/base/include/CTypes.h
@@ -21,34 +21,19 @@
 #define FLOATING_CLASSES Fractional,Floating,RealFrac,RealFloat
 
 #define ARITHMETIC_TYPE(T,B) \
-newtype T = T B deriving (ARITHMETIC_CLASSES); \
-INSTANCE_READ(T,B); \
-INSTANCE_SHOW(T,B);
+newtype T = T B deriving (ARITHMETIC_CLASSES) \
+                deriving newtype (Read, Show);
 
 #define INTEGRAL_TYPE(T,B) \
-newtype T = T B deriving (ARITHMETIC_CLASSES, INTEGRAL_CLASSES); \
-INSTANCE_READ(T,B); \
-INSTANCE_SHOW(T,B);
+newtype T = T B deriving (ARITHMETIC_CLASSES, INTEGRAL_CLASSES) \
+                deriving newtype (Read, Show);
 
 #define INTEGRAL_TYPE_WITH_CTYPE(T,THE_CTYPE,B) \
-newtype {-# CTYPE "THE_CTYPE" #-} T = T B deriving (ARITHMETIC_CLASSES, INTEGRAL_CLASSES); \
-INSTANCE_READ(T,B); \
-INSTANCE_SHOW(T,B);
+newtype {-# CTYPE "THE_CTYPE" #-} T = T B deriving (ARITHMETIC_CLASSES, INTEGRAL_CLASSES) \
+                                          deriving newtype (Read, Show);
 
 #define FLOATING_TYPE(T,B) \
-newtype T = T B deriving (ARITHMETIC_CLASSES, FLOATING_CLASSES); \
-INSTANCE_READ(T,B); \
-INSTANCE_SHOW(T,B);
-
-#define INSTANCE_READ(T,B) \
-instance Read T where { \
-   readsPrec            = unsafeCoerce# (readsPrec :: Int -> ReadS B); \
-   readList             = unsafeCoerce# (readList  :: ReadS [B]); }
-
-#define INSTANCE_SHOW(T,B) \
-instance Show T where { \
-   showsPrec            = unsafeCoerce# (showsPrec :: Int -> B -> ShowS); \
-   show                 = unsafeCoerce# (show :: B -> String); \
-   showList             = unsafeCoerce# (showList :: [B] -> ShowS); }
+newtype T = T B deriving (ARITHMETIC_CLASSES, FLOATING_CLASSES) \
+                deriving newtype (Read, Show);
 
 #endif



More information about the ghc-commits mailing list