Git Product home page Git Product logo

ghc-source-gen's Introduction

ghc-source-gen

ghc-source-gen is a Haskell library for generating Haskell source files and code fragments. It uses GHC's library API to support the latest syntax, and provides a simple, consistent interface across several major versions of GHC.

To get started, take a look at the example below, or check out the GHC.SourceGen module.

This package is not an officially supported Google product.

Example

The following example creates a module that defines the const function:

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
import GHC.SourceGen
import GHC.Paths (libdir)
import GHC (runGhc)

constModule :: HsModule'
constModule =
    module' (Just "Const") (Just [var "const"]) []
        [ typeSig "const" $ a --> b --> a
        , funBind "const" $ match [x, wildP] x
        ]
  where
    a = var "a"
    b = var "b"
    x = bvar "x"

main = runGhc (Just libdir) $ putPpr constModule

The output of that program is:

module Const (
        const
    ) where
const :: a -> b -> a
const x _ = x

Comparison with the GHC API

The raw GHC API has several complexities that ghc-source-gen simplifies for the purpose of source code generation.

Backwards-compatibility

ghc-source-gen provides the same API across several versions of GHC. Code written with ghc-source-gen should compile unchanged on each of those versions.

Currently, this library supports GHC versions 8.2, 8.4, 8.6 and 8.8.

One caveat: ghc-source-gen supports some forms of syntax which are not implemented by all of those GHC versions. For example, the DerivingVia extension is only implemented in ghc >= 8.6. When built on older versions of GHC, ghc-source-gen will omit functions for constructing that syntax (for example: GHC.SourceGen.Decl.derivingVia). We will also tag any such function with a note in its Haddock documentation.

Less verbose types and construction functions

The datatypes that GHC uses to represent Haskell syntax change their representation at different stages of the compilation: for example, parsing, renaming, or type-checking. That data transformation provides type safety and a uniform structure across the phases. However, it also adds unnecessary complexity to the task of source code generation.

ghc-source-gen aims to provide a simple interface by creating data types as GHC would represent them immediately after its parsing step. For example, ghc >= 8.4 uses a type parameter p in its syntax types: HsExpr p for expressions, HsDecl p for declarations, etc. ghc-source-gen defines type synonyms for them:

type HsExpr' = HsExpr GhcPs
type HsDecl' = HsDecl GhcPs
type HsType' = HsType GhcPs
-- etc.

Furthermore, most constructors take an extra "extension" field which can contain different information in different stages, influenced by the parameter p. In almost all cases, after the parsing step that field is the trivial type data NoExt = NoExt. (For more details, see the Trees that Grow paper. GHC versions earlier than 8.4 used a similar PlaceHolder type.). This extra data makes code generation more verbose.

ghc-source-gen automatically sets the NoExt value (or equivalent) for the terms that it generates, hiding that detail from its external API. It also sets and hides other fields that are irrelevant to parsing or pretty-printing, such as simplifier ticks.

Source Locations

GHC carefully tracks the source location of (nearly) every node in the AST. That information is very useful for error reporting. However, it would be too verbose to set it explicitly for each individual node during code generation. Furthermore, GHC doesn't use the source location when pretty-printing its output, which is ghc-source-gen's main use case.

Currently, ghc-source-gen gives to each node it generates a trivial location without an explicit line or column.

Parentheses

GHC represents parentheses explicitly in its syntax tree, so that it can print code exactly as it was parsed. Unfortunately, this means that its pretty-printing code expects those parentheses to be present, and outputs incorrect source code if they are missing. ghc-source-gen adds parentheses automatically in the code that it generates.

For example, consider a simplified expression syntax:

data Expr
    = VarE String      -- ^ Variables
    | App Expr Expr    -- ^ Function application
    | Paren Expr Expr  -- ^ Parentheses

Then GHC would pretty-print as "f (g x)" the tree

App (VarE "f") $ Paren $ App (VarE "g") (VarE "h")

But without the explicit parenthesis, it would pretty-print as "f g x":

App (VarE "f") $ App (VarE "g") (VarE "h")

which misrepresents the precedence between the two function applications.

ghc-source-gen resolves this issue by inserting parentheses automatically, and only when necessary. In the expression

