Code Monkey home page Code Monkey logo

ghc-exactprint's Introduction

ghc-exactprint

Available on Hackage License BSD3 Build Status

Github Build Status

GHC version of haskell-src-exts exactPrint

master has been updated to use the new GHC Exact Print Annotations which landed in GHC 9.2

So ghc-exactprint-1.1 and later supports GHC 9.2 and onwards ghc-exactprint-0.6.4 supports GHC from 7.10 to 9.0

Links

HIW 2021 talk on GHC Exactprint for GHC 9.2

HIW 2020 talk on plans for GHC Exactprint for GHC 9.2

Blog Post by @shayne-fletcher on experiences converting to use the new annotations.

Current Limitations

  • Does not process CPP properly
  • Does not process Lhs files properly

ghc-exactprint's People

Contributors

alanz avatar drsooch avatar jhrcek avatar jneira avatar lspitzner avatar mpickering avatar pepeiborra avatar phadej avatar rubik avatar sergv avatar thomie avatar vekhir avatar wz1000 avatar zliu41 avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

ghc-exactprint's Issues

Tests fail on file that's on hackage but not git

Trying to build ghc-exactprint on NixOS, I see:

GHC8
### Error in:   1:Round-trip tests:0:ghc710:104
parse error on input ‘]’tests/examples/ghc710/OldQuasiQuote.hs
CallStack (from HasCallStack):
  error, called at tests/Test.hs:130:54 in main:Main
Cases: 858  Tried: 858  Errors: 1  Failures: 0
Counts {cases = 858, tried = 858, errors = 1, failures = 0}
Test suite test: FAIL
Test suite logged to: dist/test/ghc-exactprint-0.5.2-test.log
0 of 1 test suites (0 of 1 test cases) passed.

