X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=GHC%2FExts.hs;h=81a9dbb4edb399c29d2fb9fc1e96053332f39572;hb=41e8fba828acbae1751628af50849f5352b27873;hp=7869c4788ac7b8935527eeb60a58e08823153d7e;hpb=848e9b5b80d5e25a2120011c4ac7b38ac4e557f8;p=ghc-base.git diff --git a/GHC/Exts.hs b/GHC/Exts.hs index 7869c47..81a9dbb 100644 --- a/GHC/Exts.hs +++ b/GHC/Exts.hs @@ -1,3 +1,5 @@ +{-# LANGUAGE MagicHash, UnboxedTuples, DeriveDataTypeable #-} + ----------------------------------------------------------------------------- -- | -- Module : GHC.Exts @@ -15,29 +17,39 @@ module GHC.Exts ( -- * Representations of some basic types - Int(..),Word(..),Float(..),Double(..),Integer(..),Char(..), - Ptr(..), FunPtr(..), + Int(..),Word(..),Float(..),Double(..), + Char(..), + Ptr(..), FunPtr(..), + + -- * The maximum tuple size + maxTupleSize, -- * Primitive operations module GHC.Prim, - shiftL#, shiftRL#, iShiftL#, iShiftRA#, iShiftRL#, + shiftL#, shiftRL#, iShiftL#, iShiftRA#, iShiftRL#, uncheckedShiftL64#, uncheckedShiftRL64#, uncheckedIShiftL64#, uncheckedIShiftRA64#, - -- * Fusion - build, augment, + -- * Fusion + build, augment, - -- * Overloaded string literals - IsString(..), + -- * Overloaded string literals + IsString(..), - -- * Debugging - breakpoint, breakpointCond, + -- * Debugging + breakpoint, breakpointCond, - -- * Ids with special behaviour - lazy, inline, + -- * Ids with special behaviour + lazy, inline, -- * Transform comprehensions - groupWith, sortWith, the + Down(..), groupWith, sortWith, the, + + -- * Event logging + traceEvent, + + -- * SpecConstr annotations + SpecConstrAnnotation(..) ) where @@ -45,18 +57,35 @@ import Prelude import GHC.Prim import GHC.Base +import GHC.Magic import GHC.Word import GHC.Int -import GHC.Num -import GHC.Float +-- import GHC.Float import GHC.Ptr import Data.String import Data.List +import Foreign.C +import Data.Data + +-- XXX This should really be in Data.Tuple, where the definitions are +maxTupleSize :: Int +maxTupleSize = 62 + +-- | 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@ +newtype Down a = Down a deriving (Eq) + +instance Ord a => Ord (Down a) where + compare (Down x) (Down y) = y `compare` x -- | 'the' ensures that all the elements of the list are identical -- and then returns that unique element the :: Eq a => [a] -> a -the (x:xs) +the (x:xs) | all (x ==) xs = x | otherwise = error "GHC.Exts.the: non-identical elements" the [] = error "GHC.Exts.the: empty list" @@ -69,5 +98,40 @@ sortWith f = sortBy (\x y -> compare (f x) (f y)) -- | The 'groupWith' function uses the user supplied function which -- projects an element out of every list element in order to to first sort the -- input list and then to form groups by equality on these projected elements +{-# INLINE groupWith #-} groupWith :: Ord b => (a -> b) -> [a] -> [[a]] -groupWith f = groupBy (\x y -> f x == f y) . sortWith f +groupWith f xs = build (\c n -> groupByFB c n (\x y -> f x == f y) (sortWith f xs)) + +groupByFB :: ([a] -> lst -> lst) -> lst -> (a -> a -> Bool) -> [a] -> lst +groupByFB c n eq xs0 = groupByFBCore xs0 + where groupByFBCore [] = n + groupByFBCore (x:xs) = c (x:ys) (groupByFBCore zs) + where (ys, zs) = span (eq x) xs + + +-- ----------------------------------------------------------------------------- +-- tracing + +traceEvent :: String -> IO () +traceEvent msg = do + withCString msg $ \(Ptr p) -> IO $ \s -> + case traceEvent# p s of s' -> (# s', () #) + + + +{- ********************************************************************** +* * +* SpecConstr annotation * +* * +********************************************************************** -} + +-- Annotating a type with NoSpecConstr will make SpecConstr +-- not specialise for arguments of that type. + +-- This data type is defined here, rather than in the SpecConstr module +-- itself, so that importing it doesn't force stupidly linking the +-- entire ghc package at runtime + +data SpecConstrAnnotation = NoSpecConstr | ForceSpecConstr + deriving( Data, Typeable, Eq ) +