var "f" @@ (var "g" @@ var "h")

it inserts a parenthesis automatically so that the result pretty-prints to "f (g x)" as expected.

GHC uses a similar approach internally itself. For more discussion, see tickets 14289 and 15738.

ghc-source-gen's People

Contributors

arifordsham avatar avdv avatar blackgnezdo avatar brandon-leapyear avatar ersran9 avatar felixonmars avatar isovector avatar jinwoo avatar judah avatar mattapet avatar mithrandi avatar mxxun avatar ocharles avatar v0d1ch 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  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

ghc-source-gen's Issues

Build failure on GHC 9.6

Hi,
when building ghc-source-gen 0.4.3.0 on GHC 9.6.3, the following 5 errors occurred:

Configuring ghc-source-gen-0.4.3.0...
Preprocessing library for ghc-source-gen-0.4.3.0..
Building library for ghc-source-gen-0.4.3.0..
[ 1 of 18] Compiling GHC.SourceGen.Pretty ( src/GHC/SourceGen/Pretty.hs, dist/build/GHC/SourceGen/Pretty.dyn_o )
[ 2 of 18] Compiling GHC.SourceGen.Syntax.Internal ( src/GHC/SourceGen/Syntax/Internal.hs, dist/build/GHC/SourceGen/Syntax/Internal.dyn_o )
[ 3 of 18] Compiling GHC.SourceGen.Name.Internal ( src/GHC/SourceGen/Name/Internal.hs, dist/build/GHC/SourceGen/Name/Internal.dyn_o )
[ 4 of 18] Compiling GHC.SourceGen.Name ( src/GHC/SourceGen/Name.hs, dist/build/GHC/SourceGen/Name.dyn_o )
[ 5 of 18] Compiling GHC.SourceGen.Lit.Internal ( src/GHC/SourceGen/Lit/Internal.hs, dist/build/GHC/SourceGen/Lit/Internal.dyn_o )
[ 6 of 18] Compiling GHC.SourceGen.Pat.Internal ( src/GHC/SourceGen/Pat/Internal.hs, dist/build/GHC/SourceGen/Pat/Internal.dyn_o )
[ 7 of 18] Compiling GHC.SourceGen.Module ( src/GHC/SourceGen/Module.hs, dist/build/GHC/SourceGen/Module.dyn_o )

src/GHC/SourceGen/Module.hs:41:26: error:
    Module ‘GHC.Types.SrcLoc’ does not export ‘LayoutInfo(..)’
   |
41 | import GHC.Types.SrcLoc (LayoutInfo(..))
   |                          ^^^^^^^^^^^^^^
[ 8 of 18] Compiling GHC.SourceGen.Lit ( src/GHC/SourceGen/Lit.hs, dist/build/GHC/SourceGen/Lit.dyn_o )
[ 9 of 18] Compiling GHC.SourceGen.Expr.Internal ( src/GHC/SourceGen/Expr/Internal.hs, dist/build/GHC/SourceGen/Expr/Internal.dyn_o )
[10 of 18] Compiling GHC.SourceGen.Binds.Internal ( src/GHC/SourceGen/Binds/Internal.hs, dist/build/GHC/SourceGen/Binds/Internal.dyn_o )

