11{-# LANGUAGE BlockArguments #-}
22{-# LANGUAGE TypeFamilies #-}
33module Language.Haskell.Stylish.Tests.Util
4- ( testStep
4+ ( dumpAst
5+ , dumpModule
6+ , testStep
57 , testStep'
68 , Snippet (.. )
79 , testSnippet
@@ -16,6 +18,8 @@ import Control.Exception (bracket, try)
1618import Control.Monad.Writer (execWriter , tell )
1719import Data.List (intercalate )
1820import GHC.Exts (IsList (.. ))
21+ import GHC.Hs.Dump (showAstData , BlankSrcSpan (.. ))
22+ import Language.Haskell.Stylish.GHC (baseDynFlags )
1923import System.Directory (createDirectory ,
2024 getCurrentDirectory ,
2125 getTemporaryDirectory ,
@@ -26,12 +30,30 @@ import System.IO.Error (isAlreadyExistsError)
2630import System.Random (randomIO )
2731import Test.HUnit (Assertion , assertFailure ,
2832 (@=?) )
29-
33+ import Outputable (showSDoc )
34+ import Data.Data (Data (.. ))
3035
3136--------------------------------------------------------------------------------
3237import Language.Haskell.Stylish.Parse
3338import Language.Haskell.Stylish.Step
39+ import Language.Haskell.Stylish.Module (Module )
3440
41+ --------------------------------------------------------------------------------
42+ -- | Takes a Haskell source as an argument and parse it into a Module.
43+ -- Extract function selects element from that Module record and returns
44+ -- its String representation.
45+ --
46+ -- This function should be used when trying to understand how particular
47+ -- Haskell code will be represented by ghc-parser's AST
48+ dumpAst :: Data a => (Module -> a ) -> String -> String
49+ dumpAst extract str =
50+ let Right (theModule) = parseModule [] Nothing str
51+ ast = extract theModule
52+ sdoc = showAstData BlankSrcSpan ast
53+ in showSDoc baseDynFlags sdoc
54+
55+ dumpModule :: String -> String
56+ dumpModule = dumpAst id
3557
3658--------------------------------------------------------------------------------
3759testStep :: Step -> String -> String
0 commit comments