[project @ 2004-12-23 00:02:41 by ralf]
authorralf <unknown>
Thu, 23 Dec 2004 00:02:42 +0000 (00:02 +0000)
committerralf <unknown>
Thu, 23 Dec 2004 00:02:42 +0000 (00:02 +0000)
Resolved stage1 issues related SPJ's
commit "Add more scoped type variables".
Incidentally, this provides some input for
the recent GHC list discussion on whether
to provide lex. scope for function signatures.
Not too many modules are affected! Good!

The example hslibs/data/edison/Seq/BinaryRandList.hs
was interesting in so far that indeed up-front
function signatures were given in one shot, so
one is really a bit confused to see type variables
in where clauses to clash with far-removed top-level
function signatures.

Ralf

Data/Generics/Text.hs
Data/Tree.hs
Foreign/ForeignPtr.hs
Foreign/Marshal/Alloc.hs
Foreign/Marshal/Array.hs
Foreign/Marshal/Pool.hs
GHC/ForeignPtr.hs

index 1ad767f..61ad5a7 100644 (file)
@@ -68,7 +68,7 @@ gread = readP_to_S gread'
  where
 
   -- Helper for recursive read
  where
 
   -- Helper for recursive read
-  gread' :: Data a => ReadP a
+  gread' :: Data a' => ReadP a'
   gread' = allButString `extR` stringCase
 
    where
   gread' = allButString `extR` stringCase
 
    where
@@ -80,7 +80,7 @@ gread = readP_to_S gread'
     -- Determine result type
     myDataType = dataTypeOf (getArg allButString)
      where
     -- Determine result type
     myDataType = dataTypeOf (getArg allButString)
      where
-      getArg :: ReadP a -> a
+      getArg :: ReadP a'' -> a''
       getArg = undefined
 
     -- The generic default for gread
       getArg = undefined
 
     -- The generic default for gread
index b9d2c54..5d91af8 100644 (file)
@@ -116,7 +116,7 @@ unfoldTreeM_BF f b = liftM (fst . fromJust . deQueue) $
 -- by Chris Okasaki, /ICFP'00/.
 unfoldForestM_BF :: Monad m => (b -> m (a, [b])) -> [b] -> m (Forest a)
 unfoldForestM_BF f = liftM (reverseOnto []) . unfoldForestQ f . listToQueue
 -- by Chris Okasaki, /ICFP'00/.
 unfoldForestM_BF :: Monad m => (b -> m (a, [b])) -> [b] -> m (Forest a)
 unfoldForestM_BF f = liftM (reverseOnto []) . unfoldForestQ f . listToQueue