src/GHC/SourceGen/Binds/Internal.hs:86:11: error: [GHC-83865]
    • Couldn't match type ‘Origin’
                     with ‘Language.Haskell.Syntax.Extension.NoExtField’
      Expected: NoExtField
                -> GHC.Types.SrcLoc.GenLocated
                     (SrcSpanAnn GHC.Parser.Annotation.AnnList)
                     [GHC.Types.SrcLoc.GenLocated
                        (SrcSpanAnn GHC.Parser.Annotation.AnnListItem)
                        (Match
                           GHC.Hs.Extension.GhcPs
                           (GHC.Types.SrcLoc.GenLocated
                              GHC.Parser.Annotation.SrcSpanAnnA
                              (Language.Haskell.Syntax.Expr.HsExpr GHC.Hs.Extension.GhcPs)))]
                -> Origin
                -> MatchGroup
                     GHC.Hs.Extension.GhcPs
                     (GHC.Types.SrcLoc.GenLocated
                        GHC.Parser.Annotation.SrcSpanAnnA
                        (Language.Haskell.Syntax.Expr.HsExpr GHC.Hs.Extension.GhcPs))
        Actual: Language.Haskell.Syntax.Extension.XMG
                  GHC.Hs.Extension.GhcPs
                  (GHC.Types.SrcLoc.GenLocated
                     GHC.Parser.Annotation.SrcSpanAnnA
                     (Language.Haskell.Syntax.Expr.HsExpr GHC.Hs.Extension.GhcPs))
                -> Language.Haskell.Syntax.Extension.XRec
                     GHC.Hs.Extension.GhcPs
                     [Language.Haskell.Syntax.Expr.LMatch
                        GHC.Hs.Extension.GhcPs
                        (GHC.Types.SrcLoc.GenLocated
                           GHC.Parser.Annotation.SrcSpanAnnA
                           (Language.Haskell.Syntax.Expr.HsExpr GHC.Hs.Extension.GhcPs))]
                -> MatchGroup
                     GHC.Hs.Extension.GhcPs
                     (GHC.Types.SrcLoc.GenLocated
                        GHC.Parser.Annotation.SrcSpanAnnA
                        (Language.Haskell.Syntax.Expr.HsExpr GHC.Hs.Extension.GhcPs))
    • In the first argument of ‘noExt’, namely ‘MG’
      In the expression:
        noExt MG (mkLocated $ map (mkLocated . mkMatch) matches) Generated
      In an equation for ‘matchGroup’:
          matchGroup context matches
            = noExt
                MG (mkLocated $ map (mkLocated . mkMatch) matches) Generated
            where
                mkMatch :: RawMatch -> Match' LHsExpr'
                mkMatch r
                  = withEpAnnNotUsed
                      Match context (map builtPat $ map parenthesize $ rawMatchPats r)
                      (mkGRHSs $ rawMatchGRHSs r)
   |
86 |     noExt MG (mkLocated $ map (mkLocated . mkMatch) matches)
   |           ^^
[11 of 18] Compiling GHC.SourceGen.Type.Internal ( src/GHC/SourceGen/Type/Internal.hs, dist/build/GHC/SourceGen/Type/Internal.dyn_o )
[12 of 18] Compiling GHC.SourceGen.Type ( src/GHC/SourceGen/Type.hs, dist/build/GHC/SourceGen/Type.dyn_o )
[13 of 18] Compiling GHC.SourceGen.Pat ( src/GHC/SourceGen/Pat.hs, dist/build/GHC/SourceGen/Pat.dyn_o )

src/GHC/SourceGen/Pat.hs:43:30: error: [GHC-83865]
    • Couldn't match type: Language.Haskell.Syntax.Extension.XRec
                             p0 (Pat p0)
                           -> Pat p0
                     with: Pat GHC.Hs.Extension.GhcPs
      Expected: EpAnn ann0
                -> GHC.Parser.Annotation.LocatedN GHC.Types.Name.Reader.RdrName
                -> Language.Haskell.Syntax.Extension.XRec
                     p0 (Language.Haskell.Syntax.Concrete.HsToken "@")
                -> Pat'
        Actual: Language.Haskell.Syntax.Extension.XAsPat p0
                -> Language.Haskell.Syntax.Extension.LIdP p0
                -> Language.Haskell.Syntax.Concrete.LHsToken "@" p0
                -> LPat p0
                -> Pat p0
    • Probable cause: ‘AsPat’ is applied to too few arguments
      In the first argument of ‘withEpAnnNotUsed’, namely ‘AsPat’
      In the first argument of ‘($)’, namely
        ‘withEpAnnNotUsed AsPat (valueRdrName v)’
      In the expression:
        withEpAnnNotUsed AsPat (valueRdrName v) $ builtPat $ parenthesize p
   |
43 | v `asP` p = withEpAnnNotUsed AsPat (valueRdrName v) $ builtPat $ parenthesize p
   |                              ^^^^^

