[commit: ghc] master: Simplify Foreign.Marshal.Alloc functions with ScopedTypeVariables (f489c12)

git at git.haskell.org git at git.haskell.org
Sat Feb 10 07:12:05 UTC 2018


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

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

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

commit f489c12c9fe4e24dce55269e6998323fd1d9b2a4
Author: Ömer Sinan Ağacan <omeragacan at gmail.com>
Date:   Sat Feb 10 09:12:42 2018 +0300

    Simplify Foreign.Marshal.Alloc functions with ScopedTypeVariables
    
    Reviewers: hvr, bgamari, RyanGlScott
    
    Reviewed By: RyanGlScott
    
    Subscribers: RyanGlScott, rwbarton, thomie, carter
    
    Differential Revision: https://phabricator.haskell.org/D4401


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

f489c12c9fe4e24dce55269e6998323fd1d9b2a4
 libraries/base/Foreign/Marshal/Alloc.hs | 35 +++++++++++----------------------
 1 file changed, 12 insertions(+), 23 deletions(-)

diff --git a/libraries/base/Foreign/Marshal/Alloc.hs b/libraries/base/Foreign/Marshal/Alloc.hs
index 2a3c756..48ed7fb 100644
--- a/libraries/base/Foreign/Marshal/Alloc.hs
+++ b/libraries/base/Foreign/Marshal/Alloc.hs
@@ -1,5 +1,6 @@
 {-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE NoImplicitPrelude, MagicHash, UnboxedTuples #-}
+{-# LANGUAGE NoImplicitPrelude, MagicHash, UnboxedTuples,
+             ScopedTypeVariables #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -79,20 +80,14 @@ import GHC.Base
 -- no longer required.
 --
 {-# INLINE malloc #-}
-malloc :: Storable a => IO (Ptr a)
-malloc  = doMalloc undefined
-  where
-    doMalloc       :: Storable b => b -> IO (Ptr b)
-    doMalloc dummy  = mallocBytes (sizeOf dummy)
+malloc :: forall a . Storable a => IO (Ptr a)
+malloc  = mallocBytes (sizeOf (undefined :: a))
 
 -- |Like 'malloc' but memory is filled with bytes of value zero.
 --
 {-# INLINE calloc #-}
-calloc :: Storable a => IO (Ptr a)
-calloc = doCalloc undefined
-  where
-    doCalloc       :: Storable b => b -> IO (Ptr b)
-    doCalloc dummy = callocBytes (sizeOf dummy)
+calloc :: forall a . Storable a => IO (Ptr a)
+calloc = callocBytes (sizeOf (undefined :: a))
 
 -- |Allocate a block of memory of the given number of bytes.
 -- The block of memory is sufficiently aligned for any of the basic
@@ -117,11 +112,9 @@ callocBytes size = failWhenNULL "calloc" $ _calloc 1 (fromIntegral size)
 -- exception), so the pointer passed to @f@ must /not/ be used after this.
 --
 {-# INLINE alloca #-}
-alloca :: Storable a => (Ptr a -> IO b) -> IO b
-alloca  = doAlloca undefined
-  where
-    doAlloca       :: Storable a' => a' -> (Ptr a' -> IO b') -> IO b'
-    doAlloca dummy  = allocaBytesAligned (sizeOf dummy) (alignment dummy)
+alloca :: forall a b . Storable a => (Ptr a -> IO b) -> IO b
+alloca  =
+  allocaBytesAligned (sizeOf (undefined :: a)) (alignment (undefined :: a))
 
 -- |@'allocaBytes' n f@ executes the computation @f@, passing as argument
 -- a pointer to a temporarily allocated block of memory of @n@ bytes.
@@ -163,14 +156,10 @@ allocaBytesAligned (I# size) (I# align) action = IO $ \ s0 ->
 -- If the argument to 'realloc' is 'nullPtr', 'realloc' behaves like
 -- 'malloc'.
 --
-realloc :: Storable b => Ptr a -> IO (Ptr b)
-realloc  = doRealloc undefined
+realloc :: forall a b . Storable b => Ptr a -> IO (Ptr b)
+realloc ptr = failWhenNULL "realloc" (_realloc ptr size)
   where
-    doRealloc           :: Storable b' => b' -> Ptr a' -> IO (Ptr b')
-    doRealloc dummy ptr  = let
-                             size = fromIntegral (sizeOf dummy)
-                           in
-                           failWhenNULL "realloc" (_realloc ptr size)
+    size = fromIntegral (sizeOf (undefined :: b))
 
 -- |Resize a memory area that was allocated with 'malloc' or 'mallocBytes'
 -- to the given size.  The returned pointer may refer to an entirely



More information about the ghc-commits mailing list