Use explicit language extensions & remove extension fields from base.cabal
[ghc-base.git] / GHC / Pack.lhs
index 081a390..14ac670 100644 (file)
@@ -1,50 +1,54 @@
-% ------------------------------------------------------------------------------
-% $Id: Pack.lhs,v 1.2 2001/09/14 11:25:24 simonmar Exp $
-%
-% (c) The University of Glasgow, 1997-2000
-%
-
-\section[GHC.Pack]{Packing/unpacking bytes}
-
-This module provides a small set of low-level functions for packing
-and unpacking a chunk of bytes. Used by code emitted by the compiler
-plus the prelude libraries.
-
-The programmer level view of packed strings is provided by a GHC
-system library PackedString.
-
 \begin{code}
-{-# OPTIONS -fno-implicit-prelude #-}
-
+{-# LANGUAGE NoImplicitPrelude, MagicHash, UnboxedTuples #-}
+{-# OPTIONS_HADDOCK hide #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  GHC.Pack
+-- Copyright   :  (c) The University of Glasgow 1997-2002
+-- License     :  see libraries/base/LICENSE
+-- 
+-- Maintainer  :  cvs-ghc@haskell.org
+-- Stability   :  internal
+-- Portability :  non-portable (GHC Extensions)
+--
+-- This module provides a small set of low-level functions for packing
+-- and unpacking a chunk of bytes. Used by code emitted by the compiler
+-- plus the prelude libraries.
+-- 
+-- The programmer level view of packed strings is provided by a GHC
+-- system library PackedString.
+--
+-----------------------------------------------------------------------------
+
+-- #hide
 module GHC.Pack
        (
-       -- (**) - emitted by compiler.
-
-       packCString#,      -- :: [Char] -> ByteArray#    **
-       unpackCString,
-       unpackCString#,    -- :: Addr# -> [Char]         **
-       unpackNBytes#,     -- :: Addr# -> Int# -> [Char] **
-       unpackFoldrCString#,  -- **
-       unpackAppendCString#,  -- **
+        -- (**) - emitted by compiler.
+
+        packCString#,      -- :: [Char] -> ByteArray#    (**)
+        unpackCString,
+        unpackCString#,    -- :: Addr# -> [Char]         (**)
+        unpackNBytes#,     -- :: Addr# -> Int# -> [Char] (**)
+        unpackFoldrCString#,  -- (**)
+        unpackAppendCString#,  -- (**)
        ) 
-       where
+        where
 
 import GHC.Base
-import {-# SOURCE #-} GHC.Err ( error )
 import GHC.List ( length )
 import GHC.ST
-import GHC.Num
 import GHC.Ptr
 
-data ByteArray ix                     = ByteArray        ix ix ByteArray#
+data ByteArray ix              = ByteArray        ix ix ByteArray#
 data MutableByteArray s ix     = MutableByteArray ix ix (MutableByteArray# s)
 
 unpackCString :: Ptr a -> [Char]
 unpackCString a@(Ptr addr)
   | a == nullPtr  = []
-  | otherwise     = unpackCString# addr
+  | otherwise      = unpackCString# addr
 
-packCString#        :: [Char]          -> ByteArray#
+packCString#         :: [Char]          -> ByteArray#
 packCString# str = case (packString str) of { ByteArray _ _ bytes -> bytes }
 
 packString :: [Char] -> ByteArray Int
@@ -73,23 +77,23 @@ packNBytesST (I# length#) str =
    return ()
 
   fill_in arr_in# idx (C# c : cs) =
-   write_ps_array arr_in# idx c         >>
+   write_ps_array arr_in# idx c  >>
    fill_in arr_in# (idx +# 1#) cs
 
 -- (Very :-) ``Specialised'' versions of some CharArray things...
 
-new_ps_array   :: Int# -> ST s (MutableByteArray s Int)
-write_ps_array :: MutableByteArray s Int -> Int# -> Char# -> ST s () 
+new_ps_array    :: Int# -> ST s (MutableByteArray s Int)
+write_ps_array  :: MutableByteArray s Int -> Int# -> Char# -> ST s () 
 freeze_ps_array :: MutableByteArray s Int -> Int# -> ST s (ByteArray Int)
 
 new_ps_array size = ST $ \ s ->
-    case (newByteArray# size s)          of { (# s2#, barr# #) ->
+    case (newByteArray# size s)   of { (# s2#, barr# #) ->
     (# s2#, MutableByteArray bot bot barr# #) }
   where
     bot = error "new_ps_array"
 
 write_ps_array (MutableByteArray _ _ barr#) n ch = ST $ \ s# ->
-    case writeCharArray# barr# n ch s# of { s2#   ->
+    case writeCharArray# barr# n ch s#  of { s2#   ->
     (# s2#, () #) }
 
 -- same as unsafeFreezeByteArray