src/GHC/SourceGen/Pat.hs:43:55: error: [GHC-83865]
    • Couldn't match type: Pat GHC.Hs.Extension.GhcPs
                     with: Language.Haskell.Syntax.Concrete.HsToken "@"
      Expected: Language.Haskell.Syntax.Extension.XRec
                  p0 (Language.Haskell.Syntax.Concrete.HsToken "@")
        Actual: LPat'
    • In the second argument of ‘($)’, namely
        ‘builtPat $ parenthesize p’
      In the expression:
        withEpAnnNotUsed AsPat (valueRdrName v) $ builtPat $ parenthesize p
      In an equation for ‘asP’:
          v `asP` p
            = withEpAnnNotUsed AsPat (valueRdrName v)
                $ builtPat $ parenthesize p
   |
43 | v `asP` p = withEpAnnNotUsed AsPat (valueRdrName v) $ builtPat $ parenthesize p
   |                                                       ^^^^^^^^^^^^^^^^^^^^^^^^^
[14 of 18] Compiling GHC.SourceGen.Overloaded ( src/GHC/SourceGen/Overloaded.hs, dist/build/GHC/SourceGen/Overloaded.dyn_o )

src/GHC/SourceGen/Overloaded.hs:289:39: error: [GHC-83865]
    • Couldn't match type: Language.Haskell.Syntax.Extension.XRec
                             p0 (Language.Haskell.Syntax.Extension.IdP p0)
                           -> IEWrappedName p0
                     with: IEWrappedName GHC.Hs.Extension.GhcPs
      Expected: IEWrappedName GHC.Hs.Extension.GhcPs
        Actual: Language.Haskell.Syntax.Extension.LIdP p0
                -> IEWrappedName p0
    • Probable cause: ‘($)’ is applied to too few arguments
      In the second argument of ‘($)’, namely ‘IEName $ exportRdrName n’
      In the second argument of ‘($)’, namely
        ‘mkLocated $ IEName $ exportRdrName n’
      In the expression:
        noExt IEVar $ mkLocated $ IEName $ exportRdrName n
    |
289 |     var n = noExt IEVar $ mkLocated $ IEName $ exportRdrName n
    |                                       ^^^^^^^^^^^^^^^^^^^^^^^^

There are two types of issues, one is a missing definition (the first error), the other is failing to match various types (the other 4 errors). I'm not sure how to go about fixing those. Do you have an idea?

System information

OS: Arch Linux
Kernel: 6.6.7-arch1-1
GHC: 9.6.3
ghc-source-gen: 0.4.3.0

Request for new release

Hi,
The current master branch supports GHC 9.4, but there was no release to hackage. This effectively blocks Arch Linux from upgrading to newer versions of GHC.

Please make a new release including the support for GHC 9.4.
Are there specific roadblocks preventing a release at this time? I also saw another PR for GHC 9.6 support.

Gratefully,
Vekhir

Support for generating haddock comments

Has there been any thought on adding support for module / declaration / parameter haddock comments? I'm trying to use this library to generate code that I would like to have nice haddock documentation on.

I tried my hand at implementing comments for modules at it seems as simple as filling out hsmodHaddockModHeader on HsModule, but as of 8.10 the Outputable instance on HsDocString wraps the output in double quotes which results in invalid Haskell.

collectModuleName breaks in the presence of MagicHash

Consider the perfectly reasonable name under -XMagicHash: Jn#. This causes an error:

Unable to parse RdrNameStr: "Jn#"
CallStack (from HasCallStack):
  error, called at src/GHC/SourceGen/Name/Internal.hs:106:10 in ghc-source-gen-0.4.0.0-5bO8D09FGq6LIxEy1df7VD:GHC.SourceGen.Name.Internal

Build error with GHC 8.10.7 in ghc-source-gen-0.4.4.0

When building with GHC 8.10.7, I get this error:

[10 of 25] Compiling GHC.SourceGen.Module ( src/GHC/SourceGen/Module.hs, dist/build/GHC/SourceGen/Module.o, dist/build/GHC/SourceGen/Module.dyn_o )

src/GHC/SourceGen/Module.hs:191:41: error:
    Variable not in scope: unqual :: OccNameStr -> RdrNameStr
    |
191 |                     (map (wrappedName . unqual) cs)
    |                                         ^^^^^^

