[commit: ghc] ghc-8.0: Make a constraint synonym for repeated BinaryStringRep and use it. (c698f1f)

git at git.haskell.org git at git.haskell.org
Fri Jan 22 12:20:15 UTC 2016


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

On branch  : ghc-8.0
Link       : http://ghc.haskell.org/trac/ghc/changeset/c698f1f322fded4609f326e6e6f5866f821721a1/ghc

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

commit c698f1f322fded4609f326e6e6f5866f821721a1
Author: Edward Z. Yang <ezyang at cs.stanford.edu>
Date:   Thu Jan 21 19:27:58 2016 +0100

    Make a constraint synonym for repeated BinaryStringRep and use it.
    
    Test Plan: validate
    
    Reviewers: austin, thomie, bgamari
    
    Reviewed By: thomie, bgamari
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D1810
    
    (cherry picked from commit adb721bd0eb60ab4c55d5197933e8090fe6297c5)


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

c698f1f322fded4609f326e6e6f5866f821721a1
 libraries/ghc-boot/GHC/PackageDb.hs | 19 +++++++++++--------
 1 file changed, 11 insertions(+), 8 deletions(-)

diff --git a/libraries/ghc-boot/GHC/PackageDb.hs b/libraries/ghc-boot/GHC/PackageDb.hs
index cc03c3b..7ca6497 100644
--- a/libraries/ghc-boot/GHC/PackageDb.hs
+++ b/libraries/ghc-boot/GHC/PackageDb.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE ConstraintKinds #-}
 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
 -----------------------------------------------------------------------------
 -- |
@@ -92,6 +93,12 @@ data InstalledPackageInfo srcpkgid srcpkgname unitid modulename
      }
   deriving (Eq, Show)
 
+-- | A convenience constraint synonym for common constraints over parameters
+-- to 'InstalledPackageInfo'.
+type RepInstalledPackageInfo srcpkgid srcpkgname unitid modulename =
+    (BinaryStringRep srcpkgid, BinaryStringRep srcpkgname,
+     BinaryStringRep unitid, BinaryStringRep modulename)
+
 -- | An original module is a fully-qualified module name (installed package ID
 -- plus module name) representing where a module was *originally* defined
 -- (i.e., the 'exposedReexport' field of the original ExposedModule entry should
@@ -127,8 +134,7 @@ class BinaryStringRep a where
   fromStringRep :: BS.ByteString -> a
   toStringRep   :: a -> BS.ByteString
 
-emptyInstalledPackageInfo :: (BinaryStringRep a, BinaryStringRep b,
-                              BinaryStringRep c)
+emptyInstalledPackageInfo :: RepInstalledPackageInfo a b c d
                           => InstalledPackageInfo a b c d
 emptyInstalledPackageInfo =
   InstalledPackageInfo {
@@ -159,8 +165,7 @@ emptyInstalledPackageInfo =
 
 -- | Read the part of the package DB that GHC is interested in.
 --
-readPackageDbForGhc :: (BinaryStringRep a, BinaryStringRep b, BinaryStringRep c,
-                        BinaryStringRep d) =>
+readPackageDbForGhc :: RepInstalledPackageInfo a b c d =>
                        FilePath -> IO [InstalledPackageInfo a b c d]
 readPackageDbForGhc file =
     decodeFromFile file getDbForGhc
@@ -193,8 +198,7 @@ readPackageDbForGhcPkg file =
 
 -- | Write the whole of the package DB, both parts.
 --
-writePackageDb :: (Binary pkgs, BinaryStringRep a, BinaryStringRep b,
-                   BinaryStringRep c, BinaryStringRep d) =>
+writePackageDb :: (Binary pkgs, RepInstalledPackageInfo a b c d) =>
                   FilePath -> [InstalledPackageInfo a b c d] -> pkgs -> IO ()
 writePackageDb file ghcPkgs ghcPkgPart =
     writeFileAtomic file (runPut putDbForGhcPkg)
@@ -281,8 +285,7 @@ writeFileAtomic targetPath content = do
         hClose handle
         renameFile tmpPath targetPath)
 
-instance (BinaryStringRep a, BinaryStringRep b, BinaryStringRep c,
-          BinaryStringRep d) =>
+instance (RepInstalledPackageInfo a b c d) =>
          Binary (InstalledPackageInfo a b c d) where
   put (InstalledPackageInfo
          unitId sourcePackageId



More information about the ghc-commits mailing list