Skip to content

Commit 9dcc02f

Browse files
authored
Dump AST (#363)
* Add dumpAst and dumpModule
1 parent 0875c0a commit 9dcc02f

File tree

1 file changed

+24
-2
lines changed
  • tests/Language/Haskell/Stylish/Tests

1 file changed

+24
-2
lines changed

tests/Language/Haskell/Stylish/Tests/Util.hs

Lines changed: 24 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,9 @@
11
{-# LANGUAGE BlockArguments #-}
22
{-# LANGUAGE TypeFamilies #-}
33
module 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)
1618
import Control.Monad.Writer (execWriter, tell)
1719
import Data.List (intercalate)
1820
import GHC.Exts (IsList (..))
21+
import GHC.Hs.Dump (showAstData, BlankSrcSpan(..))
22+
import Language.Haskell.Stylish.GHC (baseDynFlags)
1923
import System.Directory (createDirectory,
2024
getCurrentDirectory,
2125
getTemporaryDirectory,
@@ -26,12 +30,30 @@ import System.IO.Error (isAlreadyExistsError)
2630
import System.Random (randomIO)
2731
import Test.HUnit (Assertion, assertFailure,
2832
(@=?))
29-
33+
import Outputable (showSDoc)
34+
import Data.Data (Data(..))
3035

3136
--------------------------------------------------------------------------------
3237
import Language.Haskell.Stylish.Parse
3338
import 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
--------------------------------------------------------------------------------
3759
testStep :: Step -> String -> String

0 commit comments

Comments
 (0)