This appears to have broken due to #103, which split

import GHC.SourceGen.Name
    ( RdrNameStr, ModuleNameStr(unModuleNameStr), OccNameStr, unqual )

into

#if MIN_VERSION_ghc(9,0,0)
import GHC.SourceGen.Name (unqual)
#endif
#if MIN_VERSION_ghc(9,4,0)
import GHC.SourceGen.Name (RdrNameStr, ModuleNameStr(unModuleNameStr), OccNameStr)

However the usage of unqual at src/GHC/SourceGen/Module.hs:191 appears to be outside any #if, so I think GHC.SourceGen.Name needs to be imported unconditionally (at least unqual).

Or, if the intent was that GHC 9.0.0 is now the minimum supported version, the cabal file needs to be updated (and a revision pushed to Hackage) so that 0.4.4.0 isn't selected when building on older compilers.

Add pragmas

It would be nice to annotate definitions with INLINE or INLINABLE.

Support ghc 9.8

I started on doing the 9.8 uprev and got stuck with:

src/GHC/SourceGen/Module.hs:182:29: error: [GHC-83865]
    • Couldn't match type: (Maybe
                              (GHC.Parser.Annotation.LocatedP
                                 (GHC.Unit.Module.Warnings.WarningTxt GhcPs)),
                            EpAnn [GHC.Parser.Annotation.AddEpAnn])
                     with: EpAnn ann2
      Expected: EpAnn ann2
                -> GenLocated SrcSpanAnnA (IEWrappedName GhcPs) -> IE'
        Actual: Language.Haskell.Syntax.Extension.XIEThingAll GhcPs
                -> Language.Haskell.Syntax.ImpExp.LIEWrappedName GhcPs -> IE GhcPs
    • In the first argument of ‘withEpAnnNotUsed’, namely ‘IEThingAll’
      In the first argument of ‘(.)’, namely
        ‘withEpAnnNotUsed IEThingAll’
      In the expression: withEpAnnNotUsed IEThingAll . wrappedName
    |
182 | thingAll = withEpAnnNotUsed IEThingAll . wrappedName
    |                             ^^^^^^^^^^

There's a type-checker change which causes the following behavior mismatch between 9.8 and 9.6. The old versions works:

λ> z = (undefined :: GenLocated SrcSpanAnnA (IEWrappedName GhcPs))
λ> :t ($ EpAnnNotUsed) IEThingAll z
($ EpAnnNotUsed) IEThingAll z :: IE GhcPs

the new one fails:

λ> z = (undefined :: GenLocated SrcSpanAnnA (IEWrappedName GhcPs))
λ> :t ($ EpAnnNotUsed) IEThingAll z

    • Couldn't match type: (Maybe
                              (GHC.Parser.Annotation.LocatedP
                                 (GHC.Unit.Module.Warnings.WarningTxt GhcPs)),
                            EpAnn [GHC.Parser.Annotation.AddEpAnn])
                     with: EpAnn ann0
      Expected: EpAnn ann0
                -> GenLocated SrcSpanAnnA (IEWrappedName GhcPs) -> IE GhcPs
        Actual: XIEThingAll GhcPs
                -> Language.Haskell.Syntax.ImpExp.LIEWrappedName GhcPs -> IE GhcPs
    • In the first argument of ‘$ EpAnnNotUsed’, namely ‘IEThingAll’
      In the expression: ($ EpAnnNotUsed) IEThingAll z

So if somebody is well-versed in type families, they should suggest a fix.

Provide functions to build names from GHC names

When pulling names out of GHC, I often have Names or OccNames that I'd like to put into HsVars. Unfortunately var doesn't support this use case; and requires quite a mouthful: var . fromString . occNameString . nameOccName

funBinds doesn't support infix

The fixity of a binding is controlled by the mc_fixity parameter of the HsMatchContext on a Match. ghc-source-gen forces this parameter to be Prefix, but it would be nice to have the option to control this.

Support GHC 8.10

I'd like to get some help with supporting this new release. Some items that likely require attention:

  • Getting a working build plan
  • Adapting to GHC internal API changes (if any)

Support list comprehensions

There doesn't seem to be a way to construct a syntax tree for list comprehensions. Or am I missing something?

