ghc-exactprint icon indicating copy to clipboard operation
ghc-exactprint copied to clipboard

Usage examples?

Open jrp2014 opened this issue 4 years ago • 14 comments

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

jrp2014 avatar Apr 13 '20 14:04 jrp2014

In lines 24-29 (mkIEVarFromNameT) you reuse the same unique loc, which means that there is one AnnKey shared between IEVar, IEName and Unqual. As a consequence, in line 111 you overwrite the annotation value that was modified in 110.

lspitzner avatar Apr 13 '20 15:04 lspitzner

Or written in imperative style, your code roughly reads as

024 loc1 = loc2 = loc3 = generateUnique();
110 myAnnMap[loc1].annsDP = myMap[loc1].annsDP ++ [comma];
111 myAnnMap[loc2] = { dp = .., annsDP = .. };

lspitzner avatar Apr 13 '20 15:04 lspitzner

Thanks for looking, Lennart. I'm clearly being thick, but the following produces the same result.

mkIEVarFromNameT :: Monad m => Name -> TransformT m (Located (IE GhcPs))
   23 mkIEVarFromNameT name = do
   24   locIEVar  <- uniqueSrcSpanT
   25   locIEName <- uniqueSrcSpanT
   26   locUnqual <- uniqueSrcSpanT
   27   return $ L
   28     locIEVar
   29     (IEVar
   30       noExt
   31       (L locIEName
   32          (IEName (L locUnqual (mkVarUnqual ((occNameFS . occName) name))))
   33       )
   34     )

jrp2014 avatar Apr 13 '20 16:04 jrp2014

Oh, right. Try refactoring the code so that you only do one runTransform. The return value from uniqueSrcSpanT is only as unique as the state of the Transform, and every runTransform sets it to the same 0. So you still share keys atm.

lspitzner avatar Apr 13 '20 17:04 lspitzner

Although you only have 2 runTransforms, I thought you had more. Maybe try testing this hypothesis by using runTransformFrom n in line 117.

lspitzner avatar Apr 13 '20 17:04 lspitzner

If that works you can refactor the code to clean it up. It should be a bit cleaner with a single runTransform on the outside.

lspitzner avatar Apr 13 '20 17:04 lspitzner

hm no, you don't use uniqueSrcSpanT in the second runTransform. But I don't trust yet that you don't have overlapping keys nonetheless. Maybe the whole addExports should be a monadic Transform (HsModule GhcPs).

lspitzner avatar Apr 13 '20 17:04 lspitzner

Thanks to your first hins, I got the following to work! This is probably more by luck than by analysis, so it's probably buggy, and I need to simplify it. I'll have a go with the runTransformFrom n.

In your refactoring suggestion, do you mean composing the various annotation steps into one? I think that adding the () and annotating the IEVar still need to be two steps. But I could take the runTransform out of addExportDecls to the call site?

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

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

jrp2014 avatar Apr 13 '20 17:04 jrp2014

I recommend to Debug.Trace.trace the involved keys/locs to diagnose this. astLoc in line 98 and loc in 27 might still be the same.

lspitzner avatar Apr 13 '20 17:04 lspitzner

Using traceM I got

astLoc: RealSrcSpan SrcSpanPoint "test/Test/ExportImplicit.hs" 1 1
loc: RealSrcSpan SrcSpanPoint "ghc-exactprint" -1 0
loc: RealSrcSpan SrcSpanPoint "ghc-exactprint" -1 1
loc: RealSrcSpan SrcSpanPoint "ghc-exactprint" -1 2

If you have suggestions for cleaning up the code, they'd be v welcome.

jrp2014 avatar Apr 13 '20 17:04 jrp2014

oh, that is good to know. So I was wrong about the "overlapping keys" idea.

The difference is just addTrailingCommaT vs addSimpleAnnT - the former does not add an annotation to the map if it does not exist. I missed that detail earlier. The correct translation would have been:

024 loc1 = loc2 = loc3 = generateUnique(); 110 if (myAnnMap[loc1]) { myAnnMap[loc1].annsDP = myMap[loc1].annsDP ++ [comma] }; 111 myAnnMap[outerLoc] = { dp = .., annsDP = .. };

Sorry for pushing in the wrong directions with my attempts of debugging this. Glad you got something working. I am still confused why it works to be honest, because you are sharing keys again, and it seems you overwrite the annotations containing AnnVal. But maybe I overlook something.

I'd refactor it like this (doing this blind, hopefully it is not too broken):

