Skip to content

Commit

Permalink
Implement Splice (#911)
Browse files Browse the repository at this point in the history
  • Loading branch information
toku-sa-n authored Jun 9, 2024
1 parent d4fc7c9 commit 9a9d953
Show file tree
Hide file tree
Showing 5 changed files with 69 additions and 55 deletions.
1 change: 1 addition & 0 deletions hindent.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -88,6 +88,7 @@ library
HIndent.Ast.Declaration.Warning
HIndent.Ast.Declaration.Warning.Collection
HIndent.Ast.Declaration.Warning.Kind
HIndent.Ast.Expression.Splice
HIndent.Ast.FileHeaderPragma
HIndent.Ast.FileHeaderPragma.Collection
HIndent.Ast.Import
Expand Down
4 changes: 3 additions & 1 deletion src/HIndent/Ast/Declaration/Splice.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@ module HIndent.Ast.Declaration.Splice
, mkSpliceDeclaration
) where

import HIndent.Ast.Expression.Splice
import HIndent.Ast.NodeComments
import qualified HIndent.GhcLibParserWrapper.GHC.Hs as GHC
import {-# SOURCE #-} HIndent.Pretty
Expand All @@ -15,7 +16,8 @@ instance CommentExtraction SpliceDeclaration where
nodeComments SpliceDeclaration {} = NodeComments [] [] []

instance Pretty SpliceDeclaration where
pretty' (SpliceDeclaration (GHC.SpliceDecl _ sp _)) = pretty sp
pretty' (SpliceDeclaration (GHC.SpliceDecl _ sp _)) =
pretty $ fmap mkSplice sp

mkSpliceDeclaration :: GHC.SpliceDecl GHC.GhcPs -> SpliceDeclaration
mkSpliceDeclaration = SpliceDeclaration
58 changes: 58 additions & 0 deletions src/HIndent/Ast/Expression/Splice.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,58 @@
{-# LANGUAGE CPP #-}

module HIndent.Ast.Expression.Splice
( Splice
, mkSplice
) where

import qualified GHC.Data.FastString as GHC
import qualified GHC.Types.Name.Reader as GHC
import HIndent.Ast.NodeComments
import qualified HIndent.GhcLibParserWrapper.GHC.Hs as GHC
import {-# SOURCE #-} HIndent.Pretty
import HIndent.Pretty.Combinators
import HIndent.Pretty.NodeComments
#if MIN_VERSION_ghc_lib_parser(9, 6, 1)
import qualified GHC.Types.SrcLoc as GHC
#endif
data Splice
= Typed (GHC.LHsExpr GHC.GhcPs)
| UntypedDollar (GHC.LHsExpr GHC.GhcPs)
| UntypedBare (GHC.LHsExpr GHC.GhcPs)
| QuasiQuote GHC.RdrName GHC.FastString

instance CommentExtraction Splice where
nodeComments Typed {} = NodeComments [] [] []
nodeComments UntypedDollar {} = NodeComments [] [] []
nodeComments UntypedBare {} = NodeComments [] [] []
nodeComments QuasiQuote {} = NodeComments [] [] []

instance Pretty Splice where
pretty' (Typed x) = string "$$" >> pretty x
pretty' (UntypedDollar x) = string "$" >> pretty x
pretty' (UntypedBare x) = pretty x
pretty' (QuasiQuote l r) =
brackets $ do
pretty l
wrapWithBars
$ indentedWithFixedLevel 0
$ sequence_
$ printers [] ""
$ GHC.unpackFS r
where
printers ps s [] = reverse (string (reverse s) : ps)
printers ps s ('\n':xs) =
printers (newline : string (reverse s) : ps) "" xs
printers ps s (x:xs) = printers ps (x : s) xs
#if MIN_VERSION_ghc_lib_parser(9, 6, 1)
mkSplice :: GHC.HsUntypedSplice GHC.GhcPs -> Splice
mkSplice (GHC.HsUntypedSpliceExpr _ x) = UntypedDollar x
mkSplice (GHC.HsQuasiQuote _ l (GHC.L _ r)) = QuasiQuote l r
#else
mkSplice :: GHC.HsSplice GHC.GhcPs -> Splice
mkSplice (GHC.HsTypedSplice _ _ _ body) = Typed body
mkSplice (GHC.HsUntypedSplice _ GHC.DollarSplice _ body) = UntypedDollar body
mkSplice (GHC.HsUntypedSplice _ GHC.BareSplice _ body) = UntypedBare body
mkSplice (GHC.HsQuasiQuote _ _ l _ r) = QuasiQuote l r
mkSplice GHC.HsSpliced {} = error "This AST node should never appear."
#endif
55 changes: 6 additions & 49 deletions src/HIndent/Pretty.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,7 @@ import HIndent.Ast.Declaration.Data.Body
import HIndent.Ast.Declaration.Data.Record.Field
import HIndent.Ast.Declaration.Family.Type
import HIndent.Ast.Declaration.Signature
import HIndent.Ast.Expression.Splice
import HIndent.Ast.NodeComments
import HIndent.Ast.Operator.Infix
import HIndent.Ast.Operator.Prefix
Expand Down Expand Up @@ -409,7 +410,7 @@ prettyHsExpr (GHC.ExprWithTySig _ e sig) = do
pretty $ GHC.hswc_body sig
prettyHsExpr (GHC.ArithSeq _ _ x) = pretty x
#if !MIN_VERSION_ghc_lib_parser(9,6,1)
prettyHsExpr (GHC.HsSpliceE _ x) = pretty x
prettyHsExpr (GHC.HsSpliceE _ x) = pretty $ mkSplice x
#endif
prettyHsExpr (GHC.HsProc _ pat x@(GHC.L _ (GHC.HsCmdTop _ (GHC.L _ (GHC.HsCmdDo _ xs))))) = do
spaced [string "proc", pretty pat, string "-> do"]
Expand Down Expand Up @@ -444,7 +445,7 @@ prettyHsExpr GHC.HsTcBracketOut {} = notGeneratedByParser
#endif
#if MIN_VERSION_ghc_lib_parser(9,6,1)
prettyHsExpr (GHC.HsTypedSplice _ x) = string "$$" >> pretty x
prettyHsExpr (GHC.HsUntypedSplice _ x) = pretty x
prettyHsExpr (GHC.HsUntypedSplice _ x) = pretty $ mkSplice x
#endif
instance Pretty LambdaCase where
pretty' (LambdaCase matches caseOrCases) = do
Expand Down Expand Up @@ -752,7 +753,7 @@ prettyHsType (GHC.HsIParamTy _ x ty) =
spaced [string "?" >> pretty x, string "::", pretty ty]
prettyHsType GHC.HsStarTy {} = string "*"
prettyHsType (GHC.HsKindSig _ t k) = spaced [pretty t, string "::", pretty k]
prettyHsType (GHC.HsSpliceTy _ sp) = pretty sp
prettyHsType (GHC.HsSpliceTy _ sp) = pretty $ mkSplice sp
prettyHsType GHC.HsDocTy {} = docNode
prettyHsType (GHC.HsBangTy _ pack x) = pretty pack >> pretty x
prettyHsType (GHC.HsRecTy _ xs) =
Expand Down Expand Up @@ -921,29 +922,7 @@ instance Pretty GHC.EpaCommentTok where
-- contains indent spaces for all lines except the first one.
indentedWithFixedLevel 0 $ lined $ fmap string xs
pretty' _ = docNode
#if !MIN_VERSION_ghc_lib_parser(9,6,1)
instance Pretty (GHC.HsSplice GHC.GhcPs) where
pretty' (GHC.HsTypedSplice _ _ _ body) = string "$$" >> pretty body
pretty' (GHC.HsUntypedSplice _ GHC.DollarSplice _ body) =
string "$" >> pretty body
pretty' (GHC.HsUntypedSplice _ GHC.BareSplice _ body) = pretty body
-- The body of a quasi-quote must not be changed by a formatter.
-- Changing it will modify the actual behavior of the code.
pretty' (GHC.HsQuasiQuote _ _ l _ r) =
brackets $ do
pretty l
wrapWithBars
$ indentedWithFixedLevel 0
$ sequence_
$ printers [] ""
$ GHC.unpackFS r
where
printers ps s [] = reverse (string (reverse s) : ps)
printers ps s ('\n':xs) =
printers (newline : string (reverse s) : ps) "" xs
printers ps s (x:xs) = printers ps (x : s) xs
pretty' GHC.HsSpliced {} = notGeneratedByParser
#endif

instance Pretty (GHC.Pat GHC.GhcPs) where
pretty' = prettyPat

Expand Down Expand Up @@ -991,7 +970,7 @@ prettyPat GHC.ConPat {..} =
unlessSpecialOp (GHC.unLoc pat_con) space
pretty b
prettyPat (GHC.ViewPat _ l r) = spaced [pretty l, string "->", pretty r]
prettyPat (GHC.SplicePat _ x) = pretty x
prettyPat (GHC.SplicePat _ x) = pretty $ mkSplice x
prettyPat (GHC.LitPat _ x) = pretty x
prettyPat (GHC.NPat _ x _ _) = pretty x
prettyPat (GHC.NPlusKPat _ n k _ _ _) = pretty n >> string "+" >> pretty k
Expand Down Expand Up @@ -1639,28 +1618,6 @@ instance Pretty GHC.SrcStrictness where
#if MIN_VERSION_ghc_lib_parser(9,6,1)
instance Pretty GHC.FieldLabelString where
pretty' = output

instance Pretty (GHC.HsUntypedSplice GHC.GhcPs) where
pretty' (GHC.HsUntypedSpliceExpr _ x) = string "$" >> pretty x
-- The body of a quasi-quote must not be changed by a formatter.
-- Changing it will modify the actual behavior of the code.
--
-- TODO: Remove duplicated code
pretty' (GHC.HsQuasiQuote _ l r) =
brackets $ do
pretty l
printCommentsAnd
r
(wrapWithBars
. indentedWithFixedLevel 0
. sequence_
. printers [] ""
. GHC.unpackFS)
where
printers ps s [] = reverse (string (reverse s) : ps)
printers ps s ('\n':xs) =
printers (newline : string (reverse s) : ps) "" xs
printers ps s (x:xs) = printers ps (x : s) xs
#endif
-- | Marks an AST node as never appearing in an AST.
--
Expand Down
6 changes: 1 addition & 5 deletions src/HIndent/Pretty.hs-boot
Original file line number Diff line number Diff line change
Expand Up @@ -92,11 +92,7 @@ instance Pretty
(GHC.GenLocated GHC.SrcSpanAnnA (GHC.HsType GHC.GhcPs)))
#endif
instance Pretty (GHC.HsExpr GHC.GhcPs)
#if MIN_VERSION_ghc_lib_parser(9, 6, 1)
instance Pretty (GHC.HsUntypedSplice GHC.GhcPs)
#else
instance Pretty (GHC.HsSplice GHC.GhcPs)
#endif

instance Pretty (GHC.FieldOcc GHC.GhcPs)

instance Pretty GHC.OccName
Expand Down

0 comments on commit 9a9d953

Please sign in to comment.