Skip to content

Commit

Permalink
[project @ 2004-12-23 00:02:41 by ralf]
Browse files Browse the repository at this point in the history
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
  • Loading branch information
ralf committed Dec 23, 2004
1 parent 3e23aaa commit bd1dd53
Show file tree
Hide file tree
Showing 7 changed files with 19 additions and 19 deletions.
4 changes: 2 additions & 2 deletions Data/Generics/Text.hs
Expand Up @@ -68,7 +68,7 @@ gread = readP_to_S gread'
where

-- Helper for recursive read
gread' :: Data a => ReadP a
gread' :: Data a' => ReadP a'
gread' = allButString `extR` stringCase

where
Expand All @@ -80,7 +80,7 @@ gread = readP_to_S gread'
-- Determine result type
myDataType = dataTypeOf (getArg allButString)
where
getArg :: ReadP a -> a
getArg :: ReadP a'' -> a''
getArg = undefined

-- The generic default for gread
Expand Down
4 changes: 2 additions & 2 deletions Data/Tree.hs
Expand Up @@ -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
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'
Expand All @@ -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))
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'
2 changes: 1 addition & 1 deletion Foreign/ForeignPtr.hs
Expand Up @@ -174,7 +174,7 @@ mallocForeignPtrBytes n = do
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',
Expand Down
6 changes: 3 additions & 3 deletions Foreign/Marshal/Alloc.hs
Expand Up @@ -68,7 +68,7 @@ import Hugs.ForeignPtr ( FinalizerPtr )
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.
Expand All @@ -91,7 +91,7 @@ mallocBytes size = failWhenNULL "malloc" (_malloc (fromIntegral size))
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
Expand Down Expand Up @@ -131,7 +131,7 @@ allocaBytes size = bracket (mallocBytes size) free
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
Expand Down
12 changes: 6 additions & 6 deletions Foreign/Marshal/Array.hs
Expand Up @@ -85,7 +85,7 @@ import GHC.Base
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
Expand All @@ -100,7 +100,7 @@ mallocArray0 size = mallocArray (size + 1)
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
Expand All @@ -114,7 +114,7 @@ allocaArray0 size = allocaArray (size + 1)
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.
Expand Down Expand Up @@ -237,7 +237,7 @@ withArrayLen0 marker vals f =
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
Expand All @@ -246,7 +246,7 @@ copyArray = doCopy undefined
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)


Expand All @@ -271,5 +271,5 @@ lengthArray0 marker ptr = loop 0
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)
8 changes: 4 additions & 4 deletions Foreign/Marshal/Pool.hs
Expand Up @@ -116,7 +116,7 @@ withPool = bracket newPool freePool
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.
Expand All @@ -134,7 +134,7 @@ pooledMallocBytes (Pool pool) size = do
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.
Expand All @@ -154,7 +154,7 @@ pooledReallocBytes (Pool pool) ptr size = do
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
Expand All @@ -169,7 +169,7 @@ pooledMallocArray0 pool size =
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.
Expand Down
2 changes: 1 addition & 1 deletion GHC/ForeignPtr.hs
Expand Up @@ -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
where doMalloc :: Storable a => a -> IO (ForeignPtr a)
where doMalloc :: Storable b => b -> IO (ForeignPtr b)
doMalloc a = do
r <- newIORef []
IO $ \s ->
Expand Down

0 comments on commit bd1dd53

Please sign in to comment.