addExports
  :: DynFlags
  -> [AvailInfo]
  -> (Anns, Located (HsModule GhcPs))
  -> (Anns, Located (HsModule GhcPs))
addExports dflags exports (anns, ast@(L astLoc hsMod)) =
  -- runTransform :: Anns -> Transform a -> (a, (Anns, Int), [String])
  let (ast', (anns', _), s') = runTransform anns $ do
        let names = mkNamesFromAvailInfos exports
        (exports', (anns', n), s) <- mapM mkIEVarFromNameT names

        let addExportDecls
              :: [Located (IE GhcPs)] -> Transform (Located (HsModule GhcPs))
            addExportDecls expl = do
              let hsMod' = hsMod { hsmodExports = Just $ L astLoc expl }
              addSimpleAnnT
                (L astLoc expl)
                (DP (0, 1))
                [(G AnnOpenP, DP (0, 0)), (G AnnCloseP, DP (0, 1))]
              mapM_ addExportDeclAnnT expl
              mapM_ addCommaT         (init expl)
              return (L astLoc hsMod')

        addExportDecls exports'
  in  (anns', ast')

lspitzner avatar Apr 13 '20 20:04 lspitzner

Many thanks. That was v helpful and allowed me to clean up further to:

   58   addExplicitExports
   59     :: DynFlags
   60     -> [AvailInfo]
   61     -> (Anns, Located (HsModule GhcPs))
   62     -> (Anns, Located (HsModule GhcPs))
   63   addExplicitExports dflags exports (anns, L astLoc hsMod) = (anns', ast')
   64    where
   65     (ast', (anns', _n), _s) = runTransform anns $ do
   66 
   67       let names = mkNamesFromAvailInfos exports
   68       exportsList <- mapM mkIEVarFromNameT names
   69 
   70       let lExportsList = L astLoc exportsList
   71           hsMod'       = hsMod { hsmodExports = Just lExportsList }
   72       addParensT lExportsList
   73       mapM_ addExportDeclAnnT exportsList
   74       unless (null exportsList) $ mapM_ addCommaT (init exportsList)
   75       return (L astLoc hsMod')

with

   14 mkNamesFromAvailInfos :: [AvailInfo] -> [Name]
   15 mkNamesFromAvailInfos = concatMap availNames -- there are also other choices
   16 
   17 mkIEVarFromNameT :: Monad m => Name -> TransformT m (Located (IE GhcPs))
   18 mkIEVarFromNameT name = do
   19   locIEVar <- uniqueSrcSpanT
   20   locIEName <- uniqueSrcSpanT
   21   locUnqual <- uniqueSrcSpanT
   22   return $
   23     L
   24       locIEVar
   25       ( IEVar
   26           noExt
   27           ( L
   28               locIEName
   29               (IEName (L locUnqual (mkVarUnqual ((occNameFS . occName) name))))
   30           )
   31       )
   32 
   33 addExportDeclAnnT :: Monad m => Located (IE GhcPs) -> TransformT m ()
   34 addExportDeclAnnT (L _ (IEVar _ (L _ (IEName x)))) =
   35   addSimpleAnnT x (DP (1, 2)) [(G AnnVal, DP (0, 0))]
   36 
   37 addCommaT :: Monad m => Located (IE GhcPs) -> TransformT m ()
   38 addCommaT x = addSimpleAnnT x (DP (0, 0)) [(G AnnComma, DP (0, 0))]
   39 
   40 addParensT :: Monad m => Located [Located (IE GhcPs)] -> TransformT m ()
   41 addParensT x =
   42   addSimpleAnnT
   43     x
   44     (DP (0, 1))
   45     [(G AnnOpenP, DP (0, 0)), (G AnnCloseP, DP (0, 1))]

which seems much more satisfying.

I'll restored the 3 different invocations just in case ...

I'm happy to provide further debugging output if it'd help unravel the conundrum, or take any further stylistic improvements.

Many thanks for your time.

jrp2014 avatar Apr 13 '20 21:04 jrp2014

That looks good.

I just noticed that the AnnKeys are different if they are on different constructors. So because you have a IEVar, a IEName and an Unqual you should be safe sharing the SrcSpan. Maybe it is a good idea in general to avoid that because you might forget about it and share it on the same constructor in the future, but technically it is not necessary here. This is the reason why the other version worked.

lspitzner avatar Apr 14 '20 13:04 lspitzner

Thanks. Noted.

To come back to the original original question, it'd be great to have some fuller top-level documentation or examples of the use of this library and where the pitfalls are.

jrp2014 avatar Apr 14 '20 17:04 jrp2014