-  where reverseOnto :: [a] -> Queue a -> [a]
+  where reverseOnto :: [a'] -> Queue a' -> [a']
        reverseOnto as q = case deQueue q of
                Nothing -> as
                Just (a, q') -> reverseOnto (a:as) q'
        reverseOnto as q = case deQueue q of
                Nothing -> as
                Just (a, q') -> reverseOnto (a:as) q'
@@ -131,7 +131,7 @@ unfoldForestQ f aQ = case deQueue aQ of
                tQ <- unfoldForestQ f (foldl addToQueue aQ as)
                let (ts, tQ') = splitOnto [] as tQ
                return (addToQueue tQ' (Node b ts))
                tQ <- unfoldForestQ f (foldl addToQueue aQ as)
                let (ts, tQ') = splitOnto [] as tQ
                return (addToQueue tQ' (Node b ts))
-  where splitOnto :: [a] -> [b] -> Queue a -> ([a], Queue a)
+  where splitOnto :: [a'] -> [b'] -> Queue a' -> ([a'], Queue a')
        splitOnto as [] q = (as, q)
        splitOnto as (_:bs) q = case fromJust (deQueue q) of
                (a, q') -> splitOnto (a:as) bs q'
        splitOnto as [] q = (as, q)
        splitOnto as (_:bs) q = case fromJust (deQueue q) of
                (a, q') -> splitOnto (a:as) bs q'
index a0bccf5..63e0b25 100644 (file)
@@ -174,7 +174,7 @@ mallocForeignPtrBytes n = do
 mallocForeignPtrArray :: Storable a => Int -> IO (ForeignPtr a)
 mallocForeignPtrArray  = doMalloc undefined
   where
 mallocForeignPtrArray :: Storable a => Int -> IO (ForeignPtr a)
 mallocForeignPtrArray  = doMalloc undefined
   where
-    doMalloc            :: Storable a => a -> Int -> IO (ForeignPtr a)
+    doMalloc            :: Storable b => b -> Int -> IO (ForeignPtr b)
     doMalloc dummy size  = mallocForeignPtrBytes (size * sizeOf dummy)
 
 -- | This function is similar to 'Foreign.Marshal.Array.mallocArray0',
     doMalloc dummy size  = mallocForeignPtrBytes (size * sizeOf dummy)
 
 -- | This function is similar to 'Foreign.Marshal.Array.mallocArray0',
index dbd3644..65588ff 100644 (file)
@@ -68,7 +68,7 @@ import Hugs.ForeignPtr                ( FinalizerPtr )
 malloc :: Storable a => IO (Ptr a)
 malloc  = doMalloc undefined
   where
 malloc :: Storable a => IO (Ptr a)
 malloc  = doMalloc undefined
   where
-    doMalloc       :: Storable a => a -> IO (Ptr a)
+    doMalloc       :: Storable b => b -> IO (Ptr b)
     doMalloc dummy  = mallocBytes (sizeOf dummy)
 
 -- |Allocate a block of memory of the given number of bytes.
     doMalloc dummy  = mallocBytes (sizeOf dummy)
 
 -- |Allocate a block of memory of the given number of bytes.
@@ -91,7 +91,7 @@ mallocBytes size  = failWhenNULL "malloc" (_malloc (fromIntegral size))
 alloca :: Storable a => (Ptr a -> IO b) -> IO b
 alloca  = doAlloca undefined
   where
 alloca :: Storable a => (Ptr a -> IO b) -> IO b
 alloca  = doAlloca undefined
   where
-    doAlloca       :: Storable a => a -> (Ptr a -> IO b) -> IO b
+    doAlloca       :: Storable a' => a' -> (Ptr a' -> IO b') -> IO b'
     doAlloca dummy  = allocaBytes (sizeOf dummy)
 
 -- |@'allocaBytes' n f@ executes the computation @f@, passing as argument
     doAlloca dummy  = allocaBytes (sizeOf dummy)
 
 -- |@'allocaBytes' n f@ executes the computation @f@, passing as argument
@@ -131,7 +131,7 @@ allocaBytes size  = bracket (mallocBytes size) free
 realloc :: Storable b => Ptr a -> IO (Ptr b)
 realloc  = doRealloc undefined
   where
 realloc :: Storable b => Ptr a -> IO (Ptr b)
 realloc  = doRealloc undefined
   where
-    doRealloc           :: Storable b => b -> Ptr a -> IO (Ptr b)
+    doRealloc           :: Storable b' => b' -> Ptr a' -> IO (Ptr b')
     doRealloc dummy ptr  = let
                             size = fromIntegral (sizeOf dummy)
                           in
     doRealloc dummy ptr  = let
                             size = fromIntegral (sizeOf dummy)
                           in
index a28ccc8..787c37d 100644 (file)
@@ -85,7 +85,7 @@ import GHC.Base
 mallocArray :: Storable a => Int -> IO (Ptr a)
 mallocArray  = doMalloc undefined
   where
 mallocArray :: Storable a => Int -> IO (Ptr a)
 mallocArray  = doMalloc undefined
   where
-    doMalloc            :: Storable a => a -> Int -> IO (Ptr a)
+    doMalloc            :: Storable a' => a' -> Int -> IO (Ptr a')
     doMalloc dummy size  = mallocBytes (size * sizeOf dummy)
 
 -- |Like 'mallocArray', but add an extra position to hold a special
     doMalloc dummy size  = mallocBytes (size * sizeOf dummy)
 
 -- |Like 'mallocArray', but add an extra position to hold a special
@@ -100,7 +100,7 @@ mallocArray0 size  = mallocArray (size + 1)
 allocaArray :: Storable a => Int -> (Ptr a -> IO b) -> IO b
 allocaArray  = doAlloca undefined
   where
 allocaArray :: Storable a => Int -> (Ptr a -> IO b) -> IO b
 allocaArray  = doAlloca undefined
   where
-    doAlloca            :: Storable a => a -> Int -> (Ptr a -> IO b) -> IO b
+    doAlloca            :: Storable a' => a' -> Int -> (Ptr a' -> IO b') -> IO b'
     doAlloca dummy size  = allocaBytes (size * sizeOf dummy)
 
 -- |Like 'allocaArray', but add an extra position to hold a special
     doAlloca dummy size  = allocaBytes (size * sizeOf dummy)
 
 -- |Like 'allocaArray', but add an extra position to hold a special
@@ -114,7 +114,7 @@ allocaArray0 size  = allocaArray (size + 1)
 reallocArray :: Storable a => Ptr a -> Int -> IO (Ptr a)
 reallocArray  = doRealloc undefined
   where
 reallocArray :: Storable a => Ptr a -> Int -> IO (Ptr a)
 reallocArray  = doRealloc undefined
   where
-    doRealloc                :: Storable a => a -> Ptr a -> Int -> IO (Ptr a)
+    doRealloc                :: Storable a' => a' -> Ptr a' -> Int -> IO (Ptr a')
     doRealloc dummy ptr size  = reallocBytes ptr (size * sizeOf dummy)
 
 -- |Adjust the size of an array including an extra position for the end marker.
     doRealloc dummy ptr size  = reallocBytes ptr (size * sizeOf dummy)
 
 -- |Adjust the size of an array including an extra position for the end marker.
@@ -237,7 +237,7 @@ withArrayLen0 marker vals f  =
 copyArray :: Storable a => Ptr a -> Ptr a -> Int -> IO ()
 copyArray  = doCopy undefined
   where
 copyArray :: Storable a => Ptr a -> Ptr a -> Int -> IO ()
 copyArray  = doCopy undefined
   where
-    doCopy                     :: Storable a => a -> Ptr a -> Ptr a -> Int -> IO ()
+    doCopy                     :: Storable a' => a' -> Ptr a' -> Ptr a' -> Int -> IO ()
     doCopy dummy dest src size  = copyBytes dest src (size * sizeOf dummy)
 
 -- |Copy the given number of elements from the second array (source) into the
     doCopy dummy dest src size  = copyBytes dest src (size * sizeOf dummy)
 
 -- |Copy the given number of elements from the second array (source) into the
@@ -246,7 +246,7 @@ copyArray  = doCopy undefined
 moveArray :: Storable a => Ptr a -> Ptr a -> Int -> IO ()
 moveArray  = doMove undefined
   where
 moveArray :: Storable a => Ptr a -> Ptr a -> Int -> IO ()
 moveArray  = doMove undefined
   where
-    doMove                     :: Storable a => a -> Ptr a -> Ptr a -> Int -> IO ()
+    doMove                     :: Storable a' => a' -> Ptr a' -> Ptr a' -> Int -> IO ()
     doMove dummy dest src size  = moveBytes dest src (size * sizeOf dummy)
 
 
     doMove dummy dest src size  = moveBytes dest src (size * sizeOf dummy)
 
 
@@ -271,5 +271,5 @@ lengthArray0 marker ptr  = loop 0
 advancePtr :: Storable a => Ptr a -> Int -> Ptr a
 advancePtr  = doAdvance undefined
   where
 advancePtr :: Storable a => Ptr a -> Int -> Ptr a
 advancePtr  = doAdvance undefined
   where
-    doAdvance             :: Storable a => a -> Ptr a -> Int -> Ptr a
+    doAdvance             :: Storable a' => a' -> Ptr a' -> Int -> Ptr a'
     doAdvance dummy ptr i  = ptr `plusPtr` (i * sizeOf dummy)
     doAdvance dummy ptr i  = ptr `plusPtr` (i * sizeOf dummy)
index 2804a70..f182d19 100644 (file)
@@ -116,7 +116,7 @@ withPool = bracket newPool freePool
 pooledMalloc :: Storable a => Pool -> IO (Ptr a)
 pooledMalloc = pm undefined
   where
 pooledMalloc :: Storable a => Pool -> IO (Ptr a)
 pooledMalloc = pm undefined
   where
-    pm           :: Storable a => a -> Pool -> IO (Ptr a)
+    pm           :: Storable a' => a' -> Pool -> IO (Ptr a')
     pm dummy pool = pooledMallocBytes pool (sizeOf dummy)
 
 -- | Allocate the given number of bytes of storage in the pool.
     pm dummy pool = pooledMallocBytes pool (sizeOf dummy)
 
 -- | Allocate the given number of bytes of storage in the pool.
@@ -134,7 +134,7 @@ pooledMallocBytes (Pool pool) size = do
 pooledRealloc :: Storable a => Pool -> Ptr a -> IO (Ptr a)
 pooledRealloc = pr undefined
   where
 pooledRealloc :: Storable a => Pool -> Ptr a -> IO (Ptr a)
 pooledRealloc = pr undefined
   where
-    pr               :: Storable a => a -> Pool -> Ptr a -> IO (Ptr a)
+    pr               :: Storable a' => a' -> Pool -> Ptr a' -> IO (Ptr a')
     pr dummy pool ptr = pooledReallocBytes pool ptr (sizeOf dummy)
 
 -- | Adjust the storage area for an element in the pool to the given size.
     pr dummy pool ptr = pooledReallocBytes pool ptr (sizeOf dummy)
 
 -- | Adjust the storage area for an element in the pool to the given size.
@@ -154,7 +154,7 @@ pooledReallocBytes (Pool pool) ptr size = do
 pooledMallocArray :: Storable a => Pool -> Int -> IO (Ptr a)
 pooledMallocArray = pma undefined
   where
 pooledMallocArray :: Storable a => Pool -> Int -> IO (Ptr a)
 pooledMallocArray = pma undefined
   where
-    pma                :: Storable a => a -> Pool -> Int -> IO (Ptr a)
+    pma                :: Storable a' => a' -> Pool -> Int -> IO (Ptr a')
     pma dummy pool size = pooledMallocBytes pool (size * sizeOf dummy)
 
 -- | Allocate storage for the given number of elements of a storable type in the
     pma dummy pool size = pooledMallocBytes pool (size * sizeOf dummy)
 
 -- | Allocate storage for the given number of elements of a storable type in the
@@ -169,7 +169,7 @@ pooledMallocArray0 pool size =
 pooledReallocArray :: Storable a => Pool -> Ptr a -> Int -> IO (Ptr a)
 pooledReallocArray = pra undefined
   where
 pooledReallocArray :: Storable a => Pool -> Ptr a -> Int -> IO (Ptr a)
 pooledReallocArray = pra undefined
   where
-    pra                ::  Storable a => a -> Pool -> Ptr a -> Int -> IO (Ptr a)
+    pra                ::  Storable a' => a' -> Pool -> Ptr a' -> Int -> IO (Ptr a')
     pra dummy pool ptr size  = pooledReallocBytes pool ptr (size * sizeOf dummy)
 
 -- | Adjust the size of an array with an end marker in the given pool.
     pra dummy pool ptr size  = pooledReallocBytes pool ptr (size * sizeOf dummy)
 
 -- | Adjust the size of an array with an end marker in the given pool.
index 355d7a1..a418efc 100644 (file)
@@ -106,7 +106,7 @@ mallocForeignPtr :: Storable a => IO (ForeignPtr a)
 -- assume that the memory returned by 'mallocForeignPtr' has been
 -- allocated with 'Foreign.Marshal.Alloc.malloc'.
 mallocForeignPtr = doMalloc undefined
 -- assume that the memory returned by 'mallocForeignPtr' has been
 -- allocated with 'Foreign.Marshal.Alloc.malloc'.
 mallocForeignPtr = doMalloc undefined
-  where doMalloc :: Storable a => a -> IO (ForeignPtr a)
+  where doMalloc :: Storable b => b -> IO (ForeignPtr b)
         doMalloc a = do
          r <- newIORef []
          IO $ \s ->
         doMalloc a = do
          r <- newIORef []
          IO $ \s ->