[Git][ghc/ghc][wip/decode_cloned_stack] Move Modules

Sven Tennie (@supersven) gitlab at gitlab.haskell.org
Sat Feb 18 16:13:01 UTC 2023



Sven Tennie pushed to branch wip/decode_cloned_stack at Glasgow Haskell Compiler / GHC


Commits:
a4ab19b2 by Sven Tennie at 2023-02-18T16:12:40+00:00
Move Modules

- - - - -


11 changed files:

- libraries/ghc-heap/GHC/Exts/Heap.hs
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
- libraries/ghc-heap/GHC/Exts/DecodeHeap.hs → libraries/ghc-heap/GHC/Exts/Heap/Decode.hs
- libraries/ghc-heap/GHC/Exts/StackConstants.hsc → libraries/ghc-heap/GHC/Exts/Stack/Constants.hsc
- libraries/ghc-heap/GHC/Exts/DecodeStack.hs → libraries/ghc-heap/GHC/Exts/Stack/Decode.hs
- libraries/ghc-heap/ghc-heap.cabal.in
- libraries/ghc-heap/tests/TestUtils.hs
- libraries/ghc-heap/tests/stack_big_ret.hs
- libraries/ghc-heap/tests/stack_misc_closures.hs
- libraries/ghc-heap/tests/stack_stm_frames.hs
- libraries/ghc-heap/tests/stack_underflow.hs


Changes:

