Skip to content
Snippets Groups Projects
Commit 48ba40b6 authored by Matthías Páll Gissurarson's avatar Matthías Páll Gissurarson
Browse files

Correct form is 907

parent a07eeb44
No related branches found
No related tags found
No related merge requests found
Pipeline #65476 passed
...@@ -26,7 +26,7 @@ modInfo = unsafePerformIO $ do ...@@ -26,7 +26,7 @@ modInfo = unsafePerformIO $ do
data ModuleInfo = data ModuleInfo =
ModuleInfo String Word32 Hash (Ptr Word64) ModuleInfo String Word32 Hash (Ptr Word64)
#if __GLASGOW_HASKELL__ >= 970 #if __GLASGOW_HASKELL__ >= 907
(Ptr Word64) (Ptr Word64)
(Ptr Word64) (Ptr Word64)
#endif #endif
...@@ -40,14 +40,14 @@ moduleInfoList ptr ...@@ -40,14 +40,14 @@ moduleInfoList ptr
tickCount <- (#peek HpcModuleInfo, tickCount) ptr tickCount <- (#peek HpcModuleInfo, tickCount) ptr
hashNo <- (#peek HpcModuleInfo, hashNo) ptr hashNo <- (#peek HpcModuleInfo, hashNo) ptr
tixArr <- (#peek HpcModuleInfo, tixArr) ptr tixArr <- (#peek HpcModuleInfo, tixArr) ptr
#if __GLASGOW_HASKELL__ >= 970 #if __GLASGOW_HASKELL__ >= 907
trxInfo <- (#peek HpcModuleInfo, trxInfo) ptr trxInfo <- (#peek HpcModuleInfo, trxInfo) ptr
trxArr <- (#peek HpcModuleInfo, trxArr) ptr trxArr <- (#peek HpcModuleInfo, trxArr) ptr
#endif #endif
next <- (#peek HpcModuleInfo, next) ptr next <- (#peek HpcModuleInfo, next) ptr
rest <- moduleInfoList next rest <- moduleInfoList next
return $ return $
#if __GLASGOW_HASKELL__ >= 970 #if __GLASGOW_HASKELL__ >= 907
ModuleInfo modName tickCount (toHash (hashNo :: Int)) tixArr trxInfo trxArr : rest ModuleInfo modName tickCount (toHash (hashNo :: Int)) tixArr trxInfo trxArr : rest
#else #else
ModuleInfo modName tickCount (toHash (hashNo :: Int)) tixArr : rest ModuleInfo modName tickCount (toHash (hashNo :: Int)) tixArr : rest
...@@ -57,7 +57,7 @@ moduleInfoList ptr ...@@ -57,7 +57,7 @@ moduleInfoList ptr
clearTix :: IO () clearTix :: IO ()
clearTix = do clearTix = do
sequence_ [ pokeArray ptr $ take (fromIntegral count) $ repeat 0 sequence_ [ pokeArray ptr $ take (fromIntegral count) $ repeat 0
#if __GLASGOW_HASKELL__ >= 970 #if __GLASGOW_HASKELL__ >= 907
| ModuleInfo _mod count _hash ptr _info _trx <- modInfo | ModuleInfo _mod count _hash ptr _info _trx <- modInfo
#else #else
| ModuleInfo _mod count _hash ptr <- modInfo | ModuleInfo _mod count _hash ptr <- modInfo
...@@ -69,7 +69,7 @@ clearTix = do ...@@ -69,7 +69,7 @@ clearTix = do
examineTix :: IO Tix examineTix :: IO Tix
examineTix = do examineTix = do
mods <- sequence [ do tixs <- peekArray (fromIntegral count) ptr mods <- sequence [ do tixs <- peekArray (fromIntegral count) ptr
#if __GLASGOW_HASKELL__ >= 970 #if __GLASGOW_HASKELL__ >= 907
info <- peekArray (fromIntegral 2) trxInfo info <- peekArray (fromIntegral 2) trxInfo
trx <- peekArray (fromIntegral (info !! 1)) trxArr trx <- peekArray (fromIntegral (info !! 1)) trxArr
#endif #endif
...@@ -77,7 +77,7 @@ examineTix = do ...@@ -77,7 +77,7 @@ examineTix = do
return $ TixModule mod' hash return $ TixModule mod' hash
(fromIntegral count) (fromIntegral count)
(map fromIntegral tixs) (map fromIntegral tixs)
#if __GLASGOW_HASKELL__ >= 970 #if __GLASGOW_HASKELL__ >= 907
(map fromIntegral info) (map fromIntegral info)
(map fromIntegral trx) (map fromIntegral trx)
| (ModuleInfo mod' count hash ptr trxInfo trxArr) <- modInfo | (ModuleInfo mod' count hash ptr trxInfo trxArr) <- modInfo
...@@ -94,7 +94,7 @@ updateTix (Tix modTixes) ...@@ -94,7 +94,7 @@ updateTix (Tix modTixes)
| length modTixes /= length modInfo = error "updateTix failed" | length modTixes /= length modInfo = error "updateTix failed"
| otherwise = do | otherwise = do
sequence_ [ pokeArray ptr $ map fromIntegral tixs sequence_ [ pokeArray ptr $ map fromIntegral tixs
#if __GLASGOW_HASKELL__ >= 970 #if __GLASGOW_HASKELL__ >= 907
| (ModuleInfo mod1 count1 hash1 ptr info1 trx1, | (ModuleInfo mod1 count1 hash1 ptr info1 trx1,
TixModule mod2 hash2 count2 tixs info2 trx2) <- zip modInfo modTixes TixModule mod2 hash2 count2 tixs info2 trx2) <- zip modInfo modTixes
#else #else
......
...@@ -7,7 +7,7 @@ ...@@ -7,7 +7,7 @@
-- (@.tix@) used by Hpc. -- (@.tix@) used by Hpc.
module Trace.Hpc.Tix(Tix(..), TixModule(..), module Trace.Hpc.Tix(Tix(..), TixModule(..),
tixModuleName, tixModuleHash, tixModuleTixs, tixModuleName, tixModuleHash, tixModuleTixs,
#if __GLASGOW_HASKELL__ >= 970 #if __GLASGOW_HASKELL__ >= 907
tixModuleTraceInfo, tixModuleTrace, tixModuleTraceInfo, tixModuleTrace,
#endif #endif
readTix, writeTix, getTixFileName) where readTix, writeTix, getTixFileName) where
...@@ -33,7 +33,7 @@ data TixModule = TixModule ...@@ -33,7 +33,7 @@ data TixModule = TixModule
Hash -- hash number Hash -- hash number
Int -- length of Tix list (allows pre-allocation at parse time). Int -- length of Tix list (allows pre-allocation at parse time).
[Integer] -- actual ticks [Integer] -- actual ticks
#if __GLASGOW_HASKELL__ >= 970 #if __GLASGOW_HASKELL__ >= 907
[Integer] -- current trace posistion [Integer] -- current trace posistion
[Integer] -- traces [Integer] -- traces
#endif #endif
...@@ -48,7 +48,7 @@ instance NFData TixModule ...@@ -48,7 +48,7 @@ instance NFData TixModule
tixModuleName :: TixModule -> String tixModuleName :: TixModule -> String
tixModuleHash :: TixModule -> Hash tixModuleHash :: TixModule -> Hash
tixModuleTixs :: TixModule -> [Integer] tixModuleTixs :: TixModule -> [Integer]
#if __GLASGOW_HASKELL__ >= 970 #if __GLASGOW_HASKELL__ >= 907
tixModuleName (TixModule nm _ _ _ _ _) = nm tixModuleName (TixModule nm _ _ _ _ _) = nm
tixModuleHash (TixModule _ h _ _ _ _) = h tixModuleHash (TixModule _ h _ _ _ _) = h
tixModuleTixs (TixModule _ _ _ tixs _ _) = tixs tixModuleTixs (TixModule _ _ _ tixs _ _) = tixs
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment