diff options
author | Vladislav Zavialov <vlad.z.4096@gmail.com> | 2022-06-23 11:50:37 +0300 |
---|---|---|
committer | Vladislav Zavialov <vlad.z.4096@gmail.com> | 2022-10-23 00:11:50 +0300 |
commit | 11fe42d89d37539bd90f31ca47547922b3fc84ae (patch) | |
tree | 52aaeb001808eeeafb4b7bad6d19d7d5e658581c /compiler/Language/Haskell/Syntax | |
parent | 1937016b7834338eef12be19caefc8e37a90cd29 (diff) | |
download | haskell-11fe42d89d37539bd90f31ca47547922b3fc84ae.tar.gz |
Class layout info (#19623)
Updates the haddock submodule.
Diffstat (limited to 'compiler/Language/Haskell/Syntax')
-rw-r--r-- | compiler/Language/Haskell/Syntax/Concrete.hs | 63 | ||||
-rw-r--r-- | compiler/Language/Haskell/Syntax/Decls.hs | 5 | ||||
-rw-r--r-- | compiler/Language/Haskell/Syntax/Expr.hs | 1 | ||||
-rw-r--r-- | compiler/Language/Haskell/Syntax/Extension.hs | 27 | ||||
-rw-r--r-- | compiler/Language/Haskell/Syntax/Pat.hs | 1 | ||||
-rw-r--r-- | compiler/Language/Haskell/Syntax/Type.hs | 1 |
6 files changed, 70 insertions, 28 deletions
diff --git a/compiler/Language/Haskell/Syntax/Concrete.hs b/compiler/Language/Haskell/Syntax/Concrete.hs new file mode 100644 index 0000000000..982eac3216 --- /dev/null +++ b/compiler/Language/Haskell/Syntax/Concrete.hs @@ -0,0 +1,63 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE KindSignatures #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE DeriveDataTypeable #-} + +-- | Bits of concrete syntax (tokens, layout). + +module Language.Haskell.Syntax.Concrete + ( LHsToken, LHsUniToken, + HsToken(HsTok), + HsUniToken(HsNormalTok, HsUnicodeTok), + LayoutInfo(ExplicitBraces, VirtualBraces, NoLayoutInfo) + ) where + +import GHC.Prelude +import GHC.TypeLits (Symbol, KnownSymbol) +import Data.Data +import Language.Haskell.Syntax.Extension + +type LHsToken tok p = XRec p (HsToken tok) +type LHsUniToken tok utok p = XRec p (HsUniToken tok utok) + +-- | A token stored in the syntax tree. For example, when parsing a +-- let-expression, we store @HsToken "let"@ and @HsToken "in"@. +-- The locations of those tokens can be used to faithfully reproduce +-- (exactprint) the original program text. +data HsToken (tok :: Symbol) = HsTok + +-- | With @UnicodeSyntax@, there might be multiple ways to write the same +-- token. For example an arrow could be either @->@ or @→@. This choice must be +-- recorded in order to exactprint such tokens, so instead of @HsToken "->"@ we +-- introduce @HsUniToken "->" "→"@. +-- +-- See also @IsUnicodeSyntax@ in @GHC.Parser.Annotation@; we do not use here to +-- avoid a dependency. +data HsUniToken (tok :: Symbol) (utok :: Symbol) = HsNormalTok | HsUnicodeTok + +deriving instance KnownSymbol tok => Data (HsToken tok) +deriving instance (KnownSymbol tok, KnownSymbol utok) => Data (HsUniToken tok utok) + +-- | Layout information for declarations. +data LayoutInfo pass = + + -- | Explicit braces written by the user. + -- + -- @ + -- class C a where { foo :: a; bar :: a } + -- @ + ExplicitBraces !(LHsToken "{" pass) !(LHsToken "}" pass) + | + -- | Virtual braces inserted by the layout algorithm. + -- + -- @ + -- class C a where + -- foo :: a + -- bar :: a + -- @ + VirtualBraces + !Int -- ^ Layout column (indentation level, begins at 1) + | + -- | Empty or compiler-generated blocks do not have layout information + -- associated with them. + NoLayoutInfo diff --git a/compiler/Language/Haskell/Syntax/Decls.hs b/compiler/Language/Haskell/Syntax/Decls.hs index af8c0bb1e9..012304edf4 100644 --- a/compiler/Language/Haskell/Syntax/Decls.hs +++ b/compiler/Language/Haskell/Syntax/Decls.hs @@ -97,8 +97,9 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Expr -- Because Expr imports Decls via HsBracket import Language.Haskell.Syntax.Binds -import Language.Haskell.Syntax.Type +import Language.Haskell.Syntax.Concrete import Language.Haskell.Syntax.Extension +import Language.Haskell.Syntax.Type import Language.Haskell.Syntax.Basic (Role) import GHC.Types.Basic (TopLevelFlag, OverlapMode, RuleName, Activation) @@ -457,6 +458,8 @@ data TyClDecl pass -- 'GHC.Parser.Annotation.AnnRarrow' -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | ClassDecl { tcdCExt :: XClassDecl pass, -- ^ Post renamer, FVs + tcdLayout :: !(LayoutInfo pass), -- ^ Explicit or virtual braces + -- See Note [Class LayoutInfo] tcdCtxt :: Maybe (LHsContext pass), -- ^ Context... tcdLName :: LIdP pass, -- ^ Name of the class tcdTyVars :: LHsQTyVars pass, -- ^ Class type variables diff --git a/compiler/Language/Haskell/Syntax/Expr.hs b/compiler/Language/Haskell/Syntax/Expr.hs index cc1504a9ea..5a22e35c74 100644 --- a/compiler/Language/Haskell/Syntax/Expr.hs +++ b/compiler/Language/Haskell/Syntax/Expr.hs @@ -26,6 +26,7 @@ import Language.Haskell.Syntax.Basic import Language.Haskell.Syntax.Decls import Language.Haskell.Syntax.Pat import Language.Haskell.Syntax.Lit +import Language.Haskell.Syntax.Concrete import Language.Haskell.Syntax.Extension import Language.Haskell.Syntax.Type import Language.Haskell.Syntax.Binds diff --git a/compiler/Language/Haskell/Syntax/Extension.hs b/compiler/Language/Haskell/Syntax/Extension.hs index 4bdb3ce3cb..9ad16c0cd7 100644 --- a/compiler/Language/Haskell/Syntax/Extension.hs +++ b/compiler/Language/Haskell/Syntax/Extension.hs @@ -5,7 +5,6 @@ {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE EmptyCase #-} {-# LANGUAGE EmptyDataDeriving #-} -{-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} @@ -22,8 +21,6 @@ module Language.Haskell.Syntax.Extension where -- This module captures the type families to precisely identify the extension -- points for GHC.Hs syntax -import GHC.TypeLits (Symbol, KnownSymbol) - #if MIN_VERSION_GLASGOW_HASKELL(9,3,0,0) import Data.Type.Equality (type (~)) #endif @@ -731,27 +728,3 @@ type family NoGhcTc (p :: Type) -- ===================================================================== -- End of Type family definitions -- ===================================================================== - - - --- ===================================================================== --- Token information - -type LHsToken tok p = XRec p (HsToken tok) - -data HsToken (tok :: Symbol) = HsTok - -deriving instance KnownSymbol tok => Data (HsToken tok) - -type LHsUniToken tok utok p = XRec p (HsUniToken tok utok) - --- With UnicodeSyntax, there might be multiple ways to write the same token. --- For example an arrow could be either "->" or "→". This choice must be --- recorded in order to exactprint such tokens, --- so instead of HsToken "->" we introduce HsUniToken "->" "→". --- --- See also IsUnicodeSyntax in GHC.Parser.Annotation; we do not use here to --- avoid a dependency. -data HsUniToken (tok :: Symbol) (utok :: Symbol) = HsNormalTok | HsUnicodeTok - -deriving instance (KnownSymbol tok, KnownSymbol utok) => Data (HsUniToken tok utok) diff --git a/compiler/Language/Haskell/Syntax/Pat.hs b/compiler/Language/Haskell/Syntax/Pat.hs index 95abde9ce0..66b9708bfe 100644 --- a/compiler/Language/Haskell/Syntax/Pat.hs +++ b/compiler/Language/Haskell/Syntax/Pat.hs @@ -36,6 +36,7 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Expr (SyntaxExpr, LHsExpr, HsUntyp -- friends: import Language.Haskell.Syntax.Basic import Language.Haskell.Syntax.Lit +import Language.Haskell.Syntax.Concrete import Language.Haskell.Syntax.Extension import Language.Haskell.Syntax.Type diff --git a/compiler/Language/Haskell/Syntax/Type.hs b/compiler/Language/Haskell/Syntax/Type.hs index 4cb8b6ee0f..24e2ceeecc 100644 --- a/compiler/Language/Haskell/Syntax/Type.hs +++ b/compiler/Language/Haskell/Syntax/Type.hs @@ -57,6 +57,7 @@ module Language.Haskell.Syntax.Type ( import {-# SOURCE #-} Language.Haskell.Syntax.Expr ( HsUntypedSplice ) +import Language.Haskell.Syntax.Concrete import Language.Haskell.Syntax.Extension import GHC.Types.Name.Reader ( RdrName ) |