=====================================
libraries/ghc-heap/GHC/Exts/Heap.hs
=====================================
@@ -7,7 +7,6 @@
 {-# LANGUAGE DataKinds #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE RankNTypes #-}
-{-# LANGUAGE BangPatterns #-}
 #if MIN_TOOL_VERSION_ghc(9,5,0)
 {-# LANGUAGE RecordWildCards #-}
 #endif
@@ -74,15 +73,15 @@ import GHC.Exts.Heap.InfoTableProf
 #else
 import GHC.Exts.Heap.InfoTable
 #endif
-import GHC.Exts.DecodeHeap
+import GHC.Exts.Heap.Decode
 
 import GHC.Exts
 import GHC.Int
 import GHC.Word
 #if MIN_TOOL_VERSION_ghc(9,5,0)
 import GHC.Stack.CloneStack
-import GHC.Exts.DecodeStack
-import GHC.Exts.StackConstants
+import GHC.Exts.Stack.Decode
+import GHC.Exts.Stack.Constants
 import Data.Functor
 import Debug.Trace
 #endif


=====================================
libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
=====================================
@@ -55,7 +55,7 @@ import Numeric
 
 #if MIN_TOOL_VERSION_ghc(9,5,0)
 import GHC.Stack.CloneStack (StackSnapshot(..), stackSnapshotToString)
-import GHC.Exts.StackConstants
+import GHC.Exts.Stack.Constants
 #endif
 
 ------------------------------------------------------------------------


=====================================
libraries/ghc-heap/GHC/Exts/DecodeHeap.hs → libraries/ghc-heap/GHC/Exts/Heap/Decode.hs
=====================================
@@ -7,7 +7,7 @@
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE UnliftedFFITypes #-}
 
-module GHC.Exts.DecodeHeap where
+module GHC.Exts.Heap.Decode where
 import Prelude
 import GHC.Exts.Heap.Closures
 import GHC.Exts.Heap.ClosureTypes


=====================================
libraries/ghc-heap/GHC/Exts/StackConstants.hsc → libraries/ghc-heap/GHC/Exts/Stack/Constants.hsc
=====================================
@@ -1,7 +1,7 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE DerivingStrategies #-}
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
-module GHC.Exts.StackConstants where
+module GHC.Exts.Stack.Constants where
 
 -- TODO: Better expression to allow is only for the latest (this branch) GHC?
 #if MIN_TOOL_VERSION_ghc(9,5,0)


=====================================
libraries/ghc-heap/GHC/Exts/DecodeStack.hs → libraries/ghc-heap/GHC/Exts/Stack/Decode.hs
=====================================
@@ -13,8 +13,7 @@
 {-# LANGUAGE UnboxedTuples #-}
 {-# LANGUAGE UnliftedFFITypes #-}
 
--- TODO: Find better place than top level. Re-export from top-level?
-module GHC.Exts.DecodeStack
+module GHC.Exts.Stack.Decode
   ( decodeStack,
     unpackStackFrameIter,
   )
@@ -32,7 +31,7 @@ import GHC.Exts.Heap.ClosureTypes
 import GHC.Exts.Heap.Closures
 import GHC.Exts.Heap.Constants (wORD_SIZE_IN_BITS)
 import GHC.Exts.Heap.InfoTable
-import GHC.Exts.StackConstants
+import GHC.Exts.Stack.Constants
 import GHC.IO (IO (..))
 import GHC.Stack.CloneStack
 import GHC.Word
@@ -484,5 +483,5 @@ decodeStack' s =
     go (Just sfi) = StackFrameBox sfi : go (advanceStackFrameIter sfi)
 
 #else
-module GHC.Exts.DecodeStack where
+module GHC.Exts.Stack.Decode where
 #endif


=====================================
libraries/ghc-heap/ghc-heap.cabal.in
=====================================
@@ -39,8 +39,7 @@ library
                     GHC.Exts.Heap.Closures
                     GHC.Exts.Heap.ClosureTypes
                     GHC.Exts.Heap.Constants
-                    GHC.Exts.DecodeHeap
-                    GHC.Exts.DecodeStack
+                    GHC.Exts.Heap.Decode
                     GHC.Exts.Heap.InfoTable
                     GHC.Exts.Heap.InfoTable.Types
                     GHC.Exts.Heap.InfoTableProf
@@ -52,4 +51,5 @@ library
                     GHC.Exts.Heap.ProfInfo.PeekProfInfo
                     GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingDisabled
                     GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingEnabled
-                    GHC.Exts.StackConstants
+                    GHC.Exts.Stack.Constants
+                    GHC.Exts.Stack.Decode


=====================================
libraries/ghc-heap/tests/TestUtils.hs
=====================================
@@ -1,8 +1,6 @@
 {-# LANGUAGE DataKinds #-}
-{-# LANGUAGE ForeignFunctionInterface #-}
 {-# LANGUAGE LambdaCase #-}
 {-# LANGUAGE MagicHash #-}
-{-# LANGUAGE RecordWildCards #-}
 {-# LANGUAGE UnliftedFFITypes #-}
 
 module TestUtils
@@ -19,7 +17,7 @@ import Data.Array.Byte
 import Data.Foldable
 import Debug.Trace
 import GHC.Exts
-import GHC.Exts.DecodeStack
+import GHC.Exts.Stack.Decode
 import GHC.Exts.Heap
 import GHC.Exts.Heap.Closures
 import GHC.Records


=====================================
libraries/ghc-heap/tests/stack_big_ret.hs
=====================================
@@ -8,7 +8,7 @@ import Control.Concurrent
 import Data.IORef
 import Data.Maybe
 import GHC.Exts (StackSnapshot#)
-import GHC.Exts.DecodeStack
+import GHC.Exts.Stack.Decode
 import GHC.Exts.Heap.ClosureTypes
 import GHC.Exts.Heap.Closures
 import GHC.Exts.Heap.InfoTable.Types


=====================================
libraries/ghc-heap/tests/stack_misc_closures.hs
=====================================
@@ -16,7 +16,7 @@ import Data.Functor
 -- TODO: Remove later
 import Debug.Trace
 import GHC.Exts
-import GHC.Exts.DecodeStack
+import GHC.Exts.Stack.Decode
 import GHC.Exts.Heap
 import GHC.Exts.Heap.Closures
 import GHC.IO (IO (..))
@@ -233,7 +233,7 @@ main = do
         assertEqual wds [1 .. (fromIntegral closureCount)]
       e -> error $ "Wrong closure type: " ++ show e
   traceM $ "Test 24"
-  testSize any_ret_big_closures_two_words_frame# ((fromIntegral bitsInWord) + 1 + 1)
+  testSize any_ret_big_closures_two_words_frame# (fromIntegral bitsInWord + 1 + 1)
   traceM $ "Test 25"
   test any_ret_fun_arg_n_prim_frame# $
     \case


=====================================
libraries/ghc-heap/tests/stack_stm_frames.hs
=====================================
@@ -5,7 +5,7 @@ module Main where
 import Control.Concurrent.STM
 import Control.Exception
 import GHC.Conc
-import GHC.Exts.DecodeStack
+import GHC.Exts.Stack.Decode
 import GHC.Exts.Heap.ClosureTypes
 import GHC.Exts.Heap.Closures
 import GHC.Exts.Heap.InfoTable.Types


=====================================
libraries/ghc-heap/tests/stack_underflow.hs
=====================================
@@ -1,10 +1,9 @@
-{-# LANGUAGE BangPatterns #-}
 {-# LANGUAGE RecordWildCards #-}
 
 module Main where
 
 import Data.Bool (Bool (True))
-import GHC.Exts.DecodeStack
+import GHC.Exts.Stack.Decode
 import GHC.Exts.Heap
 import GHC.Exts.Heap.ClosureTypes
 import GHC.Exts.Heap.Closures



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a4ab19b23442a2aee81e1b9cf8b0b6e878b024d4

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a4ab19b23442a2aee81e1b9cf8b0b6e878b024d4
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230218/0bd68e7b/attachment-0001.html>


More information about the ghc-commits mailing list