The strange thing is, while that file does exist in the distribution (as you can see here, it doesn't exist in git. I'm betting it was a file renamed out of the way during development that got picked up when creating the source distribution. Regardless, might be good to drop a 0.5.2.1 release without it.

Weird Parsing of Tuple Sections

I'm not sure what's going on here.

Original file:

{-# LANGUAGE TupleSections #-}

baz = (1, "hello", 6.5,,) 'a' (Just ())

When parsed there are two Missing elements which have the exact same information.

                     ({ tests/examples/Tuple.hs:3:24 }
                      Just (Ann (DP (0,0)) (ColDelta 24) DP (0,0) [] [((G AnnComma),DP (0,0))])
                      (Missing
                       (PlaceHolder))),
                     ({ tests/examples/Tuple.hs:3:24 }
                      Just (Ann (DP (0,0)) (ColDelta 24) DP (0,0) [] [((G AnnComma),DP (0,0))])
                      (Missing
                       (PlaceHolder)))]

Log

{-# LANGUAGE TupleSections #-}

baz = (1, "hello", 6.5,,,) 'a' (Just ())


==============
tests/examples/Tuple.hs
==============
lengths:(74,73)

==============

({ tests/examples/Tuple.hs:1:1 }
 Just (Ann (DP (0,0)) (ColDelta 1) DP (0,0) [] [((G AnnEofPos),DP (2,0))])
 (HsModule
  (Nothing)
  (Nothing)
  []
  [
   ({ tests/examples/Tuple.hs:3:1-39 }
    Just (Ann (DP (2,1)) (ColDelta 1) DP (2,1) [DComment (DP (0,0),DP (0,30)) "{-# LANGUAGE TupleSections #-}" Nothing] [])
    (ValD
     (FunBind
      ({ tests/examples/Tuple.hs:3:1-3 }
       Just (Ann (DP (0,0)) (ColDelta 1) DP (0,0) [] [((G AnnVal),DP (0,0))])
       (Unqual {OccName: baz}))
      (False)
      (MG
       [
        ({ tests/examples/Tuple.hs:3:1-39 }
         Just (Ann (DP (0,0)) (ColDelta 1) DP (0,0) [] [((G AnnEqual),DP (0,1)),((AnnList <no location info> NotNeeded),DP (0,0))])
         (Match
          (Just
           ((,)
            ({ tests/examples/Tuple.hs:3:1-3 }
             Just (Ann (DP (0,0)) (ColDelta 1) DP (0,0) [] [((G AnnVal),DP (0,0))])
             (Unqual {OccName: baz}))
            (False)))
          []
          (Nothing)
          (GRHSs
           [
            ({ tests/examples/Tuple.hs:3:5-39 }
             Just (Ann (DP (0,-1)) (ColDelta 5) DP (0,-1) [] [])
             (GRHS
              []
              ({ tests/examples/Tuple.hs:3:7-39 }
               Just (Ann (DP (0,1)) (ColDelta 7) DP (0,1) [] [])
               (HsApp
                ({ tests/examples/Tuple.hs:3:7-29 }
                 Just (Ann (DP (0,0)) (ColDelta 7) DP (0,0) [] [])
                 (HsApp
                  ({ tests/examples/Tuple.hs:3:7-25 }
                   Just (Ann (DP (0,0)) (ColDelta 7) DP (0,0) [] [((G AnnOpenP),DP (0,0)),((G AnnCloseP),DP (0,0))])
                   (ExplicitTuple
                    [
                     ({ tests/examples/Tuple.hs:3:8 }
                      Just (Ann (DP (0,0)) (ColDelta 8) DP (0,0) [] [])
                      (Present
                       ({ tests/examples/Tuple.hs:3:8 }
                        Just (Ann (DP (0,0)) (ColDelta 8) DP (0,0) [] [((G AnnVal),DP (0,0)),((G AnnComma),DP (0,0))])
                        (HsOverLit {HsOverLit:1})))),
                     ({ tests/examples/Tuple.hs:3:11-17 }
                      Just (Ann (DP (0,1)) (ColDelta 11) DP (0,1) [] [])
                      (Present
                       ({ tests/examples/Tuple.hs:3:11-17 }
                        Just (Ann (DP (0,0)) (ColDelta 11) DP (0,0) [] [((G AnnVal),DP (0,0)),((G AnnComma),DP (0,0))])
                        (HsLit
                         (HsString "\"hello\"" {FastString: "hello"}))))),
                     ({ tests/examples/Tuple.hs:3:20-22 }
                      Just (Ann (DP (0,1)) (ColDelta 20) DP (0,1) [] [])
                      (Present
                       ({ tests/examples/Tuple.hs:3:20-22 }
                        Just (Ann (DP (0,0)) (ColDelta 20) DP (0,0) [] [((G AnnVal),DP (0,0)),((G AnnComma),DP (0,0))])
                        (HsOverLit {HsOverLit:6.5})))),
                     ({ tests/examples/Tuple.hs:3:24 }
                      Just (Ann (DP (0,0)) (ColDelta 24) DP (0,0) [] [((G AnnComma),DP (0,0))])
                      (Missing
                       (PlaceHolder))),
                     ({ tests/examples/Tuple.hs:3:24 }
                      Just (Ann (DP (0,0)) (ColDelta 24) DP (0,0) [] [((G AnnComma),DP (0,0))])
                      (Missing
                       (PlaceHolder)))]
                    (Boxed)))
                  ({ tests/examples/Tuple.hs:3:27-29 }
                   Just (Ann (DP (0,1)) (ColDelta 27) DP (0,1) [] [((G AnnVal),DP (0,0))])
                   (HsLit
                    (HsChar "'a'"
                     ('a'))))))
                ({ tests/examples/Tuple.hs:3:31-39 }
                 Just (Ann (DP (0,1)) (ColDelta 31) DP (0,1) [] [((G AnnOpenP),DP (0,0)),((G AnnCloseP),DP (0,0))])
                 (HsPar
                  ({ tests/examples/Tuple.hs:3:32-38 }
                   Just (Ann (DP (0,0)) (ColDelta 32) DP (0,0) [] [])
                   (HsApp
                    ({ tests/examples/Tuple.hs:3:32-35 }
                     Just (Ann (DP (0,0)) (ColDelta 32) DP (0,0) [] [((G AnnVal),DP (0,0))])
                     (HsVar
                      (Unqual {OccName: Just})))
                    ({ tests/examples/Tuple.hs:3:37-38 }
                     Just (Ann (DP (0,1)) (ColDelta 37) DP (0,1) [] [((G AnnOpenP),DP (0,0)),((G AnnCloseP),DP (0,0))])
                     (HsVar
                      (Exact {Name: ()})))))))))))]
           (EmptyLocalBinds))))]
       []
       (PlaceHolder)
       (FromSource))
      (WpHole)
      (PlaceHolder)
      [])))]
  (Nothing)
  (Nothing)))
==============
([(AnnKey tests/examples/Tuple.hs:1:1 CN "HsModule" NotNeeded,
   (Ann (DP (0,0)) (ColDelta 1) DP (0,0) [] [((G AnnEofPos),DP (2,0))])),
  (AnnKey tests/examples/Tuple.hs:3:1-3 CN "Unqual" NotNeeded,
   (Ann (DP (0,0)) (ColDelta 1) DP (0,0) [] [((G AnnVal),DP (0,0))])),
  (AnnKey tests/examples/Tuple.hs:3:1-39 CN "Match" NotNeeded,
   (Ann (DP (0,0)) (ColDelta 1) DP (0,0) [] [((G AnnEqual),DP (0,1)),((AnnList <no location info> NotNeeded),DP (0,0))])),
  (AnnKey tests/examples/Tuple.hs:3:1-39 CN "ValD" NotNeeded,
   (Ann (DP (2,1)) (ColDelta 1) DP (2,1) [DComment (DP (0,0),DP (0,30)) "{-# LANGUAGE TupleSections #-}" Nothing] [])),
  (AnnKey tests/examples/Tuple.hs:3:5-39 CN "GRHS" NotNeeded,
   (Ann (DP (0,-1)) (ColDelta 5) DP (0,-1) [] [])),
  (AnnKey tests/examples/Tuple.hs:3:7-25 CN "ExplicitTuple" NotNeeded,
   (Ann (DP (0,0)) (ColDelta 7) DP (0,0) [] [((G AnnOpenP),DP (0,0)),((G AnnCloseP),DP (0,0))])),
  (AnnKey tests/examples/Tuple.hs:3:7-29 CN "HsApp" NotNeeded,
   (Ann (DP (0,0)) (ColDelta 7) DP (0,0) [] [])),
  (AnnKey tests/examples/Tuple.hs:3:7-39 CN "HsApp" NotNeeded,
   (Ann (DP (0,1)) (ColDelta 7) DP (0,1) [] [])),
  (AnnKey tests/examples/Tuple.hs:3:8 CN "HsOverLit" NotNeeded,
   (Ann (DP (0,0)) (ColDelta 8) DP (0,0) [] [((G AnnVal),DP (0,0)),((G AnnComma),DP (0,0))])),
  (AnnKey tests/examples/Tuple.hs:3:8 CN "Present" NotNeeded,
   (Ann (DP (0,0)) (ColDelta 8) DP (0,0) [] [])),
  (AnnKey tests/examples/Tuple.hs:3:11-17 CN "HsLit" NotNeeded,
   (Ann (DP (0,0)) (ColDelta 11) DP (0,0) [] [((G AnnVal),DP (0,0)),((G AnnComma),DP (0,0))])),
  (AnnKey tests/examples/Tuple.hs:3:11-17 CN "Present" NotNeeded,
   (Ann (DP (0,1)) (ColDelta 11) DP (0,1) [] [])),
  (AnnKey tests/examples/Tuple.hs:3:20-22 CN "HsOverLit" NotNeeded,
   (Ann (DP (0,0)) (ColDelta 20) DP (0,0) [] [((G AnnVal),DP (0,0)),((G AnnComma),DP (0,0))])),
  (AnnKey tests/examples/Tuple.hs:3:20-22 CN "Present" NotNeeded,
   (Ann (DP (0,1)) (ColDelta 20) DP (0,1) [] [])),
  (AnnKey tests/examples/Tuple.hs:3:24 CN "Missing" NotNeeded,
   (Ann (DP (0,0)) (ColDelta 24) DP (0,0) [] [((G AnnComma),DP (0,0))])),
  (AnnKey tests/examples/Tuple.hs:3:27-29 CN "HsLit" NotNeeded,
   (Ann (DP (0,1)) (ColDelta 27) DP (0,1) [] [((G AnnVal),DP (0,0))])),
  (AnnKey tests/examples/Tuple.hs:3:31-39 CN "HsPar" NotNeeded,
   (Ann (DP (0,1)) (ColDelta 31) DP (0,1) [] [((G AnnOpenP),DP (0,0)),((G AnnCloseP),DP (0,0))])),
  (AnnKey tests/examples/Tuple.hs:3:32-35 CN "HsVar" NotNeeded,
   (Ann (DP (0,0)) (ColDelta 32) DP (0,0) [] [((G AnnVal),DP (0,0))])),
  (AnnKey tests/examples/Tuple.hs:3:32-38 CN "HsApp" NotNeeded,
   (Ann (DP (0,0)) (ColDelta 32) DP (0,0) [] [])),
  (AnnKey tests/examples/Tuple.hs:3:37-38 CN "HsVar" NotNeeded,
   (Ann (DP (0,1)) (ColDelta 37) DP (0,1) [] [((G AnnOpenP),DP (0,0)),((G AnnCloseP),DP (0,0))])),
  (AnnKey <no location info> CN "EmptyLocalBinds" NotNeeded,
   (Ann (DP (-3,0)) (ColDelta 0) DP (-3,0) [] []))],
 [])
==============
([((tests/examples/Tuple.hs:3:1-39, AnnEqual),
   [tests/examples/Tuple.hs:3:5]),
  ((tests/examples/Tuple.hs:3:1-39, AnnFunId),
   [tests/examples/Tuple.hs:3:1-3]),
  ((tests/examples/Tuple.hs:3:1-39, AnnSemi),
   [tests/examples/Tuple.hs:5:1]),
  ((tests/examples/Tuple.hs:3:7-25, AnnCloseP),
   [tests/examples/Tuple.hs:3:25]),
  ((tests/examples/Tuple.hs:3:7-25, AnnOpenP),
   [tests/examples/Tuple.hs:3:7]),
  ((tests/examples/Tuple.hs:3:8, AnnComma),
   [tests/examples/Tuple.hs:3:9]),
  ((tests/examples/Tuple.hs:3:11-17, AnnComma),
   [tests/examples/Tuple.hs:3:18]),
  ((tests/examples/Tuple.hs:3:20-22, AnnComma),
   [tests/examples/Tuple.hs:3:23]),
  ((tests/examples/Tuple.hs:3:24, AnnComma),
   [tests/examples/Tuple.hs:3:24]),
  ((tests/examples/Tuple.hs:3:31-39, AnnCloseP),
   [tests/examples/Tuple.hs:3:39]),
  ((tests/examples/Tuple.hs:3:31-39, AnnOpenP),
   [tests/examples/Tuple.hs:3:31]),
  ((tests/examples/Tuple.hs:3:37-38, AnnCloseP),
   [tests/examples/Tuple.hs:3:38]),
  ((tests/examples/Tuple.hs:3:37-38, AnnOpenP),
   [tests/examples/Tuple.hs:3:37]),
  ((<no location info>, AnnEofPos), [tests/examples/Tuple.hs:5:1])],
 [(<no location info>,
   [AnnBlockComment "{-# LANGUAGE TupleSections #-}"])])

Test suite run failure from Hackage

Looks like some missing files in the sdist:

### Error in:   189
./tests/examples/UnicodeRules.hs.bad: openFile: does not exist (No such file or directory)
### Error in:   190
./tests/examples/UnicodeSyntax.hs.bad: openFile: does not exist (No such file or directory)
### Error in:   191
./tests/examples/InfixOperator.hs.bad: openFile: does not exist (No such file or directory)
Cases: 213  Tried: 213  Errors: 5  Failures: 0
Counts {cases = 213, tried = 213, errors = 5, failures = 0}
Test suite test: FAIL
Test suite logged to: /home/stackage/work/logs/nightly/ghc-exactprint-0.3.1/test-run.out

addAnnotationsForPretty breaks layout

Consider the following, completely synthesized term:

import Language.Haskell.GHC.ExactPrint
import OccName
import HsExpr
import HsPat
import RdrName
import GHC
import BasicTypes


z :: LHsExpr GhcPs
z = noLoc $ HsVar NoExt $ noLoc $ Unqual $ mkVarOcc "hi"

c :: LHsExpr GhcPs
c = noLoc $ HsCase noExt z $ MG noExt (noLoc
  [ noLoc $ Match noExt CaseAlt [noLoc $ WildPat noExt] $ GRHSs noExt [noLoc $ GRHS noExt [] z] $ noLoc $ EmptyLocalBinds noExt
  , noLoc $ Match noExt CaseAlt [noLoc $ WildPat noExt] $ GRHSs noExt [noLoc $ GRHS noExt [] z] $ noLoc $ EmptyLocalBinds noExt
  , noLoc $ Match noExt CaseAlt [noLoc $ WildPat noExt] $ GRHSs noExt [noLoc $ GRHS noExt [] z] $ noLoc $ EmptyLocalBinds noExt
  ]) Generated

blarg :: String
blarg =
  let anns = addAnnotationsForPretty [] c mempty
   in exactPrint c anns

The above prints

 case hi of
   _ -> hi
      _ -> hi
      _ -> hi

which is completely broken for layout. It should instead be:

case hi of
  _ -> hi
  _ -> hi
  _ -> hi

See also: #80

Weird annotations for comments

If we parse this input:

import qualified MegaModule as M
  ( (>>>) -- (1)
  , (<<<) -- (2)
  , Either -- (3)
  )

-- (1) appears in annotations for (>>>), -- (2) appears in annotations for (<<<), but -- (3) is attached to some weird thingy:

[(AnnKey Foo.hs:1:1 CN "HsModule",
  (Ann (DP (0,0)) [] [] [((G AnnEofPos),DP (1,0))] Nothing Nothing)),
 (AnnKey Foo.hs:(1,1)-(5,3) CN "ImportDecl",
  (Ann (DP (0,0)) [] [] [((G AnnImport),DP (0,0)),((G AnnQualified),DP (0,1)),((G AnnAs),DP (0,1))] Nothing Nothing)),
 (AnnKey Foo.hs:1:18-27 CN "{abstract:ModuleName}",
  (Ann (DP (0,1)) [] [] [((G AnnVal),DP (0,0))] Nothing Nothing)),
 (AnnKey Foo.hs:1:32 CN "{abstract:ModuleName}",
  (Ann (DP (0,1)) [] [] [((G AnnVal),DP (0,0))] Nothing Nothing)),
 (AnnKey Foo.hs:(2,3)-(5,3) CN "(:)",
  (Ann (DP (1,2)) [] [] [((G AnnOpenP),DP (0,0)),((AnnComment (Comment "-- (3)" Foo.hs:4:12-17 Nothing)),DP (0,1)),((G AnnCloseP),DP (1,2))] Nothing Nothing)),
 (AnnKey Foo.hs:2:5-9 CN "IEName",
  (Ann (DP (0,0)) [] [] [] Nothing Nothing)),
 (AnnKey Foo.hs:2:5-9 CN "IEVar",
  (Ann (DP (0,1)) [] [] [((AnnComment (Comment "-- (1)" Foo.hs:2:11-16 Nothing)),DP (0,1)),((G AnnComma),DP (1,2))] Nothing Nothing)),
 (AnnKey Foo.hs:2:5-9 CN "Unqual",
  (Ann (DP (0,0)) [] [] [((G AnnOpenP),DP (0,0)),((G AnnVal),DP (0,0)),((G AnnCloseP),DP (0,0))] Nothing Nothing)),
 (AnnKey Foo.hs:3:5-9 CN "IEName",
  (Ann (DP (0,0)) [] [] [] Nothing Nothing)),
 (AnnKey Foo.hs:3:5-9 CN "IEVar",
  (Ann (DP (0,1)) [] [] [((AnnComment (Comment "-- (2)" Foo.hs:3:11-16 Nothing)),DP (0,1)),((G AnnComma),DP (1,2))] Nothing Nothing)),
 (AnnKey Foo.hs:3:5-9 CN "Unqual",
  (Ann (DP (0,0)) [] [] [((G AnnOpenP),DP (0,0)),((G AnnVal),DP (0,0)),((G AnnCloseP),DP (0,0))] Nothing Nothing)),
 (AnnKey Foo.hs:4:5-10 CN "IEName",
  (Ann (DP (0,0)) [] [] [] Nothing Nothing)),
 (AnnKey Foo.hs:4:5-10 CN "IEThingAbs",
  (Ann (DP (0,1)) [] [] [] Nothing Nothing)),
 (AnnKey Foo.hs:4:5-10 CN "Unqual",
  (Ann (DP (0,0)) [] [] [((G AnnVal),DP (0,0))] Nothing Nothing))]

What on the earth is this "(:)" and why the last comment is treated specially?

Release 0.6.3.3

@alanz Do you mind making a release? I think multiple users have reported the bug in #92 which was fixed in #94 so it's probably worth making a release for it.

Comments are attached to wrong import declarations

We have noticed an inadequate behavior with respect to how comment annotations are generated for import sections. Indeed, it's rather counter-intuitive, for example:

import Foo -- (1)
import Bar -- (2)
import Baz -- (3)

Here, contrary to what a programmer could have meant, -- (1) is saved in the annotation for import Bar, while -- (2) is saved in annotation for import Baz. import Foo doesn't have any comments associated with it, while -- (3) is a comment attached to the entire module.

One could see how wrong this is if we try to do any sort of meaningful transformation on parsed source, such as reordering of imports. Indeed, as simple as it seems, this cannot be done in a satisfactory fashion unless we manage to reassign comments somehow.

Currently we get:

-- (2)
import Bar
-- (3)
import Baz
import Foo

CPP preprocessing

I had taken your Preprocess module and modified it a little to suit my needs for the Argon project. I had encountered a bug in CPP preprocessing, and I see now that it's mentioned in ghc-exactprint's readme.

This is the commit in which I fixed the problem:
rubik/argon@35ad16f

I annotated the commit diff to show exactly what changed. I could submit a PR if you want, but I'd need tests in order to verify my work.

Comments are attached quite incorrectly

Here is an example:

-- | Something.

data Foo
  = Foo Int
        Int
    -- ^ Foo
  | Bar Bool
        Bool
    -- ^ Bar

-- ^ Bar get attached to HsModule, while it's obvious that it should be attached to the Bar data constructor instead.

deltaposition anchor inconsistency

Considering the elements of annsDP, and the anchor of DPs for the contained elements:

  • for comments (AnnComment _, _someDP) the DP is relative to the "current cursor position", i.e. relative to the end of the last thing inserted when pretty-printing;
  • for "normal keyword"s (G _, _someDP) the DP is relative to the node's position (the "cursor position" before pretty-printing anything for the relevant node.

Consider this example:

list = [ some laaaaaaaaaaaaarge expresssion -- this comment has DP (0,1)

       , another thing -- comma at start of this line has DP relative
                       -- to the position before "[", i.e. DP (2,7)
       ]

-- might be re-formatted like this:

list = [ some
           laaaaaaaaaaaaarge
           expresssion -- still at DP (0,1)

       , another thing -- now would be DP (4,7)
       ]

That is, node-relative DPs change when using a different layout for some random child node. If at all possible, an encoding that does not change for such a re-format should be used instead. This would make it much easier for brittany to respect/retain such additional newlines.

(And imho the status quo is just inconsistent and surprising, and it requires additional statefulness when processing annotations.)

Correct behaviour of parseModule

I butchered it a bit when I moved it into the top level module. We should decide what semantics it should have before release.

ParseResult is a different type after 8.10

ParseResult should probably be the same type in any GHC version. It makes reading the haddocks confusing if type aliases are different things in different GHC versions.

Doesn't build with GHC-8.6.1-alpha

When I try to build ghc-exactprint with ghc >= 8.6 in my dependencies, I see the following error:

src/Language/Haskell/GHC/ExactPrint/Types.hs:370:7: error:
    Not in scope: data constructor GHC.VectD
    Neither DynFlags, GHC nor Outputable exports VectD’.
    |
370 |       GHC.VectD d       -> f (GHC.L l d)
    |       ^^^^^^^^^

I could try to fix it by myself but I don't even know where to find Haddock for latest GHC...

addAnnotationsForPretty doesn't play nicely with do blocks

addAnnotationsForPretty inserts a leading space for HsVars (or RdrNames, I haven't dug in). This is the wrong thing to do in the case of a BodyStmt, which will break the do block's layout.

Consider this:

foo = do
  a

and we want to append a new noLoc $ BodyStmt _ (noLoc $ HsVar _ (noLoc $ Unqual "b") _ _ for b into the do block. After making new source spans for the noLocs, wen can call addAnnotationsForPretty, on the BodyStmt above, but printing this is:

foo = do
  a
   b

which is a parse error :(

Test suite failure for package ghc-exactprint-0.6.2

In the Stackage Nightly Nightly build:

    GHC88
### Error in:   5:Default Annotations round-trip tests:1:ghc80:150:SemicolonIf.hs
    ExitFailure 1
Cases: 1979  Tried: 1979  Errors: 1  Failures: 0
    Counts {cases = 1979, tried = 1979, errors = 1, failures = 0}

exactPrinted comments seem to gain additional carriage returns on Windows

ghc-exactprint 0.6.3.1 (ghc-8.10.1) works well on Windows for most code, but it seems to insert extra carriage returns in comments.

For example,

--Another comment
--

newtype N a = Int a

data D a = A a  | B | C a

gets turned into:

--Another comment

--


newtype N a = Int a

data D a = A a  | B | C a

(there are \r\n, rather than \n at the end of each comment line. (Multi-line comments ({-) also have all their internal newlines replaced by cr+nl.)

There are two solutions:

  • get newline to push out \r\n, rather than \n, under Windows
  • always replace \r\nby\nwithin comments

Or you could offer both in different print styles, I suppose, because different people will have different git settings to handle this and golden test case output should be cross-platform.

graftT

I have found this function useful when copying an AST fragment from one module to another:

graftT :: (Data a,Typeable a) => Anns -> a -> Transform a
graftT origAnns = everywhereM (return `ext2M` replaceLocated)
  where
    replaceLocated :: forall loc a. (Typeable loc, Typeable a, Data a)
                    => GenLocated loc a -> Transform (GenLocated loc a)
    replaceLocated (L l t) = do
      case cast l :: Maybe SrcSpan of
        Just ss -> do
          newSpan <- uniqueSrcSpanT
          modifyAnnsT (\anns -> case M.lookup (mkAnnKey (L ss t)) origAnns of
                                  Nothing -> anns
                                  Just an -> M.insert (mkAnnKey (L newSpan t)) an anns)
          return $ fromJust $ cast $ L newSpan t
        Nothing -> return (L l t)

(it is a slightly more general form of cloneT)

Pasting here in case you want to include it with ghc-exactprint.

GHC 8.6 compatibility?

I have

$ cabal --version
cabal-install version 2.2.0.0
compiled using version 2.2.0.1 of the Cabal library 
$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 8.6.0.20180907

(courtesy HVR's PPA)
When cloning the source and doing cabal new-build I get

src/Language/Haskell/GHC/ExactPrint/Parsers.hs:305:3: error:
    • Could not deduce (Control.Monad.Fail.MonadFail m)
        arising from a do statement
        with the failable pattern ‘(dflags3, [], [])’
...

Am I doing something wrong?

Binds of a HsLet ignore the location of HsLocalBinds

To recap our conversation on IRC:

11:47 <ocharles> alanz, mpickering: I'm looking at doing pretty printing with just ghc-exactprint - essentially just moving DPs around to get the formatting I want. It's pretty cool! But I have a q... ghc-exactprint seems to discard some locations, and I wonder why
11:47 <ocharles> for example, Annotate for HsLet in HsExpr ignores the location of the binds of the let statement, so this doesn't do anything:
11:48 <alanz> ocharles: have you looked at brittany? Does a similar thing
11:48 <ocharles> case expr of HsLet binds body -> setEntryDPT binds (DP (100000, 0))
11:48 <ocharles> alanz: yep, I know of brittany, but brittany actually does the printing itself
11:48 <alanz> ocharles: which GHC version?
11:48 <ocharles> I wanted to do nothing except move deltas around
11:49 <ocharles> 8.0.2
11:50 <ocharles> alanz: but https://github.com/alanz/ghc-exactprint/blob/master/src-ghc82/Language/Haskell/GHC/ExactPrint/Annotater.hs#L1877 seems problematic, it just discards the srcspan of the binds
11:51 <alanz> ok, you need to look in the src-ghc80 dir
11:51 <alanz> which is the same
11:51 <alanz> also discards the location
11:51 <ocharles> right
11:52 <alanz> That location was added to allow indexing the list by it, so it could move independently
11:52 <alanz> but before that the engine was set up to ignore it
11:52 <alanz> and I have not gone back to make use of it yey
11:52 <alanz> yet
11:52 <ocharles> ok, so this could be considered a bug?
11:52 <ocharles> hsmodName is similarly affected, setting the entry DP of that doesn't do anything
11:52 <alanz> There was some technical issue about managing the list in the surrounding scope, and breaking existing behaviuour
11:53 <ocharles> and I haven't tried transforming much more than that :)
11:53 <alanz> Well, it is more of a feature at the moment :(
11:53 <alanz> The thing it to look at the Annotater code and see what is used, and work from there
11:54 <alanz> You can also call showAnnData to see exactly what annotations exist
11:54 <ocharles> my use case is I want to "swing" bindings of a let statement under the let, so `let x =` becomes `let\n<space><space>x =`. Right now I'm doing that by using the first location of the binds, but that breaks if the let statement opens with a type signature
11:54 <alanz> What I normally do is run a test with the "from" source code, look at what I get, then with the manually formatted new one, and compare
11:55 <alanz> And that should be possible (it is a design goal), but you need to check what to work with
11:55 <alanz> (my brain is a bit rusty)
11:56 <alanz> iirc, I originally wanted the indent to be on the location of the binds, then each could start at zero and be freely re-arranged
11:56 <alanz> But that is not what ended up in the code, and it needs to be fixed
11:57 <alanz> The "setLayoutFlag" triggers the indentation, by the way
11:57 <alanz> no, sorry, markLocalBindsWithLayout
11:58 <ocharles> so far I haven't written my own interpreter for Annotate because I'm hoping the Print module should be sufficient
11:58 <alanz> it should be
11:59 <alanz> The problem you are seeing comes because the HsLet binds are not decls, so are split into sigs and binds
11:59 <alanz> which means you end up with this: https://github.com/alanz/ghc-exactprint/blob/master/src-ghc80/Language/Haskell/GHC/ExactPrint/Annotater.hs#L1738
11:59 <ocharles> well, that would be one explanation. my expectation was that each dp of the binds (and sigs) are relative to the dp of the whole HsLocalBinds
12:00 <alanz> that is what I want to see too.
12:00 <alanz> Unfortunately it did not happen originally, and needs to be retrofitted to be that way
12:00 <ocharles> ok, if we're in agreement there then I will at least open an issue
12:00 <alanz> please do

Test Suite Failure with GHC 8.2.2

I'm getting a test suite failure building ghc-exactprint with GHC 8.2.2:

Running 1 test suites...
Test suite test: RUNNING...
GHC82
### Failure in: 1:Round-trip tests:0:ghc710:20:Control.hs
tests/Test/Common.hs:123
Control.hs
### Failure in: 1:Round-trip tests:0:ghc710:77:Internals.hs
tests/Test/Common.hs:123
Internals.hs
Cases: 1764  Tried: 1764  Errors: 0  Failures: 2
Counts {cases = 1764, tried = 1764, errors = 0, failures = 2}
Test suite test: FAIL
Test suite logged to: dist/test/ghc-exactprint-0.5.6.1-test.log
0 of 1 test suites (0 of 1 test cases) passed.

I've got this failure with the master branch and several versions from hackage:

  • 0.5.6.1
  • 0.5.6.0
  • 0.5.5.0

parseModuleFromString seems to use unhelpful dflags

I am using ghx-exactprint to write ghc type-checked plugin, with ghc-8.10.1. I am testing it over the agda codebase (https://github.com/agda/agda) as it uses a range of GHC features. ghc-exactprint generally does a great job, but there are a couple of cases where it seems not to respect the language extensions, when parsing a file using parseModuleFromString. If instead, I use parseModuleFromStringInternal with the dflags that ghc provides to a plug-in, everything seems to work well.

So I have a work-around, but thought that I'd report the issue, in case there is an underlying problem, rather than a misuse of ghc-exactprint

For example, parseModulefromString doesn't seem to like this

src/full/Agda/Syntax/Translation/AbstractToConcrete.hs:75:42: error:
    parse error on input ‘:|’
   |
75 | import Agda.Utils.List1 (List1, pattern (:|))
   |                                          ^^

The language extentions in use are:

 On TypeSynonymInstances, On TupleSections, On StandaloneDeriving,
 On ExplicitForAll, On ScopedTypeVariables,
 On DisambiguateRecordFields, On RecordWildCards, On ExplicitForAll,
 On RankNTypes, On PatternSynonyms, On OverloadedStrings,
 On RecordPuns, On MultiWayIf, On ConstrainedClassMethods,
 On MultiParamTypeClasses, On LambdaCase,
 On ConstrainedClassMethods, On MultiParamTypeClasses,
 On FunctionalDependencies, On TypeSynonymInstances,
 On FlexibleInstances, On FlexibleContexts, On ExplicitForAll,
 On ExistentialQuantification, On DeriveFunctor, On DeriveFoldable,
 On DeriveTraversable, On DeriveFunctor, On DeriveFoldable,
 On DefaultSignatures, On ConstraintKinds, On BangPatterns]

A further case is:

src/full/Agda/TypeChecking/Monad/Signature.hs:98:76: error:
    Illegal lambda-case (use LambdaCase)
   |
98 | setTerminates q b = modifySignature $ updateDefinition q $ updateTheDef $ \case
   |                                                                            ^^^^
:
src/full/Agda/TypeChecking/Monad/Signature.hs:845:7: error:
    Illegal bang-pattern (use BangPatterns):
    ! cs'
    |
845 |   let !cs' = cs ++ dataCons def in
    |       ^^^^

with language extensions (extensions dflags)

[On MonoLocalBinds, On KindSignatures, On ExplicitNamespaces,
 On TypeFamilies, On NondecreasingIndentation,
 On TypeSynonymInstances, On TupleSections, On StandaloneDeriving,
 On ExplicitForAll, On ScopedTypeVariables,
 On DisambiguateRecordFields, On RecordWildCards, On ExplicitForAll,
 On RankNTypes, On PatternSynonyms, On OverloadedStrings,
 On RecordPuns, On MultiWayIf, On ConstrainedClassMethods,
 On MultiParamTypeClasses, On LambdaCase,
 On ConstrainedClassMethods, On MultiParamTypeClasses,
 On FunctionalDependencies, On TypeSynonymInstances,
 On FlexibleInstances, On FlexibleContexts, On ExplicitForAll,
 On ExistentialQuantification, On DeriveFunctor, On DeriveFoldable,
 On DeriveTraversable, On DeriveFunctor, On DeriveFoldable,
 On DefaultSignatures, On ConstraintKinds, On BangPatterns]

As I am writing a type-checked phase plugin, ghc has parsed the code without complaint. In fact, I am feeding parseModuleFromString with a string generated by lexemeToString applied to ms_hspp_buf modSummary (ie, the pre-processed source).

As I say, the issue appears to be with the DynFlags that parseModuleFromString conjures up. When I use those provided to the plugin (via getDynFlags and parseModuleFromStringInternal) all seems well. Maybe this can be fixed, or the documentation of the contexts in which parseModuleFromString could be supplemented.

[Later]
Maybe spoke too soon. Source comments appear to be discarded when I use parseModulefromStringIntenal

Anyway thanks for the package.

PS: I assume that the a key reason for having ghc-exactprint is that GHC does not retain enough source code annotations, hence the need to reparse the source.

ghc-exactprint-0.1.0.0 doesn't compile with GHC 7.8.4

I get the following error:

Building ghc-exactprint-0.1.0.0...
Preprocessing library ghc-exactprint-0.1.0.0...
[1 of 3] Compiling Language.Haskell.GHC.ExactPrint.Types ( src/Language/Haskell/GHC/ExactPrint/Types.hs, dist/build/Language/Haskell/GHC/ExactPrint/Types.o )

src/Language/Haskell/GHC/ExactPrint/Types.hs:111:20:
    Not in scope: type constructor or class ‘GHC.AnnKeywordId’

src/Language/Haskell/GHC/ExactPrint/Types.hs:135:20:
    Not in scope: type constructor or class ‘GHC.DataId’
    Perhaps you meant ‘GHC.DataCon’ (imported from GHC)

A complete build log is at http://hydra.cryp.to/build/522473/nixlog/2/raw.

Pure interface for module parsing

Imo the unsafeGlobalDynFlags justify adding a pure wrapper, because "unsafe" and no real documentation that i can find if it is ok to use them.

This probably needs ghc-api additions, like a pure parseDynamicFilePragma.

Parse/Print roundtrip loses shebang unless file path is in the form of "dir/file.hs"

First reported in ndmitchell/hlint#1122 by @pbrisbin

Suppose the content of Foo.hs is

#!/usr/bin/env stack
{- stack --resolver lts-16.10 script -}
module Main (main) where
main :: IO ()
main = putStrLn "hi"

In the following program, only the first way of parsing Foo.hs preserves the shebang.

import Language.Haskell.GHC.ExactPrint.Parsers
import Language.Haskell.GHC.ExactPrint.Print

main :: IO ()
main = do
  Right (as, m) <- parseModule "test/Foo.hs"   -- preserves shebang
  Right (as, m) <- parseModule "./test/Foo.hs" -- loses shebang
  Right (as, m) <- parseModule "Foo.hs"        -- loses shebang
  Right (as, m) <- parseModule "./Foo.hs"      -- loses shebang
  Right (as, m) <- parseModule "/tmp/Foo.hs"   -- loses shebang
  putStrLn $ exactPrint m as

Should the flags be marked manual?

In ghc-exactprint.cabal, the flags dev and roundtrip are automatic, meaning that cabal-install will twiddle them on or off if it feels like it. However, both of them look like they shouldn't be touched automatically, and should be left up to the user to set - i.e., have manual: True.

Exact printing does not work with quasiquoters and whitespace

I have the following program which should just echo back its input:

module Main where

import System.Environment

import HsSyn
import RdrName
import SrcLoc

import Language.Haskell.GHC.ExactPrint

loadModule :: FilePath -> IO (Anns, Located (HsModule RdrName))
loadModule fp = do
    mMod <- parseModule fp
    case mMod of
        Left (src, err) -> fail $ fp ++ ": Parse error: " ++ err ++ " at " ++ show src
        Right res       -> return res

main :: IO ()
main = do
    [file] <- getArgs
    (anns, modul) <- loadModule file
    writeFile (file ++ ".exact") $ exactPrint modul anns

I give the following input to the program:

{-# LANGUAGE QuasiQuotes #-}
module Test where

a = bar
    where
        bar = [q|
            |]

b = bar
    where
        bar = [q|
           |]

c = bar
    where
        bar = [q|
             |]

d = [q|
            |]

This is the generated output:

{-# LANGUAGE QuasiQuotes #-}
module Test where

a = bar
    where
        bar = 


b = bar
    where
        bar = [q|
           |]

c = bar
    where
        bar = [q|
             |]

d = [q|
            |]

So the quasiquoter in the first where-clause disappeared. Adding or removing a single space fixes the problem. Note that the input contains no tabs, only spaces and the problem appears with GHC 7.10.2 and 7.10.3, both with ghc-exactprint 0.5.0.0 from hackage.

Test suite failure with GHC 8.0.2

The output's pretty confusing, so only including a subset of it:

> /tmp/stackage-build13/ghc-exactprint-0.5.2.1$ dist/build/test/test
GHC8
^MCases: 856  Tried: 0  Errors: 0  Failures: 0^MCases: 856  Tried: 1  Errors: 0  Failures: 0^MCases: 856  Tried: 2  Errors: 0  Failures: 0^MCases: 856  Tried: 3  Errors: 0  Failures: 0^MCases: 856  Tried: 4  Errors: 0  Failures: 0^MCases: 856  Tried: 5  Errors: 0  Failures: 0^MCases: 856  Tried: 6  Errors: 0  Failures: 0^MCases: 856  Tried: 7  Errors: 0  Failures: 0^MCases: 856  Tried: 8  Errors: 0  Failures: 0^MCases: 856  Tried: 9  Errors: 0  Failures: 0^MCases: 856  Tried: 10  Errors: 0  Failures: 0^MCases: 856  Tried: 11  Errors: 0  Failures: 0^MCases: 856  Tried: 12  Errors: 0  Failures: 0^MCases: 856  Tried: 13  Errors: 0  Failures: 0^MCases: 856  Tried: 14  Errors: 0  Failures: 0^MCases: 856  Tried: 15  Errors: 0  Failures: 0^MCases: 856  Tried: 16  Errors: 0  Failures: 0^MCases: 856  Tried: 17  Errors: 0  Failures: 0^MCases: 856  Tried: 18  Errors: 0  Failures: 0^MCases: 856  Tried: 19  Errors: 0  Failures: 0^M                                             ^M### Failure in: 1:Round-trip tests:0:ghc710:19
tests/Test.hs:135

Harmonise `annDelta` value

At the top level, annDelta is set to 1 for items against the left margin

Within a list e.g. where clause, each item has an annDelta of 0.

These two should both use the same value, probably 0.

Don't seem to be able to re-order imports

I expect the following code to re-order imports, yet the resulting printed code is in the original order.

import Data.Typeable
import Data.Function
import Data.Ord
import Data.Data
import Data.List
import qualified Data.Map as Map
import GHC hiding (Phase, parseModule)
import Language.Haskell.GHC.ExactPrint
import Language.Haskell.GHC.ExactPrint.Types

formatFile fp = do
  out <- parseModule fp
  case out of
    Left (_, e) ->
      fail $ "Could not parse file: " ++ e

    Right (annotations, parsed) ->
      let (transformed, (anns, _), log) =
            runTransform annotations (sortImports parsed)
      in do
        mapM_ print $ Map.toList annotations
        mapM_ putStrLn log
        return $ exactPrint transformed anns

sortImports :: ParsedSource -> Transform ParsedSource
sortImports lmod@(L l mod) = do
  let newOrder =
        sortBy (comparing (ideclName . unLoc)) (hsmodImports mod)
      lmod' = L (l :: SrcSpan) (mod { hsmodImports = newOrder })
  modifyAnnsT $ captureOrder lmod' newOrder
  logDataWithAnnsTr "HsModule" lmod'
  return lmod'

How to modify Anns / How to use `addAnnotationsForPretty` properly?

I'm using ghc-exactprint to modify some source code.
I parse a haskell module using parseModuleFromString and obtain (Anns, ParsedSource)

Then I modify that ParsedSource and obtain a new ParsedSource.
I tried using addAnnotationsForPretty in the following manner:

Right (oldAnns, parsedSrc) -> do
      let newSrc = someModificationFunction parsedSrc
      let newAnns = addAnnotationsForPretty [] newSrc oldAnns
      pure $ exactPrint newSrc newAnns

When I do this, the file is printed without language extensions and formatting is lost (I'm guessing that since the modified annotations don't match with the new ParsedSource, the annotations are being discarded/not being modified as expected by addAnnotationsForPretty.

What is the best way to modify the existing annotations in order for them to match up/make sense/accomodate for the changes in the ParsedSource ?

comment DeltaPosition indentation logic

Sorry, but I will nag once more about the logic behind DeltaPositions/addEntryDelta, and under what circumstances the "layouting context" (in relation to which positions are expressed) changes. Consider:

func =
  [ foo x
  | y <- z
    -- the DP of this comment is (1, 0). i would expect (1, 4).
   -- the DP of this comment is (1, -1). i would expect (1, 3).
  , x <- y
  ]

From the pure haskell standard perspective, there is only one item in this code affected by the layouting rule: the func binding. This means that the "layouting context" for all the above code is column 0, and thus the (entry)deltas should be relative to column 0. Current behaviour is different - some part of the list/monad comprehensions adds an artificial context. This means that I did not fully describe the current behaviour in #48.

I'd really appreciate if the documentation could be completed, perhaps by those that actually implemented the behaviour. Most important would be a complete list of the cases where artificial contexts are inserted.

(the above code is not printed correctly via brittany at the moment, as a consequence.)

Migrate to ghc-lib

I didn't see an existing issue on this - thought it would be a good idea to create one.

This would enable apply-refact and other libraries depending on ghc-exactprint to migrate to ghc-lib.

delta in unexpected places

If I parse and dump the annotations for print $ 3 + 4, I get:

AnnKey debug:1:1-5 CN "HsVar"
  (Ann (DP (0,0)) [] [] [((G AnnVal),DP (0,0))] Nothing Nothing)
AnnKey debug:1:1-9 CN "OpApp"
  (Ann (DP (0,0)) [] [] [] Nothing Nothing)
AnnKey debug:1:1-13 CN "OpApp"
  (Ann (DP (0,0)) [] [] [] Nothing Nothing)
AnnKey debug:1:7 CN "HsVar"
  (Ann (DP (0,1)) [] [] [((G AnnVal),DP (0,0))] Nothing Nothing)
AnnKey debug:1:9 CN "HsOverLit"
  (Ann (DP (0,1)) [] [] [((G AnnVal),DP (0,0))] Nothing Nothing)
AnnKey debug:1:11 CN "HsVar"
  (Ann (DP (0,1)) [] [] [((G AnnVal),DP (0,0))] Nothing Nothing)
AnnKey debug:1:13 CN "HsOverLit"
  (Ann (DP (0,1)) [] [] [((G AnnVal),DP (0,0))] Nothing Nothing)

The delta offset for 3 + 4 is actually on 3, instead of +, as I would've guessed. This makes it difficult to transfer/swap deltas correctly. If I try to set the delta entry of 3 + 4, I get the extra space from 3.

Are there library functions I've missed for getting/setting the "true" offset of an expression like 3 + 4? (Perhaps by walking the left children... for whatever "left" means.) Alternatively, is it possible to assign the delta entry to + instead of 3? (And in general, assign to the outermost enclosing AST element.)

MIN_VERSION macros need special processing.

We get the following roundtrip result.

./hackage-roundtrip-work/Agda-2.5.2/src/full/Agda/Utils/Functor.hs

21c21
< -- #if !MIN_VERSION_transformers(0,4,1)
---
> -- #if !MIN_VERSION_transformers(0,4,1)-- #if !(  (0) <  0 ||   (0) == 0 && (4) <  5 ||   (0) == 0 && (4) == 5 && (1) <= 2)
94a95
> 

These are likely to be quite common, we need to come up with a way around them.

Usage examples?

I'm having a go at using exactprint to add an explicit export list for a module. So starting from something without an explicit export list, I should get

module Test.ExportExplicit (isExported, anotherExport, andAnother) where

isExported = (+1)

anotherExport = True

andAnother = 27

main :: IO ()
main = pure ()

So far, I get almost the right output; it is missing commas:

module Test.ExportImplicit (alsoExportedisExportedmain) where

isExported = (+1)

alsoExported = True

main :: IO ()
main = print $ isExported 1

The core of my code is

   22 mkIEVarFromNameT :: Monad m => Name -> TransformT m (Located (IE GhcPs))
   23 mkIEVarFromNameT name = do
   24   loc <- uniqueSrcSpanT
   25   return $ L
   26     loc
   27     (IEVar noExt
   28            (L loc (IEName (L loc (mkVarUnqual ((occNameFS . occName) name)))))
   29     )
   30 
   31 addExportDeclAnnT :: Monad m => Located (IE GhcPs) -> TransformT m ()
   32 addExportDeclAnnT (L _ (IEVar _ (L _ (IEName x)))) =
   33   addSimpleAnnT x (DP (0, 0)) [(G AnnVal, DP (0, 0))]
   34   
   35 mkNamesFromAvailInfos :: [AvailInfo] -> [Name]
   36 mkNamesFromAvailInfos = concatMap availNames -- there are also other choices

   94     addExports
   95       :: DynFlags
   96       -> [AvailInfo]
   97       -> (Anns, Located (HsModule GhcPs))
   98       -> (Anns, Located (HsModule GhcPs))
   99     addExports dflags exports (anns, ast@(L astLoc hsMod)) = do
  100       let
  101         names = mkNamesFromAvailInfos exports
  102         (exports', (anns', n), s) =
  103           --
  104           runTransform anns $ mapM mkIEVarFromNameT names
  105 
  106         addExportDecls
  107           :: [Located (IE GhcPs)] -> Transform (Located (HsModule GhcPs))
  108         addExportDecls expl = do
  109           let hsMod' = hsMod { hsmodExports = Just $ L astLoc expl }
  110           mapM_ addTrailingCommaT expl -- init expl
  111           mapM_ addExportDeclAnnT expl
  112           addSimpleAnnT (L astLoc expl)
  113                         (DP (0, 1))
  114                         [(G AnnOpenP, DP (0, 0)), (G AnnCloseP, DP (0, 0))]
  115           return (L astLoc hsMod')
  116 
  117         (ast', (anns'', n'), s') = runTransform anns' (addExportDecls exports')
  118 
  119       (anns'', ast')

anns'' contains no comma annotations, whereas I would have expected the result to be something like the following (generated by brittany)

A Just (Ann (DP (0,0)) [] [] [((G AnnModule),DP (0,0)),((G AnnVal),DP (0,1)),((G AnnWhere),DP (0,1)),((G AnnEofPos),DP (1,0))] Nothing Nothing)
  HsModule
    Just (A (Nothing) {abstract:ModuleName})
    Just
      A Just (Ann (DP (0,1)) [] [] [((G AnnOpenP),DP (0,0)),((G AnnCloseP),DP (0,0))] Nothing Nothing)
        [ A Just (Ann (DP (0,0)) [] [] [((G AnnComma),DP (0,0))] Nothing Nothing)
            IEVar
              NoExt
              A Just (Ann (DP (0,0)) [] [] [] Nothing Nothing)
                IEName
                  A Just (Ann (DP (0,0)) [] [] [((G AnnVal),DP (0,0))] Nothing Nothing)
                    Unqual {OccName: isExported}
        , A Just (Ann (DP (0,1)) [] [] [((G AnnComma),DP (0,0))] Nothing Nothing)
            IEVar
              NoExt
              A Just (Ann (DP (0,0)) [] [] [] Nothing Nothing)
                IEName
                  A Just (Ann (DP (0,0)) [] [] [((G AnnVal),DP (0,0))] Nothing Nothing)
                    Unqual {OccName: anotherExport}
        , A Just (Ann (DP (0,1)) [] [] [] Nothing Nothing)
            IEVar
              NoExt
              A Just (Ann (DP (0,0)) [] [] [] Nothing Nothing)
                IEName
                  A Just (Ann (DP (0,0)) [] [] [((G AnnVal),DP (0,0))] Nothing Nothing)
                    Unqual {OccName: andAnother}
        ]

I'm clearly not applying addTrailingCommaT correctly at line 110. Is there an obvious bug, or is there a better example of how to generate the additional syntax from a given list of '[Name]'? The only libraries that seem to use ghc-exacprint are apply-refact, brittany, HaRe, hgrep, lens-th-rewrite, retrie and smuggler, but I haven't found anything that is obviously on point in them. Thanks.

PS: ppr ast' seems to put in its own brackets

module Test.ExportImplicit (
        alsoExported, isExported, main
    ) where
isExported = (+ 1)
alsoExported = True
main :: IO ()
main = print $ isExported 1

Roundtripping breaks when using exactPrint on single LHsDecl

code to reproduce:

module Main where



import           DynFlags ( getDynFlags )
import           GHC ( runGhc, GenLocated(L), moduleNameString )
import qualified DynFlags      as GHC
import qualified GHC           as GHC hiding (parseModule)
import qualified Parser        as GHC
import qualified SrcLoc        as GHC
import           RdrName ( RdrName(..) )
import           HsSyn
import           SrcLoc ( SrcSpan, Located )
import           RdrName ( RdrName(..) )

import Control.Monad.Trans.Either as EitherT
import qualified System.IO
import Control.Monad.IO.Class
import Control.Monad.Trans.Class

import qualified Language.Haskell.GHC.ExactPrint            as ExactPrint
import qualified Language.Haskell.GHC.ExactPrint.Parsers    as ExactPrint

import qualified Data.Generics as SYB

import Control.Monad



(<&>) = flip (<$>)

parseModuleFromString
  :: [String]
  -> System.IO.FilePath
  -> String
  -> IO (Either String (ExactPrint.Anns, GHC.ParsedSource))
parseModuleFromString args fp str =
  ExactPrint.ghcWrapper $ EitherT.runEitherT $ do
    dflags0                       <- lift $ ExactPrint.initDynFlagsPure fp str
    (dflags1, leftover, warnings) <-
      lift $ GHC.parseDynamicFlagsCmdLine dflags0 (GHC.noLoc <$> args)
    when (not $ null leftover)
      $  EitherT.left
      $  "when parsing ghc flags: leftover flags: "
      ++ show (leftover <&> \(L _ s) -> s)
    when (not $ null warnings)
      $  EitherT.left
      $  "when parsing ghc flags: encountered warnings: "
      ++ show (warnings <&> \(L _ s) -> s)
    EitherT.hoistEither
      $ either (\(span, err) -> Left $ show span ++ ": " ++ err)
               (\(a, m) -> Right (a, m))
      $ ExactPrint.parseWith dflags1 fp GHC.parseModule str

main = do
  let extensions = []
  let input = "type instance HReplicateR 'HZero e = '[]"
  Right (anns, parsedSource@(L _ modul)) <- parseModuleFromString extensions "stdin" input
  putStrLn $ ExactPrint.exactPrint parsedSource anns
  hsmodDecls modul `forM_` \d -> putStrLn $ ExactPrint.exactPrint d anns

then

> ghc Main.hs -package ghc-8.0.2
> [1 of 1] Compiling Main             ( Main.hs, Main.o )
Linking Main ...
> ./Main
type instance HReplicateR 'HZero e = '[]
type HReplicateR 'HZero e = '[]            # this is problematic.

Missing testsuite for ghc 8.2

Test suite test: RUNNING...
GHC82
test: tests/examples/ghc82: getDirectoryContents:openDirStream: does not exist (No such file or directory)

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.