| 
| GHC.Exts | | Portability | non-portable (GHC Extensions) |  | Stability | internal |  | Maintainer | cvs-ghc@haskell.org |  
  |  
  | 
 | 
 | 
 | 
| Description | 
| GHC Extensions: this is the Approved Way to get at GHC-specific extensions.
 | 
 | 
| Synopsis | 
 | 
 | 
 | 
 | 
| Representations of some basic types
 | 
 | 
 | 
| A Word is an unsigned integral type, with the same size as Int.
 |  | Constructors |   |    Instances |   |  
  | 
 | 
 | 
A value of type Ptr a represents a pointer to an object, or an
 array of objects, which may be marshalled to or from Haskell values
 of type a.
 The type a will often be an instance of class
 Foreign.Storable.Storable which provides the marshalling operations.
 However this is not essential, and you can provide your own operations
 to access the pointer.  For example you might write small foreign
 functions to get or set the fields of a C struct.
  |  | Constructors |   |    Instances |   |  
  | 
 | 
 | 
A value of type FunPtr a is a pointer to a function callable
 from foreign code.  The type a will normally be a foreign type,
 a function type with zero or more arguments where
 -  the argument types are marshallable foreign types,
   i.e. Char, Int, Prelude.Double, Prelude.Float,
   Bool, Data.Int.Int8, Data.Int.Int16, Data.Int.Int32,
   Data.Int.Int64, Data.Word.Word8, Data.Word.Word16,
   Data.Word.Word32, Data.Word.Word64, Ptr a, FunPtr a,
   Foreign.StablePtr.StablePtr a or a renaming of any of these
   using newtype.
 -  the return type is either a marshallable foreign type or has the form
   Prelude.IO t where t is a marshallable foreign type or ().
 
 A value of type FunPtr a may be a pointer to a foreign function,
 either returned by another foreign function or imported with a
 a static address import like
  foreign import ccall "stdlib.h &free"
   p_free :: FunPtr (Ptr a -> IO ())
 or a pointer to a Haskell function created using a wrapper stub
 declared to produce a FunPtr of the correct type.  For example:
  type Compare = Int -> Int -> Bool
 foreign import ccall "wrapper"
   mkCompare :: Compare -> IO (FunPtr Compare)
 Calls to wrapper stubs like mkCompare allocate storage, which
 should be released with Foreign.Ptr.freeHaskellFunPtr when no
 longer required.
 To convert FunPtr values to corresponding Haskell functions, one
 can define a dynamic stub for the specific foreign type, e.g.
  type IntFunction = CInt -> IO ()
 foreign import ccall "dynamic" 
   mkFun :: FunPtr IntFunction -> IntFunction
  |  | Constructors |   |    Instances |   |  
  | 
 | 
| The maximum tuple size
 | 
 | 
 | 
 | 
| Primitive operations
 | 
 | 
 | 
| Shift the argument left by the specified number of bits
 (which must be non-negative).
 | 
 | 
 | 
| Shift the argument right by the specified number of bits
 (which must be non-negative).
 | 
 | 
 | 
| Shift the argument left by the specified number of bits
 (which must be non-negative).
 | 
 | 
 | 
| Shift the argument right (signed) by the specified number of bits
 (which must be non-negative).
 | 
 | 
 | 
| Shift the argument right (unsigned) by the specified number of bits
 (which must be non-negative).
 | 
 | 
| Fusion
 | 
 | 
| build :: forall a.  (forall b.  (a -> b -> b) -> b -> b) -> [a] | Source |  
  | 
A list producer that can be fused with foldr.
 This function is merely
     build g = g (:) []
 but GHC's simplifier will transform an expression of the form
 foldr k z (build g), which may arise after inlining, to g k z,
 which avoids producing an intermediate list.
  | 
 | 
| augment :: forall a.  (forall b.  (a -> b -> b) -> b -> b) -> [a] -> [a] | Source |  
  | 
A list producer that can be fused with foldr.
 This function is merely
     augment g xs = g (:) xs
 but GHC's simplifier will transform an expression of the form
 foldr k z (augment g xs), which may arise after inlining, to
 g k (foldr k z xs), which avoids producing an intermediate list.
  | 
 | 
| Overloaded string literals
 | 
 | 
 | 
| Class for string-like datastructures; used by the overloaded string
   extension (-foverloaded-strings in GHC).
 |   |  | Methods |   |   |    Instances |   |  
  | 
 | 
| Debugging
 | 
 | 
 | 
 | 
 | 
 | 
| Ids with special behaviour
 | 
 | 
 | 
| The call '(lazy e)' means the same as e, but lazy has a 
 magical strictness property: it is lazy in its first argument, 
 even though its semantics is strict.
 | 
 | 
 | 
| The call '(inline f)' reduces to f, but inline has a BuiltInRule
 that tries to inline f (if it has an unfolding) unconditionally
 The NOINLINE pragma arranges that inline only gets inlined (and
 hence eliminated) late in compilation, after the rule has had
 a god chance to fire.
 | 
 | 
| Transform comprehensions
 | 
 | 
 | 
| The Down type allows you to reverse sort order conveniently.  A value of type
 Down a contains a value of type a (represented as Down a).
 If a has an Ord instance associated with it then comparing two
 values thus wrapped will give you the opposite of their normal sort order.
 This is particularly useful when sorting in generalised list comprehensions,
 as in: then sortWith by Down x
 |  | Constructors |   |    Instances |   |  
  | 
 | 
| groupWith :: Ord b => (a -> b) -> [a] -> [[a]] | Source |  
  | 
 | 
| sortWith :: Ord b => (a -> b) -> [a] -> [a] | Source |  
  | 
| The sortWith function sorts a list of elements using the
 user supplied function to project something out of each element
 | 
 | 
 | 
| the ensures that all the elements of the list are identical
 and then returns that unique element
 | 
 | 
| Produced by Haddock version 2.3.0 |