Remove ci/circleci setup

Our pull requests show:

ci/circleci: build-success Expected — Waiting for status to be reported

whereas the real CI has been using github actions for a while. I'm not sure where circleci is hiding, probably it's in project settings that aren't visible in the repo.

Consider requiring `OccNameStr` to initialize pattern vars

Currently pattern variables are initialized by var which takes a RdrNameStr. However, in practice a pattern variable can't be qualified, so an OccNameStr would be more appropriate.

As another example, haskell-src-exts has data Pat l = PVar l (Name l) | ... where Name corresponds to OccName/OccNameStr.

Add a cabal file to repo

Right now cabal users cannot use ghc-source-gen via a cabal.project file as a source-repository-package - since it insists on a cabal file. I'd be happy to provide a PR if its okay.

GHC 9.4 compatibility

If I override the bounds, I currently get this error, building with GHC 9.4:

Building library for ghc-source-gen-0.4.3.0..
[ 1 of 18] Compiling GHC.SourceGen.Pretty ( src/GHC/SourceGen/Pretty.hs, dist/build/GHC/SourceGen/Pretty.o, dist/build/GHC/SourceGen/Pretty.dyn_o )
[ 2 of 18] Compiling GHC.SourceGen.Syntax.Internal ( src/GHC/SourceGen/Syntax/Internal.hs, dist/build/GHC/SourceGen/Syntax/Internal.o, dist/build/GHC/SourceGen/Syntax/Internal.dyn_o )
[ 3 of 18] Compiling GHC.SourceGen.Name.Internal ( src/GHC/SourceGen/Name/Internal.hs, dist/build/GHC/SourceGen/Name/Internal.o, dist/build/GHC/SourceGen/Name/Internal.dyn_o )
[ 4 of 18] Compiling GHC.SourceGen.Name ( src/GHC/SourceGen/Name.hs, dist/build/GHC/SourceGen/Name.o, dist/build/GHC/SourceGen/Name.dyn_o )
[ 5 of 18] Compiling GHC.SourceGen.Lit.Internal ( src/GHC/SourceGen/Lit/Internal.hs, dist/build/GHC/SourceGen/Lit/Internal.o, dist/build/GHC/SourceGen/Lit/Internal.dyn_o )
[ 6 of 18] Compiling GHC.SourceGen.Pat.Internal ( src/GHC/SourceGen/Pat/Internal.hs, dist/build/GHC/SourceGen/Pat/Internal.o, dist/build/GHC/SourceGen/Pat/Internal.dyn_o )

src/GHC/SourceGen/Pat/Internal.hs:54:27: error:
    • Couldn't match type: Language.Haskell.Syntax.Extension.XRec
                             p0 (Pat p0)
                           -> Language.Haskell.Syntax.Extension.XRec
                                p0 (Language.Haskell.Syntax.Extension.HsToken ")")
                           -> Pat p0
                     with: Pat GHC.Hs.Extension.GhcPs
      Expected: GHC.Parser.Annotation.EpAnn ann0
                -> Language.Haskell.Syntax.Extension.XRec
                     p0 (Language.Haskell.Syntax.Extension.HsToken "(")
                -> Pat'
        Actual: Language.Haskell.Syntax.Extension.XParPat p0
                -> Language.Haskell.Syntax.Extension.LHsToken "(" p0
                -> Language.Haskell.Syntax.Pat.LPat p0
                -> Language.Haskell.Syntax.Extension.LHsToken ")" p0
                -> Pat p0
    • Probable cause: ‘ParPat’ is applied to too few arguments
      In the first argument of ‘withEpAnnNotUsed’, namely ‘ParPat’
      In the first argument of ‘(.)’, namely ‘withEpAnnNotUsed ParPat’
      In the expression: withEpAnnNotUsed ParPat . builtPat
   |
54 | parPat = withEpAnnNotUsed ParPat . builtPat
   |                           ^^^^^^

Expose builtSpan

When interoping with ghc-exactprint, getting unique source spans is crucial for connecting annotations to everything. I do this today by locating noSrcSpans, and generating unique spans for them. Without builtSpan being exposed, this approach doesn't work!

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.