diff --git a/Cabal-described/src/Distribution/Described/Extension.hs b/Cabal-described/src/Distribution/Described/Extension.hs index 623e091ada8..4c5c81e46ae 100644 --- a/Cabal-described/src/Distribution/Described/Extension.hs +++ b/Cabal-described/src/Distribution/Described/Extension.hs @@ -1,7 +1,8 @@ {-# LANGUAGE OverloadedStrings #-} {-# OPTIONS_GHC -Wno-orphans #-} module Distribution.Described.Extension - ( reKnownExtension + ( reEnableExtension + , reKnownExtension , reDisableExtension , reXs -- * Extension groups @@ -44,6 +45,9 @@ instance Described Extension where reXs :: [KnownExtension] -> GrammarRegex a reXs xs = REUnion (fromString . prettyShow <$> xs) +reEnableExtension :: GrammarRegex a +reEnableExtension = "enable-extension" + reKnownExtension :: GrammarRegex a reKnownExtension = REUnion [ RENamed "interactive-extension" $ reXs xGroupInteractive diff --git a/Cabal-syntax-docs/Cabal-syntax-docs.cabal b/Cabal-syntax-docs/Cabal-syntax-docs.cabal new file mode 100644 index 00000000000..1b4578c66de --- /dev/null +++ b/Cabal-syntax-docs/Cabal-syntax-docs.cabal @@ -0,0 +1,44 @@ +cabal-version: 2.2 +name: Cabal-syntax-docs +version: 0 + +library + default-language: Haskell2010 + hs-source-dirs: src + ghc-options: -Wall + build-depends: + , base >=4.11 && <4.20 + , Cabal + , Cabal-described + , containers + , pretty + , zinza ^>=0.2 + exposed-modules: Cabal.Syntax.Docs.ZFields + +executable gen-cabal-package-syntax-docs + default-language: Haskell2010 + hs-source-dirs: cabal-package + ghc-options: -Wall + main-is: Main.hs + build-depends: + , base >=4.11 && <4.20 + , Cabal + , Cabal-described + , Cabal-syntax-docs + , containers + , pretty + , zinza ^>=0.2 + +executable gen-ghc-syntax-docs + default-language: Haskell2010 + hs-source-dirs: ghc + ghc-options: -Wall + main-is: Main.hs + build-depends: + , base >=4.11 && <4.20 + , Cabal + , Cabal-described + , Cabal-syntax-docs + , containers + , pretty + , zinza ^>=0.2 diff --git a/Cabal-syntax-docs/cabal-package/Main.hs b/Cabal-syntax-docs/cabal-package/Main.hs new file mode 100644 index 00000000000..c8b2dea4226 --- /dev/null +++ b/Cabal-syntax-docs/cabal-package/Main.hs @@ -0,0 +1,84 @@ +{-# LANGUAGE DeriveGeneric #-} +module Main (main) where + +import Data.List (partition) +import Data.Proxy (Proxy (..)) +import GHC.Generics (Generic) +import System.Environment (getArgs) +import System.Exit (exitFailure) + +import Distribution.PackageDescription.FieldGrammar (buildInfoFieldGrammar, packageDescriptionFieldGrammar, testSuiteFieldGrammar) + +import qualified Zinza as Z + +import Distribution.Described +import Distribution.Described.Extension () +import Distribution.Utils.GrammarRegex + +import Distribution.ModuleName (ModuleName) +import Distribution.Types.Version (Version) +import Distribution.Types.VersionRange (VersionRange) +import Cabal.Syntax.Docs.ZFields + +main :: IO () +main = do + args <- getArgs + case args of + [tmpl] -> do + let (biGhc, biCabal) = partition isGhcBuildInfo $ fromReference buildInfoFieldGrammar + run <- Z.parseAndCompileTemplateIO tmpl + contents <- run $ Z + { zGhcBuildInfoFields = biGhc + , zCabalBuildInfoFields = biCabal + , zPackageDescriptionFields = fromReference packageDescriptionFieldGrammar + , zTestSuiteFields = fromReference $ testSuiteFieldGrammar // buildInfoFieldGrammar + , zProductions = + [ zproduction "hs-string" reHsString + "String as in Haskell; it's recommended to avoid using Haskell-specific escapes." + , zproduction "unqual-name" reUnqualComponent $ unwords + [ "Unqualified component names are used for package names, component names etc. but not flag names." + , "Unqualified component name consist of components separated by dash, each component is non-empty alphanumeric string, with at least one alphabetic character." + , "In other words, component may not look like a number." + ] + + , zproduction "module-name" (describe (Proxy :: Proxy ModuleName)) + "Haskell module name as recognized by Cabal parser." + , zproduction "version" (describe (Proxy :: Proxy Version)) + "Version is to first approximation numbers separated by dots, where leading zero is not allowed and each version digit is consists at most of nine characters." + , zproduction "version-range" (describe (Proxy :: Proxy VersionRange)) + "Version range syntax is recursive. Also note the set syntax added in ``cabal-version: 3.0``, set cannot be empty." + ] + , zSpaceList = show $ regexDoc $ + REMunch RESpaces1 (RENamed "element" RETodo) + , zCommaList = show $ regexDoc $ + expandedCommaList (RENamed "element" RETodo) + , zOptCommaList = show $ regexDoc $ + expandedOptCommaList (RENamed "element" RETodo) + + , zNull = null + , zNotNull = not . null + } + + putStrLn contents + _ -> do + putStrLn "Usage: generator " + exitFailure + +data Z = Z + { zGhcBuildInfoFields :: [ZField] + , zCabalBuildInfoFields :: [ZField] + , zPackageDescriptionFields :: [ZField] + , zTestSuiteFields :: [ZField] + , zProductions :: [ZProduction] + , zSpaceList :: String + , zCommaList :: String + , zOptCommaList :: String + , zNull :: String -> Bool + , zNotNull :: String -> Bool + } + deriving (Generic) + +instance Z.Zinza Z where + toType = Z.genericToTypeSFP + toValue = Z.genericToValueSFP + fromValue = Z.genericFromValueSFP diff --git a/buildinfo-reference-generator/template.zinza b/Cabal-syntax-docs/cabal-package/template.zinza similarity index 91% rename from buildinfo-reference-generator/template.zinza rename to Cabal-syntax-docs/cabal-package/template.zinza index 8ae6cffb52c..d2e7371df53 100644 --- a/buildinfo-reference-generator/template.zinza +++ b/Cabal-syntax-docs/cabal-package/template.zinza @@ -1,10 +1,24 @@ -.. _buildinfo-field-reference: +.. _cabal-package-syntax: -Field Syntax Reference -====================== +Cabal Package Syntax +==================== + +GHC syntax +---------- + +Some elements of cabal package syntax are controlled by GHC. As such these are +effectively strings passed on to GHC and that may be as far as Cabal will check +their syntax. See the :ref:`ghc-syntax` for these elements of GHC syntax +embedded within cabal package descriptions. + +- :ref:`ghc-enable-extension` +- :ref:`ghc-disable-extension` +{% for field in ghcBuildInfoFields %} +- :ref:`{{field.name}}` +{% endfor %} Notation ---------------- +-------- Field syntax is described as they are in the latest cabal file format version. @@ -142,7 +156,7 @@ In the syntax definitions below the following non-terminal symbols are used: Build info fields ----------------- -{% for field in buildInfoFields %} +{% for field in cabalBuildInfoFields %} {{ field.name }} * {{field.format}} {% if notNull field.default %} diff --git a/Cabal-syntax-docs/ghc/Main.hs b/Cabal-syntax-docs/ghc/Main.hs new file mode 100644 index 00000000000..a14173bdc4d --- /dev/null +++ b/Cabal-syntax-docs/ghc/Main.hs @@ -0,0 +1,106 @@ +{-# LANGUAGE DeriveGeneric #-} +module Main (main) where + +import GHC.Generics (Generic) +import System.Environment (getArgs) +import System.Exit (exitFailure) + +import Distribution.PackageDescription.FieldGrammar (buildInfoFieldGrammar) + +import qualified Zinza as Z + +import Distribution.Described +import Distribution.Described.Extension +import Distribution.Utils.GrammarRegex +import Cabal.Syntax.Docs.ZFields + +main :: IO () +main = do + args <- getArgs + case args of + [tmpl] -> do + let biGhc = filter isGhcBuildInfo $ fromReference buildInfoFieldGrammar + run <- Z.parseAndCompileTemplateIO tmpl + contents <- run $ Z + { zGhcBuildInfoFields = biGhc + , zProductions = + [ zproduction "disable-extension" reDisableExtension + "Disable a language extension by prepending the extension with \"No\"." + , zproduction "enable-extension" reKnownExtension + "All GHC language extensions known to cabal. There may be more and some of these may be on by default." + , zproduction "interactive-extension" (reXs xGroupInteractive) + "Language Extensions related to GHC interactive." + , zproduction "phase-extension" (reXs xGroupPhase) + "Language Extensions related to a particular GHC phase." + , zproduction "syntax-extension" (reXs xGroupSyntax) + "Syntax Language Extensions." + , zproduction "import-export-extension" (reXs xGroupImportExport) + "Import and Export Language Extensions." + , zproduction "type-extension" (reXs xGroupTypes) + "Language Extensions for Types." + , zproduction "record-extension" (reXs xGroupRecords) + "Record Language Extensions." + , zproduction "deriving-extension" (reXs xGroupDeriving) + "Language Extensions for deriving mechanisms." + , zproduction "pattern-extension" (reXs xGroupPatterns) + "Patterns Language Extensions." + , zproduction "classes-instances-extension" (reXs xGroupClassesInstances) + "Language Extensions for class and instance declarations." + , zproduction "literal-extension" (reXs xGroupLiterals) + "Literals Language Extensions." + , zproduction "constraint-extension" (reXs xGroupConstraints) + "Constraint Language Extensions." + , zproduction "type-signature-extension" (reXs xGroupTypeSignatures) + "Type Signature Language Extensions." + , zproduction "binding-generalisation-extension" (reXs xGroupBindingsGeneralisation) + "Language Extensions for bindings and generalisation " + , zproduction "template-haskell-extension" (reXs xGroupTemplates) + "Template Haskell Language Extensions." + , zproduction "bang-strict-extension" (reXs xGroupBangStrict) + "Bang pattern and Strict Haskell Language Extensions." + , zproduction "parallel-concurrent-extension" (reXs xGroupParallelConcurrent) + "Parallel and Concurrent Language Extensions." + , zproduction "unboxed-primitive-extension" (reXs xGroupUnboxedPrimitive) + "Unboxed types and Primitive operations Language Extensions." + , zproduction "foreign-extension" (reXs xGroupForeign) + "Foreign function interface (FFI) Language Extensions." + , zproduction "safe-extension" (reXs xGroupSafe) + "Safe Haskell Language Extensions." + , zproduction "miscellaneous-extension" (reXs xGroupMiscellaneous) + "Miscellaneous Language Extensions." + , zproduction "bugs-extension" (reXs xGroupBugs) + "Language Extensions related to GHC bugs and infelicities." + , zproduction "ungrouped-extension" (reXs xUngrouped) + "Language Extensions not belonging to other extension groups, includes undocumented extensions." + ] + , zSpaceList = show $ regexDoc $ + REMunch RESpaces1 (RENamed "element" RETodo) + , zCommaList = show $ regexDoc $ + expandedCommaList (RENamed "element" RETodo) + , zOptCommaList = show $ regexDoc $ + expandedOptCommaList (RENamed "element" RETodo) + + , zNull = null + , zNotNull = not . null + } + + putStrLn contents + _ -> do + putStrLn "Usage: generator " + exitFailure + +data Z = Z + { zGhcBuildInfoFields :: [ZField] + , zProductions :: [ZProduction] + , zSpaceList :: String + , zCommaList :: String + , zOptCommaList :: String + , zNull :: String -> Bool + , zNotNull :: String -> Bool + } + deriving (Generic) + +instance Z.Zinza Z where + toType = Z.genericToTypeSFP + toValue = Z.genericToValueSFP + fromValue = Z.genericFromValueSFP \ No newline at end of file diff --git a/Cabal-syntax-docs/ghc/template.zinza b/Cabal-syntax-docs/ghc/template.zinza new file mode 100644 index 00000000000..0272d5d99a3 --- /dev/null +++ b/Cabal-syntax-docs/ghc/template.zinza @@ -0,0 +1,63 @@ +.. _ghc-syntax: + +GHC Syntax Reference +==================== + +Language Extensions +------------------- + +The many GHC language extensions are divided into groups of extensions +corresponding to subsections of the GHC users' guide on language extensions. +Those of the :ref:`ungrouped-extension ` group are +undocumented in the GHC users' guide. + +{% for production in productions %} +.. _ghc-{{ production.name }}: + +{{ production.name }} + {{ production.description }} + + .. math:: + + {{ production.syntax }} + +{% endfor %} + +GHC build info fields +--------------------- + +These are cabal package build info fields that are more related to GHC, the +Haskell compiler, than they are to Cabal. + +{% for field in ghcBuildInfoFields %} +.. _ghc-{{ field.name }}: + +{{ field.name }} + * {{field.format}} +{% if notNull field.default %} + * Default: ``{{field.default}}`` +{% endif %} +{% if notNull field.availableSince %} + * Available since ``cabal-version: {{field.availableSince}}``. +{% endif %} +{% if notNull field.deprecatedSince.fst %} + * Deprecated since ``cabal-version: {{field.deprecatedSince.fst}}``: {{field.deprecatedSince.snd}} +{% endif %} +{% if notNull field.removedIn.fst %} + * Removed in ``cabal-version: {{field.removedIn.fst}}``: {{field.removedIn.snd}} +{% endif %} +{# We show documentation link only for non deprecated fields #} +{% if null field.deprecatedSince.fst %} +{% if null field.removedIn.fst %} + * Documentation of :pkg-field:`library:{{field.name}}` +{% endif %} +{% endif %} +{% if notNull field.syntax %} + + .. math:: + + {{field.syntax}} +{% endif %} + +{% endfor %} + diff --git a/Cabal-syntax-docs/src/Cabal/Syntax/Docs/ZFields.hs b/Cabal-syntax-docs/src/Cabal/Syntax/Docs/ZFields.hs new file mode 100644 index 00000000000..de2ca86e50c --- /dev/null +++ b/Cabal-syntax-docs/src/Cabal/Syntax/Docs/ZFields.hs @@ -0,0 +1,203 @@ +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE MultiParamTypeClasses #-} +module Cabal.Syntax.Docs.ZFields where + +import Data.Map.Strict (Map) + +import Data.Bifunctor (first) +import Data.Void (Void) +import Distribution.CabalSpecVersion (CabalSpecVersion, showCabalSpecVersion) +import Distribution.Compat.Newtype (pack') +import Distribution.FieldGrammar.Class (FieldGrammar (..)) +import Distribution.Fields.Field (FieldName) +import Distribution.Pretty (pretty) +import Distribution.Simple.Utils (fromUTF8BS) +import GHC.Generics (Generic) + +import qualified Data.Map.Strict as Map +import qualified Text.PrettyPrint as PP + +import qualified Zinza as Z + +import Distribution.Described +import Distribution.Described.Extension () +import Distribution.Utils.GrammarRegex + +ghcBuildInfoFields :: [String] +ghcBuildInfoFields = ["default-language", "other-languages", "default-extensions", "other-extensions", "extensions"] + +isGhcBuildInfo :: ZField -> Bool +isGhcBuildInfo = (`elem` ghcBuildInfoFields) . zfieldName + +zproduction :: String -> GrammarRegex Void -> String -> ZProduction +zproduction name re desc = ZProduction + { zprodName = name + , zprodSyntax = show (regexDoc re') + , zprodDescription = desc + } + where + re' = case re of + RENamed _ r -> r + _ -> re + +-- also in UnitTests.Distribution.Described +expandedCommaList :: GrammarRegex a -> GrammarRegex a +expandedCommaList = REUnion . expandedCommaList' + +expandedCommaList' :: GrammarRegex a -> [GrammarRegex a] +expandedCommaList' r = + [ REMunch reSpacedComma r + , reComma <> RESpaces <> REMunch1 reSpacedComma r + , REMunch1 reSpacedComma r <> RESpaces <> reComma + ] + +expandedOptCommaList :: GrammarRegex a -> GrammarRegex a +expandedOptCommaList r = REUnion $ reSpacedList r : expandedCommaList' r + +data ZField = ZField + { zfieldName :: String + , zfieldAvailableSince :: String + , zfieldDeprecatedSince :: (String, String) + , zfieldRemovedIn :: (String, String) + , zfieldFormat :: String + , zfieldDefault :: String + , zfieldSyntax :: String + } + deriving (Generic) + +instance Z.Zinza ZField where + toType = Z.genericToTypeSFP + toValue = Z.genericToValueSFP + fromValue = Z.genericFromValueSFP + +data ZProduction = ZProduction + { zprodName :: String + , zprodSyntax :: String + , zprodDescription :: String + } + deriving (Generic) + +instance Z.Zinza ZProduction where + toType = Z.genericToTypeSFP + toValue = Z.genericToValueSFP + fromValue = Z.genericFromValueSFP + +------------------------------------------------------------------------------- +-- From reference +------------------------------------------------------------------------------- + +-- TODO: produce ZField +fromReference :: Reference a a -> [ZField] +fromReference (Reference m) = + [ ZField + { zfieldName = fromUTF8BS n + , zfieldAvailableSince = maybe "" showCabalSpecVersion (fdAvailableSince desc) + , zfieldDeprecatedSince = maybe ("", "") (first showCabalSpecVersion) (fdDeprecatedSince desc) + , zfieldRemovedIn = maybe ("", "") (first showCabalSpecVersion) (fdRemovedIn desc) + , zfieldFormat = fmt + , zfieldDefault = def + , zfieldSyntax = syntax + } + | (n, desc) <- Map.toList m + , let (fmt, def, syntax) = fromFieldDesc' (fdDescription desc) + ] + +fromFieldDesc' :: FieldDesc' -> (String, String, String) +fromFieldDesc' (MonoidalFieldAla s) = ("Monoidal field", "", show s) +fromFieldDesc' (BooleanFieldDesc def) = ("Boolean field", show def, show $ describeDoc ([] :: [Bool])) +fromFieldDesc' (OptionalFieldAla s) = ("Optional field", "", show s) +fromFieldDesc' (OptionalFieldDefAla s def) = ("Optional field", show def, show s) +fromFieldDesc' FreeTextField = ("Free text field", "", "") +fromFieldDesc' (UniqueField s) = ("Required field", "", show s) + +------------------------------------------------------------------------------- +-- Reference +------------------------------------------------------------------------------- + +newtype Reference a b = Reference (Map FieldName FieldDesc) + deriving (Functor) + +referenceAvailableSince :: CabalSpecVersion -> Reference a b -> Reference a b +referenceAvailableSince v (Reference m) = + Reference (fmap (fieldDescAvailableSince v) m) + +referenceRemovedIn :: CabalSpecVersion -> String -> Reference a b -> Reference a b +referenceRemovedIn v desc (Reference m) = + Reference (fmap (fieldDescRemovedIn v desc) m) + +referenceDeprecatedSince :: CabalSpecVersion -> String -> Reference a b -> Reference a b +referenceDeprecatedSince v desc (Reference m) = + Reference (fmap (fieldDescDeprecatedSince v desc) m) + +(//) :: Reference a b -> Reference c d -> Reference a b +Reference ab // Reference cd = Reference $ Map.difference ab cd + +fieldDescAvailableSince :: CabalSpecVersion -> FieldDesc -> FieldDesc +fieldDescAvailableSince v d = d { fdAvailableSince = Just v } + +fieldDescRemovedIn :: CabalSpecVersion -> String -> FieldDesc -> FieldDesc +fieldDescRemovedIn v desc d = d { fdRemovedIn = Just (v, desc) } + +fieldDescDeprecatedSince :: CabalSpecVersion -> String -> FieldDesc -> FieldDesc +fieldDescDeprecatedSince v desc d = d { fdDeprecatedSince = Just (v, desc) } + +data FieldDesc = FieldDesc + { fdAvailableSince :: Maybe CabalSpecVersion + , fdRemovedIn :: Maybe (CabalSpecVersion, String) + , fdDeprecatedSince :: Maybe (CabalSpecVersion, String) + , fdDescription :: FieldDesc' + } + deriving Show + +reference :: FieldName -> FieldDesc' -> Reference a b +reference fn d = Reference $ Map.singleton fn $ FieldDesc Nothing Nothing Nothing d + +data FieldDesc' + = BooleanFieldDesc Bool + | UniqueField PP.Doc -- ^ not used in BuildInfo + | FreeTextField -- ^ not user in BuildInfo + | OptionalFieldAla PP.Doc + | OptionalFieldDefAla PP.Doc PP.Doc + | MonoidalFieldAla PP.Doc + deriving Show + +instance Applicative (Reference a) where + pure _ = Reference Map.empty + Reference f <*> Reference x = Reference (Map.union f x) + +instance FieldGrammar Described Reference where + blurFieldGrammar _ (Reference xs) = Reference xs + + uniqueFieldAla fn pack _l = + reference fn $ UniqueField (describeDoc pack) + + booleanFieldDef fn _l def = + reference fn $ BooleanFieldDesc def + + optionalFieldAla fn pack _l = + reference fn $ OptionalFieldAla (describeDoc pack) + + optionalFieldDefAla fn pack _l def = + reference fn $ OptionalFieldDefAla + (describeDoc pack) + (pretty $ pack' pack def) + + freeTextField fn _l = reference fn FreeTextField + + freeTextFieldDef fn _l = reference fn FreeTextField + freeTextFieldDefST fn _l = reference fn FreeTextField + + monoidalFieldAla fn pack _l = + reference fn (MonoidalFieldAla (describeDoc pack)) + + prefixedFields _pfx _l = Reference Map.empty + + knownField _fn = Reference Map.empty -- TODO + + -- hidden fields are hidden from the reference. + hiddenField _ = Reference Map.empty + + deprecatedSince = referenceDeprecatedSince + removedIn = referenceRemovedIn + availableSince v _ r = referenceAvailableSince v r \ No newline at end of file diff --git a/Makefile b/Makefile index cf670814edf..fe53fbfe710 100644 --- a/Makefile +++ b/Makefile @@ -60,13 +60,13 @@ $(TEMPLATE_PATHS) : templates/Paths_pkg.template.hs cabal-dev-scripts/src/GenPat # generated docs # Use cabal build before cabal run to avoid output of the build on stdout when running -doc/buildinfo-fields-reference.rst : \ +doc/%-syntax.rst : \ $(wildcard Cabal-syntax/src/*/*.hs Cabal-syntax/src/*/*/*.hs Cabal-syntax/src/*/*/*/*.hs) \ $(wildcard Cabal-described/src/Distribution/Described.hs Cabal-described/src/Distribution/Utils/*.hs) \ - buildinfo-reference-generator/src/Main.hs \ - buildinfo-reference-generator/template.zinza - cabal build --project-file=cabal.project.buildinfo buildinfo-reference-generator - cabal run --project-file=cabal.project.buildinfo buildinfo-reference-generator buildinfo-reference-generator/template.zinza | tee $@ + Cabal-syntax-docs/$*/Main.hs \ + Cabal-syntax-docs/$*/template.zinza + cabal build --project-file=cabal.project.docs gen-%-syntax-docs + cabal run --project-file=cabal.project.docs gen-%-syntax-docs Cabal-syntax-docs/$*/template.zinza | tee $@ git diff --exit-code $@ # analyse-imports @@ -212,7 +212,9 @@ bootstrap-jsons: $(BOOTSTRAP_GHC_VERSIONS:%=bootstrap-json-%) ############################################################################## .PHONY: users-guide -users-guide: +users-guide: \ + doc/ghc-syntax.rst \ + doc/cabal-package-syntax.rst $(MAKE) -C doc users-guide .PHONY: users-guide-requirements diff --git a/buildinfo-reference-generator/buildinfo-reference-generator.cabal b/buildinfo-reference-generator/buildinfo-reference-generator.cabal deleted file mode 100644 index 667e8346b63..00000000000 --- a/buildinfo-reference-generator/buildinfo-reference-generator.cabal +++ /dev/null @@ -1,16 +0,0 @@ -cabal-version: 2.2 -name: buildinfo-reference-generator -version: 0 - -executable buildinfo-reference-generator - default-language: Haskell2010 - hs-source-dirs: src - ghc-options: -Wall - main-is: Main.hs - build-depends: - , base >=4.11 && <4.20 - , Cabal - , Cabal-described - , containers - , pretty - , zinza ^>=0.2 diff --git a/buildinfo-reference-generator/src/Main.hs b/buildinfo-reference-generator/src/Main.hs deleted file mode 100644 index dd0f01c8883..00000000000 --- a/buildinfo-reference-generator/src/Main.hs +++ /dev/null @@ -1,299 +0,0 @@ -{-# LANGUAGE DeriveFunctor #-} -{-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE MultiParamTypeClasses #-} -module Main (main) where - -import Data.Map.Strict (Map) - -import Data.Bifunctor (first) -import Data.Proxy (Proxy (..)) -import Data.Void (Void) -import Distribution.CabalSpecVersion (CabalSpecVersion, showCabalSpecVersion) -import Distribution.Compat.Newtype (pack') -import Distribution.FieldGrammar.Class (FieldGrammar (..)) -import Distribution.Fields.Field (FieldName) -import Distribution.Pretty (pretty) -import Distribution.Simple.Utils (fromUTF8BS) -import GHC.Generics (Generic) -import System.Environment (getArgs) -import System.Exit (exitFailure) - -import Distribution.PackageDescription.FieldGrammar (buildInfoFieldGrammar, packageDescriptionFieldGrammar, testSuiteFieldGrammar) - -import qualified Data.Map.Strict as Map -import qualified Text.PrettyPrint as PP - -import qualified Zinza as Z - -import Distribution.Described -import Distribution.Described.Extension -import Distribution.Utils.GrammarRegex - -import Distribution.ModuleName (ModuleName) -import Distribution.Types.Version (Version) -import Distribution.Types.VersionRange (VersionRange) - -------------------------------------------------------------------------------- --- Main -------------------------------------------------------------------------------- - -main :: IO () -main = do - args <- getArgs - case args of - [tmpl] -> do - -- TODO: getArgs - run <- Z.parseAndCompileTemplateIO tmpl - contents <- run $ Z - { zBuildInfoFields = fromReference buildInfoFieldGrammar - , zPackageDescriptionFields = fromReference packageDescriptionFieldGrammar - , zTestSuiteFields = fromReference $ testSuiteFieldGrammar // buildInfoFieldGrammar - , zProductions = - [ zproduction "interactive-extension" (reXs xGroupInteractive) "Language Extensions related to GHC interactive." - , zproduction "phase-extension" (reXs xGroupPhase) "Language Extensions related to a particular GHC phase." - , zproduction "syntax-extension" (reXs xGroupSyntax) "Syntax Language Extensions." - , zproduction "import-export-extension" (reXs xGroupImportExport) "Import and Export Language Extensions." - , zproduction "type-extension" (reXs xGroupTypes) "Language Extensions for Types." - , zproduction "record-extension" (reXs xGroupRecords) "Record Language Extensions." - , zproduction "deriving-extension" (reXs xGroupDeriving) "Language Extensions for deriving mechanisms." - , zproduction "pattern-extension" (reXs xGroupPatterns) "Patterns Language Extensions." - , zproduction "classes-instances-extension" (reXs xGroupClassesInstances) "Language Extensions for class and instance declarations." - , zproduction "literal-extension" (reXs xGroupLiterals) "Literals Language Extensions." - , zproduction "constraint-extension" (reXs xGroupConstraints) "Constraint Language Extensions." - , zproduction "type-signature-extension" (reXs xGroupTypeSignatures) "Type Signature Language Extensions." - , zproduction "binding-generalisation-extension" (reXs xGroupBindingsGeneralisation) "Language Extensions for bindings and generalisation " - , zproduction "template-haskell-extension" (reXs xGroupTemplates) "Template Haskell Language Extensions." - , zproduction "bang-strict-extension" (reXs xGroupBangStrict) "Bang pattern and Strict Haskell Language Extensions." - , zproduction "parallel-concurrent-extension" (reXs xGroupParallelConcurrent) "Parallel and Concurrent Language Extensions." - , zproduction "unboxed-primitive-extension" (reXs xGroupUnboxedPrimitive) "Unboxed types and Primitive operations Language Extensions." - , zproduction "foreign-extension" (reXs xGroupForeign) "Foreign function interface (FFI) Language Extensions." - , zproduction "safe-extension" (reXs xGroupSafe) "Safe Haskell Language Extensions." - , zproduction "miscellaneous-extension" (reXs xGroupMiscellaneous) "Miscellaneous Language Extensions." - , zproduction "bugs-extension" (reXs xGroupBugs) "Language Extensions related to GHC bugs and infelicities." - , zproduction "ungrouped-extension" (reXs xUngrouped) "Language Extensions not belonging to other extension groups, includes undocumented extensions." - , zproduction "enable-extension" reKnownExtension "GHC Language Extensions, some of these may be on by default." - , zproduction "disable-extension" reDisableExtension "Disable a GHC Language Extension." - , zproduction "hs-string" reHsString - "String as in Haskell; it's recommended to avoid using Haskell-specific escapes." - , zproduction "unqual-name" reUnqualComponent $ unwords - [ "Unqualified component names are used for package names, component names etc. but not flag names." - , "Unqualified component name consist of components separated by dash, each component is non-empty alphanumeric string, with at least one alphabetic character." - , "In other words, component may not look like a number." - ] - - , zproduction "module-name" (describe (Proxy :: Proxy ModuleName)) - "Haskell module name as recognized by Cabal parser." - , zproduction "version" (describe (Proxy :: Proxy Version)) - "Version is to first approximation numbers separated by dots, where leading zero is not allowed and each version digit is consists at most of nine characters." - , zproduction "version-range" (describe (Proxy :: Proxy VersionRange)) - "Version range syntax is recursive. Also note the set syntax added in ``cabal-version: 3.0``, set cannot be empty." - ] - , zSpaceList = show $ regexDoc $ - REMunch RESpaces1 (RENamed "element" RETodo) - , zCommaList = show $ regexDoc $ - expandedCommaList (RENamed "element" RETodo) - , zOptCommaList = show $ regexDoc $ - expandedOptCommaList (RENamed "element" RETodo) - - , zNull = null - , zNotNull = not . null - } - - putStrLn contents - _ -> do - putStrLn "Usage: generator " - exitFailure - -zproduction :: String -> GrammarRegex Void -> String -> ZProduction -zproduction name re desc = ZProduction - { zprodName = name - , zprodSyntax = show (regexDoc re') - , zprodDescription = desc - } - where - re' = case re of - RENamed _ r -> r - _ -> re - --- also in UnitTests.Distribution.Described -expandedCommaList :: GrammarRegex a -> GrammarRegex a -expandedCommaList = REUnion . expandedCommaList' - -expandedCommaList' :: GrammarRegex a -> [GrammarRegex a] -expandedCommaList' r = - [ REMunch reSpacedComma r - , reComma <> RESpaces <> REMunch1 reSpacedComma r - , REMunch1 reSpacedComma r <> RESpaces <> reComma - ] - -expandedOptCommaList :: GrammarRegex a -> GrammarRegex a -expandedOptCommaList r = REUnion $ reSpacedList r : expandedCommaList' r - -------------------------------------------------------------------------------- --- Template Inputs -------------------------------------------------------------------------------- - -data Z = Z - { zBuildInfoFields :: [ZField] - , zPackageDescriptionFields :: [ZField] - , zTestSuiteFields :: [ZField] - , zProductions :: [ZProduction] - , zSpaceList :: String - , zCommaList :: String - , zOptCommaList :: String - , zNull :: String -> Bool - , zNotNull :: String -> Bool - } - deriving (Generic) - -data ZField = ZField - { zfieldName :: String - , zfieldAvailableSince :: String - , zfieldDeprecatedSince :: (String, String) - , zfieldRemovedIn :: (String, String) - , zfieldFormat :: String - , zfieldDefault :: String - , zfieldSyntax :: String - } - deriving (Generic) - -data ZProduction = ZProduction - { zprodName :: String - , zprodSyntax :: String - , zprodDescription :: String - } - deriving (Generic) - -instance Z.Zinza Z where - toType = Z.genericToTypeSFP - toValue = Z.genericToValueSFP - fromValue = Z.genericFromValueSFP - -instance Z.Zinza ZField where - toType = Z.genericToTypeSFP - toValue = Z.genericToValueSFP - fromValue = Z.genericFromValueSFP - -instance Z.Zinza ZProduction where - toType = Z.genericToTypeSFP - toValue = Z.genericToValueSFP - fromValue = Z.genericFromValueSFP - -------------------------------------------------------------------------------- --- From reference -------------------------------------------------------------------------------- - --- TODO: produce ZField -fromReference :: Reference a a -> [ZField] -fromReference (Reference m) = - [ ZField - { zfieldName = fromUTF8BS n - , zfieldAvailableSince = maybe "" showCabalSpecVersion (fdAvailableSince desc) - , zfieldDeprecatedSince = maybe ("", "") (first showCabalSpecVersion) (fdDeprecatedSince desc) - , zfieldRemovedIn = maybe ("", "") (first showCabalSpecVersion) (fdRemovedIn desc) - , zfieldFormat = fmt - , zfieldDefault = def - , zfieldSyntax = syntax - } - | (n, desc) <- Map.toList m - , let (fmt, def, syntax) = fromFieldDesc' (fdDescription desc) - ] - -fromFieldDesc' :: FieldDesc' -> (String, String, String) -fromFieldDesc' (MonoidalFieldAla s) = ("Monoidal field", "", show s) -fromFieldDesc' (BooleanFieldDesc def) = ("Boolean field", show def, show $ describeDoc ([] :: [Bool])) -fromFieldDesc' (OptionalFieldAla s) = ("Optional field", "", show s) -fromFieldDesc' (OptionalFieldDefAla s def) = ("Optional field", show def, show s) -fromFieldDesc' FreeTextField = ("Free text field", "", "") -fromFieldDesc' (UniqueField s) = ("Required field", "", show s) - -------------------------------------------------------------------------------- --- Reference -------------------------------------------------------------------------------- - -newtype Reference a b = Reference (Map FieldName FieldDesc) - deriving (Functor) - -referenceAvailableSince :: CabalSpecVersion -> Reference a b -> Reference a b -referenceAvailableSince v (Reference m) = - Reference (fmap (fieldDescAvailableSince v) m) - -referenceRemovedIn :: CabalSpecVersion -> String -> Reference a b -> Reference a b -referenceRemovedIn v desc (Reference m) = - Reference (fmap (fieldDescRemovedIn v desc) m) - -referenceDeprecatedSince :: CabalSpecVersion -> String -> Reference a b -> Reference a b -referenceDeprecatedSince v desc (Reference m) = - Reference (fmap (fieldDescDeprecatedSince v desc) m) - -(//) :: Reference a b -> Reference c d -> Reference a b -Reference ab // Reference cd = Reference $ Map.difference ab cd - -fieldDescAvailableSince :: CabalSpecVersion -> FieldDesc -> FieldDesc -fieldDescAvailableSince v d = d { fdAvailableSince = Just v } - -fieldDescRemovedIn :: CabalSpecVersion -> String -> FieldDesc -> FieldDesc -fieldDescRemovedIn v desc d = d { fdRemovedIn = Just (v, desc) } - -fieldDescDeprecatedSince :: CabalSpecVersion -> String -> FieldDesc -> FieldDesc -fieldDescDeprecatedSince v desc d = d { fdDeprecatedSince = Just (v, desc) } - -data FieldDesc = FieldDesc - { fdAvailableSince :: Maybe CabalSpecVersion - , fdRemovedIn :: Maybe (CabalSpecVersion, String) - , fdDeprecatedSince :: Maybe (CabalSpecVersion, String) - , fdDescription :: FieldDesc' - } - deriving Show - -reference :: FieldName -> FieldDesc' -> Reference a b -reference fn d = Reference $ Map.singleton fn $ FieldDesc Nothing Nothing Nothing d - -data FieldDesc' - = BooleanFieldDesc Bool - | UniqueField PP.Doc -- ^ not used in BuildInfo - | FreeTextField -- ^ not user in BuildInfo - | OptionalFieldAla PP.Doc - | OptionalFieldDefAla PP.Doc PP.Doc - | MonoidalFieldAla PP.Doc - deriving Show - -instance Applicative (Reference a) where - pure _ = Reference Map.empty - Reference f <*> Reference x = Reference (Map.union f x) - -instance FieldGrammar Described Reference where - blurFieldGrammar _ (Reference xs) = Reference xs - - uniqueFieldAla fn pack _l = - reference fn $ UniqueField (describeDoc pack) - - booleanFieldDef fn _l def = - reference fn $ BooleanFieldDesc def - - optionalFieldAla fn pack _l = - reference fn $ OptionalFieldAla (describeDoc pack) - - optionalFieldDefAla fn pack _l def = - reference fn $ OptionalFieldDefAla - (describeDoc pack) - (pretty $ pack' pack def) - - freeTextField fn _l = reference fn FreeTextField - - freeTextFieldDef fn _l = reference fn FreeTextField - freeTextFieldDefST fn _l = reference fn FreeTextField - - monoidalFieldAla fn pack _l = - reference fn (MonoidalFieldAla (describeDoc pack)) - - prefixedFields _pfx _l = Reference Map.empty - - knownField _fn = Reference Map.empty -- TODO - - -- hidden fields are hidden from the reference. - hiddenField _ = Reference Map.empty - - deprecatedSince = referenceDeprecatedSince - removedIn = referenceRemovedIn - availableSince v _ r = referenceAvailableSince v r diff --git a/cabal.project.buildinfo b/cabal.project.docs similarity index 63% rename from cabal.project.buildinfo rename to cabal.project.docs index 839f35c5805..d59cf4a3f16 100644 --- a/cabal.project.buildinfo +++ b/cabal.project.docs @@ -1,7 +1,7 @@ -packages: Cabal-syntax/ -packages: Cabal/ +packages: Cabal-syntax +packages: Cabal packages: Cabal-described -packages: buildinfo-reference-generator/ +packages: Cabal-syntax-docs tests: False optimization: False diff --git a/doc/buildinfo-fields-reference.rst b/doc/cabal-package-syntax.rst similarity index 67% rename from doc/buildinfo-fields-reference.rst rename to doc/cabal-package-syntax.rst index f34486cb7ce..7e3ba57ae2a 100644 --- a/doc/buildinfo-fields-reference.rst +++ b/doc/cabal-package-syntax.rst @@ -1,10 +1,26 @@ -.. _buildinfo-field-reference: +.. _cabal-package-syntax: -Field Syntax Reference -====================== +Cabal Package Syntax +==================== + +GHC syntax +---------- + +Some elements of cabal package syntax are controlled by GHC. As such these are +effectively strings passed on to GHC and that may be as far as Cabal will check +their syntax. See the :ref:`ghc-syntax` for these elements of GHC syntax +embedded within cabal package descriptions. + +- :ref:`ghc-enable-extension` +- :ref:`ghc-disable-extension` +- :ref:`default-extensions` +- :ref:`default-language` +- :ref:`extensions` +- :ref:`other-extensions` +- :ref:`other-languages` Notation ---------------- +-------- Field syntax is described as they are in the latest cabal file format version. @@ -129,174 +145,6 @@ Non-terminals In the syntax definitions below the following non-terminal symbols are used: -interactive-extension - Language Extensions related to GHC interactive. - - .. math:: - - \mathop{\mathord{``}\mathtt{ExtendedDefaultRules}\mathord{"}} - -phase-extension - Language Extensions related to a particular GHC phase. - - .. math:: - - \mathop{\mathord{``}\mathtt{CPP}\mathord{"}} - -syntax-extension - Syntax Language Extensions. - - .. math:: - - \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{UnicodeSyntax}\mathord{"}}\\\mathop{\mathord{``}\mathtt{MagicHash}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RecursiveDo}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ApplicativeDo}\mathord{"}}\\\mathop{\mathord{``}\mathtt{QualifiedDo}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ParallelListComp}\mathord{"}}\\\mathop{\mathord{``}\mathtt{TransformListComp}\mathord{"}}\\\mathop{\mathord{``}\mathtt{MonadComprehensions}\mathord{"}}\\\mathop{\mathord{``}\mathtt{OverloadedLists}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ImplicitPrelude}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RebindableSyntax}\mathord{"}}\\\mathop{\mathord{``}\mathtt{PostfixOperators}\mathord{"}}\\\mathop{\mathord{``}\mathtt{TupleSections}\mathord{"}}\\\mathop{\mathord{``}\mathtt{LambdaCase}\mathord{"}}\\\mathop{\mathord{``}\mathtt{EmptyCase}\mathord{"}}\\\mathop{\mathord{``}\mathtt{MultiWayIf}\mathord{"}}\\\mathop{\mathord{``}\mathtt{Arrows}\mathord{"}}\\\mathop{\mathord{``}\mathtt{LexicalNegation}\mathord{"}}\\\mathop{\mathord{``}\mathtt{BlockArguments}\mathord{"}}\end{gathered} \right\} - -import-export-extension - Import and Export Language Extensions. - - .. math:: - - \left\{ \mathop{\mathord{``}\mathtt{PackageImports}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{ExplicitNamespaces}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{ImportQualifiedPost}\mathord{"}} \right\} - -type-extension - Language Extensions for Types. - - .. math:: - - \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{EmptyDataDecls}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DatatypeContexts}\mathord{"}}\\\mathop{\mathord{``}\mathtt{TypeOperators}\mathord{"}}\\\mathop{\mathord{``}\mathtt{LiberalTypeSynonyms}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ExistentialQuantification}\mathord{"}}\\\mathop{\mathord{``}\mathtt{GADTSyntax}\mathord{"}}\\\mathop{\mathord{``}\mathtt{GADTs}\mathord{"}}\\\mathop{\mathord{``}\mathtt{TypeFamilies}\mathord{"}}\\\mathop{\mathord{``}\mathtt{TypeFamilyDependencies}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DataKinds}\mathord{"}}\\\mathop{\mathord{``}\mathtt{TypeData}\mathord{"}}\\\mathop{\mathord{``}\mathtt{TypeInType}\mathord{"}}\\\mathop{\mathord{``}\mathtt{PolyKinds}\mathord{"}}\\\mathop{\mathord{``}\mathtt{CUSKs}\mathord{"}}\\\mathop{\mathord{``}\mathtt{StandaloneKindSignatures}\mathord{"}}\\\mathop{\mathord{``}\mathtt{StarIsType}\mathord{"}}\\\mathop{\mathord{``}\mathtt{TypeApplications}\mathord{"}}\\\mathop{\mathord{``}\mathtt{TypeAbstractions}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RequiredTypeArguments}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RankNTypes}\mathord{"}}\\\mathop{\mathord{``}\mathtt{Rank2Types}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DeepSubsumption}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ImpredicativeTypes}\mathord{"}}\\\mathop{\mathord{``}\mathtt{LinearTypes}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RoleAnnotations}\mathord{"}}\end{gathered} \right\} - -record-extension - Record Language Extensions. - - .. math:: - - \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{TraditionalRecordSyntax}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DisambiguateRecordFields}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DuplicateRecordFields}\mathord{"}}\\\mathop{\mathord{``}\mathtt{FieldSelectors}\mathord{"}}\\\mathop{\mathord{``}\mathtt{NamedFieldPuns}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RecordWildCards}\mathord{"}}\\\mathop{\mathord{``}\mathtt{OverloadedRecordDot}\mathord{"}}\\\mathop{\mathord{``}\mathtt{OverloadedRecordUpdate}\mathord{"}}\end{gathered} \right\} - -deriving-extension - Language Extensions for deriving mechanisms. - - .. math:: - - \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{EmptyDataDeriving}\mathord{"}}\\\mathop{\mathord{``}\mathtt{StandaloneDeriving}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DeriveFoldable}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DeriveFunctor}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DeriveTraversable}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DeriveDataTypeable}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DeriveLift}\mathord{"}}\\\mathop{\mathord{``}\mathtt{GeneralizedNewtypeDeriving}\mathord{"}}\\\mathop{\mathord{``}\mathtt{GeneralisedNewtypeDeriving}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DeriveAnyClass}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DerivingStrategies}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DerivingVia}\mathord{"}}\end{gathered} \right\} - -pattern-extension - Patterns Language Extensions. - - .. math:: - - \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{PatternGuards}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ViewPatterns}\mathord{"}}\\\mathop{\mathord{``}\mathtt{NPlusKPatterns}\mathord{"}}\\\mathop{\mathord{``}\mathtt{PatternSynonyms}\mathord{"}}\end{gathered} \right\} - -classes-instances-extension - Language Extensions for class and instance declarations. - - .. math:: - - \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{MultiParamTypeClasses}\mathord{"}}\\\mathop{\mathord{``}\mathtt{UndecidableSuperClasses}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ConstrainedClassMethods}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DefaultSignatures}\mathord{"}}\\\mathop{\mathord{``}\mathtt{NullaryTypeClasses}\mathord{"}}\\\mathop{\mathord{``}\mathtt{FunctionalDependencies}\mathord{"}}\\\mathop{\mathord{``}\mathtt{TypeSynonymInstances}\mathord{"}}\\\mathop{\mathord{``}\mathtt{FlexibleInstances}\mathord{"}}\\\mathop{\mathord{``}\mathtt{UndecidableInstances}\mathord{"}}\\\mathop{\mathord{``}\mathtt{OverlappingInstances}\mathord{"}}\\\mathop{\mathord{``}\mathtt{IncoherentInstances}\mathord{"}}\\\mathop{\mathord{``}\mathtt{InstanceSigs}\mathord{"}}\end{gathered} \right\} - -literal-extension - Literals Language Extensions. - - .. math:: - - \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{NegativeLiterals}\mathord{"}}\\\mathop{\mathord{``}\mathtt{BinaryLiterals}\mathord{"}}\\\mathop{\mathord{``}\mathtt{HexFloatLiterals}\mathord{"}}\\\mathop{\mathord{``}\mathtt{NumDecimals}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ExtendedLiterals}\mathord{"}}\\\mathop{\mathord{``}\mathtt{NumericUnderscores}\mathord{"}}\\\mathop{\mathord{``}\mathtt{OverloadedStrings}\mathord{"}}\\\mathop{\mathord{``}\mathtt{OverloadedLabels}\mathord{"}}\end{gathered} \right\} - -constraint-extension - Constraint Language Extensions. - - .. math:: - - \left\{ \mathop{\mathord{``}\mathtt{FlexibleContexts}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{ConstraintKinds}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{QuantifiedConstraints}\mathord{"}} \right\} - -type-signature-extension - Type Signature Language Extensions. - - .. math:: - - \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{ExplicitForAll}\mathord{"}}\\\mathop{\mathord{``}\mathtt{AllowAmbiguousTypes}\mathord{"}}\\\mathop{\mathord{``}\mathtt{KindSignatures}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ScopedTypeVariables}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ImplicitParams}\mathord{"}}\\\mathop{\mathord{``}\mathtt{PartialTypeSignatures}\mathord{"}}\\\mathop{\mathord{``}\mathtt{NamedWildCards}\mathord{"}}\end{gathered} \right\} - -binding-generalisation-extension - Language Extensions for bindings and generalisation - - .. math:: - - \left\{ \mathop{\mathord{``}\mathtt{MonomorphismRestriction}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{MonoLocalBinds}\mathord{"}} \right\} - -template-haskell-extension - Template Haskell Language Extensions. - - .. math:: - - \left\{ \mathop{\mathord{``}\mathtt{TemplateHaskell}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{TemplateHaskellQuotes}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{QuasiQuotes}\mathord{"}} \right\} - -bang-strict-extension - Bang pattern and Strict Haskell Language Extensions. - - .. math:: - - \left\{ \mathop{\mathord{``}\mathtt{BangPatterns}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{StrictData}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{Strict}\mathord{"}} \right\} - -parallel-concurrent-extension - Parallel and Concurrent Language Extensions. - - .. math:: - - \mathop{\mathord{``}\mathtt{StaticPointers}\mathord{"}} - -unboxed-primitive-extension - Unboxed types and Primitive operations Language Extensions. - - .. math:: - - \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{UnboxedTuples}\mathord{"}}\\\mathop{\mathord{``}\mathtt{UnboxedSums}\mathord{"}}\\\mathop{\mathord{``}\mathtt{UnliftedNewtypes}\mathord{"}}\\\mathop{\mathord{``}\mathtt{UnliftedDatatypes}\mathord{"}}\end{gathered} \right\} - -foreign-extension - Foreign function interface (FFI) Language Extensions. - - .. math:: - - \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{ForeignFunctionInterface}\mathord{"}}\\\mathop{\mathord{``}\mathtt{UnliftedFFITypes}\mathord{"}}\\\mathop{\mathord{``}\mathtt{GHCForeignImportPrim}\mathord{"}}\\\mathop{\mathord{``}\mathtt{InterruptibleFFI}\mathord{"}}\\\mathop{\mathord{``}\mathtt{CApiFFI}\mathord{"}}\end{gathered} \right\} - -safe-extension - Safe Haskell Language Extensions. - - .. math:: - - \left\{ \mathop{\mathord{``}\mathtt{Safe}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{Trustworthy}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{Unsafe}\mathord{"}} \right\} - -miscellaneous-extension - Miscellaneous Language Extensions. - - .. math:: - - \mathop{\mathord{``}\mathtt{DeriveGeneric}\mathord{"}} - -bugs-extension - Language Extensions related to GHC bugs and infelicities. - - .. math:: - - \mathop{\mathord{``}\mathtt{NondecreasingIndentation}\mathord{"}} - -ungrouped-extension - Language Extensions not belonging to other extension groups, includes undocumented extensions. - - .. math:: - - \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{DoRec}\mathord{"}}\\\mathop{\mathord{``}\mathtt{PolymorphicComponents}\mathord{"}}\\\mathop{\mathord{``}\mathtt{PatternSignatures}\mathord{"}}\\\mathop{\mathord{``}\mathtt{Generics}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ExtensibleRecords}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RestrictedTypeSynonyms}\mathord{"}}\\\mathop{\mathord{``}\mathtt{HereDocuments}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RecordPuns}\mathord{"}}\\\mathop{\mathord{``}\mathtt{MonoPatBinds}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RelaxedPolyRec}\mathord{"}}\\\mathop{\mathord{``}\mathtt{NewQualifiedOperators}\mathord{"}}\\\mathop{\mathord{``}\mathtt{XmlSyntax}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RegularPatterns}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DoAndIfThenElse}\mathord{"}}\\\mathop{\mathord{``}\mathtt{SafeImports}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ParallelArrays}\mathord{"}}\\\mathop{\mathord{``}\mathtt{AutoDeriveTypeable}\mathord{"}}\\\mathop{\mathord{``}\mathtt{JavaScriptFFI}\mathord{"}}\\\mathop{\mathord{``}\mathtt{MonadFailDesugaring}\mathord{"}}\\\mathop{\mathord{``}\mathtt{AlternativeLayoutRule}\mathord{"}}\\\mathop{\mathord{``}\mathtt{AlternativeLayoutRuleTransitional}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RelaxedLayout}\mathord{"}}\end{gathered} \right\} - -enable-extension - GHC Language Extensions, some of these may be on by default. - - .. math:: - - \left\{ \begin{gathered}\mathop{\mathit{interactive\text{-}extension}}\\\mathop{\mathit{phase\text{-}extension}}\\\mathop{\mathit{syntax\text{-}extension}}\\\mathop{\mathit{import\text{-}export\text{-}extension}}\\\mathop{\mathit{type\text{-}extension}}\\\mathop{\mathit{record\text{-}extension}}\\\mathop{\mathit{deriving\text{-}extension}}\\\mathop{\mathit{pattern\text{-}extension}}\\\mathop{\mathit{classes\text{-}instances\text{-}extension}}\\\mathop{\mathit{literals\text{-}extension}}\\\mathop{\mathit{constraint\text{-}extension}}\\\mathop{\mathit{type\text{-}signature\text{-}extension}}\\\mathop{\mathit{binding\text{-}generalisation\text{-}extension}}\\\mathop{\mathit{template\text{-}haskell\text{-}extension}}\\\mathop{\mathit{bang\text{-}strict\text{-}extension}}\\\mathop{\mathit{parallel\text{-}concurrent\text{-}extension}}\\\mathop{\mathit{unboxed\text{-}primitive\text{-}extension}}\\\mathop{\mathit{foreign\text{-}extension}}\\\mathop{\mathit{safe\text{-}extension}}\\\mathop{\mathit{miscellaneous\text{-}extension}}\\\mathop{\mathit{bugs\text{-}extension}}\\\mathop{\mathit{ungrouped\text{-}extension}}\end{gathered} \right\} - -disable-extension - Disable a GHC Language Extension. - - .. math:: - - \mathop{\mathord{``}\mathtt{No}\mathord{"}}\mathop{\mathit{enable\text{-}extension}} - hs-string String as in Haskell; it's recommended to avoid using Haskell-specific escapes. @@ -466,33 +314,6 @@ cxx-sources \mathrm{commalist}\left\{ \mathop{\mathit{hs\text{-}string}}\mid{{[\mathop{\mathord{``}\mathtt{\ }\mathord{"}}\mathop{\mathord{``}\mathtt{\text{,}}\mathord{"}}]^c}}^+_{} \right\} -default-extensions - * Monoidal field - * Available since ``cabal-version: 1.10``. - * Documentation of :pkg-field:`library:default-extensions` - - .. math:: - - \mathrm{optcommalist}\left\{ \mathop{\mathit{enable\text{-}extension}}\mid\mathop{\mathit{disable\text{-}extension}} \right\} - -default-language - * Optional field - * Available since ``cabal-version: 1.10``. - * Documentation of :pkg-field:`library:default-language` - - .. math:: - - \left\{ \mathop{\mathord{``}\mathtt{GHC2021}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{Haskell2010}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{Haskell98}\mathord{"}} \right\} - -extensions - * Monoidal field - * Deprecated since ``cabal-version: 1.12``: Please use 'default-extensions' or 'other-extensions' fields. - * Removed in ``cabal-version: 3.0``: Please use 'default-extensions' or 'other-extensions' fields. - - .. math:: - - \mathrm{optcommalist}\left\{ \mathop{\mathit{enable\text{-}extension}}\mid\mathop{\mathit{disable\text{-}extension}} \right\} - extra-bundled-libraries * Monoidal field * Documentation of :pkg-field:`library:extra-bundled-libraries` @@ -699,23 +520,6 @@ mixins \mathrm{commalist}\left(\mathop{\mathit{package\text{-}name}}{\left(\mathop{\mathord{``}\mathtt{\text{:}}\mathord{"}}\mathop{\mathit{library\text{-}name}}\right)}^?{\left(\bullet\left\{ \mid\mathop{\mathord{``}\mathtt{hiding}\mathord{"}}\circ\mathop{\mathord{``}\mathtt{\text{(}}\mathord{"}}\circ{\mathop{\mathit{module\text{-}name}}}^\ast_{\left(\circ\mathop{\mathord{``}\mathtt{\text{,}}\mathord{"}}\circ\right)}\circ\mathop{\mathord{``}\mathtt{\text{)}}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{\text{(}}\mathord{"}}\circ{\left(\mathop{\mathit{module\text{-}name}}{\left(\bullet\mathop{\mathord{``}\mathtt{as}\mathord{"}}\bullet\mathop{\mathit{module\text{-}name}}\right)}^?\right)}^\ast_{\left(\circ\mathop{\mathord{``}\mathtt{\text{,}}\mathord{"}}\circ\right)}\circ\mathop{\mathord{``}\mathtt{\text{)}}\mathord{"}} \right\}{\left(\circ\mathop{\mathord{``}\mathtt{requires}\mathord{"}}\bullet\left\{ \mid\mathop{\mathord{``}\mathtt{hiding}\mathord{"}}\circ\mathop{\mathord{``}\mathtt{\text{(}}\mathord{"}}\circ{\mathop{\mathit{module\text{-}name}}}^\ast_{\left(\circ\mathop{\mathord{``}\mathtt{\text{,}}\mathord{"}}\circ\right)}\circ\mathop{\mathord{``}\mathtt{\text{)}}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{\text{(}}\mathord{"}}\circ{\left(\mathop{\mathit{module\text{-}name}}{\left(\bullet\mathop{\mathord{``}\mathtt{as}\mathord{"}}\bullet\mathop{\mathit{module\text{-}name}}\right)}^?\right)}^\ast_{\left(\circ\mathop{\mathord{``}\mathtt{\text{,}}\mathord{"}}\circ\right)}\circ\mathop{\mathord{``}\mathtt{\text{)}}\mathord{"}} \right\}\right)}^?\right)}^?\right) -other-extensions - * Monoidal field - * Documentation of :pkg-field:`library:other-extensions` - - .. math:: - - \mathrm{optcommalist}\left\{ \mathop{\mathit{enable\text{-}extension}}\mid\mathop{\mathit{disable\text{-}extension}} \right\} - -other-languages - * Monoidal field - * Available since ``cabal-version: 1.10``. - * Documentation of :pkg-field:`library:other-languages` - - .. math:: - - \mathrm{optcommalist}\left\{ \mathop{\mathord{``}\mathtt{GHC2021}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{Haskell2010}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{Haskell98}\mathord{"}} \right\} - other-modules * Monoidal field * Documentation of :pkg-field:`library:other-modules` diff --git a/doc/ghc-syntax.rst b/doc/ghc-syntax.rst new file mode 100644 index 00000000000..3e5601e1e39 --- /dev/null +++ b/doc/ghc-syntax.rst @@ -0,0 +1,292 @@ +.. _ghc-syntax: + +GHC Syntax Reference +==================== + +Language Extensions +------------------- + +The many GHC language extensions are divided into groups of extensions +corresponding to subsections of the GHC users' guide on language extensions. +Those of the :ref:`ungrouped-extension ` group are +undocumented in the GHC users' guide. + +.. _ghc-disable-extension: + +disable-extension + Disable a language extension by prepending the extension with "No". + + .. math:: + + \mathop{\mathord{``}\mathtt{No}\mathord{"}}\mathop{\mathit{enable\text{-}extension}} + +.. _ghc-enable-extension: + +enable-extension + All GHC language extensions known to cabal. There may be more and some of these may be on by default. + + .. math:: + + \left\{ \begin{gathered}\mathop{\mathit{interactive\text{-}extension}}\\\mathop{\mathit{phase\text{-}extension}}\\\mathop{\mathit{syntax\text{-}extension}}\\\mathop{\mathit{import\text{-}export\text{-}extension}}\\\mathop{\mathit{type\text{-}extension}}\\\mathop{\mathit{record\text{-}extension}}\\\mathop{\mathit{deriving\text{-}extension}}\\\mathop{\mathit{pattern\text{-}extension}}\\\mathop{\mathit{classes\text{-}instances\text{-}extension}}\\\mathop{\mathit{literals\text{-}extension}}\\\mathop{\mathit{constraint\text{-}extension}}\\\mathop{\mathit{type\text{-}signature\text{-}extension}}\\\mathop{\mathit{binding\text{-}generalisation\text{-}extension}}\\\mathop{\mathit{template\text{-}haskell\text{-}extension}}\\\mathop{\mathit{bang\text{-}strict\text{-}extension}}\\\mathop{\mathit{parallel\text{-}concurrent\text{-}extension}}\\\mathop{\mathit{unboxed\text{-}primitive\text{-}extension}}\\\mathop{\mathit{foreign\text{-}extension}}\\\mathop{\mathit{safe\text{-}extension}}\\\mathop{\mathit{miscellaneous\text{-}extension}}\\\mathop{\mathit{bugs\text{-}extension}}\\\mathop{\mathit{ungrouped\text{-}extension}}\end{gathered} \right\} + +.. _ghc-interactive-extension: + +interactive-extension + Language Extensions related to GHC interactive. + + .. math:: + + \mathop{\mathord{``}\mathtt{ExtendedDefaultRules}\mathord{"}} + +.. _ghc-phase-extension: + +phase-extension + Language Extensions related to a particular GHC phase. + + .. math:: + + \mathop{\mathord{``}\mathtt{CPP}\mathord{"}} + +.. _ghc-syntax-extension: + +syntax-extension + Syntax Language Extensions. + + .. math:: + + \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{UnicodeSyntax}\mathord{"}}\\\mathop{\mathord{``}\mathtt{MagicHash}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RecursiveDo}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ApplicativeDo}\mathord{"}}\\\mathop{\mathord{``}\mathtt{QualifiedDo}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ParallelListComp}\mathord{"}}\\\mathop{\mathord{``}\mathtt{TransformListComp}\mathord{"}}\\\mathop{\mathord{``}\mathtt{MonadComprehensions}\mathord{"}}\\\mathop{\mathord{``}\mathtt{OverloadedLists}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ImplicitPrelude}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RebindableSyntax}\mathord{"}}\\\mathop{\mathord{``}\mathtt{PostfixOperators}\mathord{"}}\\\mathop{\mathord{``}\mathtt{TupleSections}\mathord{"}}\\\mathop{\mathord{``}\mathtt{LambdaCase}\mathord{"}}\\\mathop{\mathord{``}\mathtt{EmptyCase}\mathord{"}}\\\mathop{\mathord{``}\mathtt{MultiWayIf}\mathord{"}}\\\mathop{\mathord{``}\mathtt{Arrows}\mathord{"}}\\\mathop{\mathord{``}\mathtt{LexicalNegation}\mathord{"}}\\\mathop{\mathord{``}\mathtt{BlockArguments}\mathord{"}}\end{gathered} \right\} + +.. _ghc-import-export-extension: + +import-export-extension + Import and Export Language Extensions. + + .. math:: + + \left\{ \mathop{\mathord{``}\mathtt{PackageImports}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{ExplicitNamespaces}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{ImportQualifiedPost}\mathord{"}} \right\} + +.. _ghc-type-extension: + +type-extension + Language Extensions for Types. + + .. math:: + + \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{EmptyDataDecls}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DatatypeContexts}\mathord{"}}\\\mathop{\mathord{``}\mathtt{TypeOperators}\mathord{"}}\\\mathop{\mathord{``}\mathtt{LiberalTypeSynonyms}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ExistentialQuantification}\mathord{"}}\\\mathop{\mathord{``}\mathtt{GADTSyntax}\mathord{"}}\\\mathop{\mathord{``}\mathtt{GADTs}\mathord{"}}\\\mathop{\mathord{``}\mathtt{TypeFamilies}\mathord{"}}\\\mathop{\mathord{``}\mathtt{TypeFamilyDependencies}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DataKinds}\mathord{"}}\\\mathop{\mathord{``}\mathtt{TypeData}\mathord{"}}\\\mathop{\mathord{``}\mathtt{TypeInType}\mathord{"}}\\\mathop{\mathord{``}\mathtt{PolyKinds}\mathord{"}}\\\mathop{\mathord{``}\mathtt{CUSKs}\mathord{"}}\\\mathop{\mathord{``}\mathtt{StandaloneKindSignatures}\mathord{"}}\\\mathop{\mathord{``}\mathtt{StarIsType}\mathord{"}}\\\mathop{\mathord{``}\mathtt{TypeApplications}\mathord{"}}\\\mathop{\mathord{``}\mathtt{TypeAbstractions}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RequiredTypeArguments}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RankNTypes}\mathord{"}}\\\mathop{\mathord{``}\mathtt{Rank2Types}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DeepSubsumption}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ImpredicativeTypes}\mathord{"}}\\\mathop{\mathord{``}\mathtt{LinearTypes}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RoleAnnotations}\mathord{"}}\end{gathered} \right\} + +.. _ghc-record-extension: + +record-extension + Record Language Extensions. + + .. math:: + + \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{TraditionalRecordSyntax}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DisambiguateRecordFields}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DuplicateRecordFields}\mathord{"}}\\\mathop{\mathord{``}\mathtt{FieldSelectors}\mathord{"}}\\\mathop{\mathord{``}\mathtt{NamedFieldPuns}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RecordWildCards}\mathord{"}}\\\mathop{\mathord{``}\mathtt{OverloadedRecordDot}\mathord{"}}\\\mathop{\mathord{``}\mathtt{OverloadedRecordUpdate}\mathord{"}}\end{gathered} \right\} + +.. _ghc-deriving-extension: + +deriving-extension + Language Extensions for deriving mechanisms. + + .. math:: + + \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{EmptyDataDeriving}\mathord{"}}\\\mathop{\mathord{``}\mathtt{StandaloneDeriving}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DeriveFoldable}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DeriveFunctor}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DeriveTraversable}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DeriveDataTypeable}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DeriveLift}\mathord{"}}\\\mathop{\mathord{``}\mathtt{GeneralizedNewtypeDeriving}\mathord{"}}\\\mathop{\mathord{``}\mathtt{GeneralisedNewtypeDeriving}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DeriveAnyClass}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DerivingStrategies}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DerivingVia}\mathord{"}}\end{gathered} \right\} + +.. _ghc-pattern-extension: + +pattern-extension + Patterns Language Extensions. + + .. math:: + + \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{PatternGuards}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ViewPatterns}\mathord{"}}\\\mathop{\mathord{``}\mathtt{NPlusKPatterns}\mathord{"}}\\\mathop{\mathord{``}\mathtt{PatternSynonyms}\mathord{"}}\end{gathered} \right\} + +.. _ghc-classes-instances-extension: + +classes-instances-extension + Language Extensions for class and instance declarations. + + .. math:: + + \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{MultiParamTypeClasses}\mathord{"}}\\\mathop{\mathord{``}\mathtt{UndecidableSuperClasses}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ConstrainedClassMethods}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DefaultSignatures}\mathord{"}}\\\mathop{\mathord{``}\mathtt{NullaryTypeClasses}\mathord{"}}\\\mathop{\mathord{``}\mathtt{FunctionalDependencies}\mathord{"}}\\\mathop{\mathord{``}\mathtt{TypeSynonymInstances}\mathord{"}}\\\mathop{\mathord{``}\mathtt{FlexibleInstances}\mathord{"}}\\\mathop{\mathord{``}\mathtt{UndecidableInstances}\mathord{"}}\\\mathop{\mathord{``}\mathtt{OverlappingInstances}\mathord{"}}\\\mathop{\mathord{``}\mathtt{IncoherentInstances}\mathord{"}}\\\mathop{\mathord{``}\mathtt{InstanceSigs}\mathord{"}}\end{gathered} \right\} + +.. _ghc-literal-extension: + +literal-extension + Literals Language Extensions. + + .. math:: + + \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{NegativeLiterals}\mathord{"}}\\\mathop{\mathord{``}\mathtt{BinaryLiterals}\mathord{"}}\\\mathop{\mathord{``}\mathtt{HexFloatLiterals}\mathord{"}}\\\mathop{\mathord{``}\mathtt{NumDecimals}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ExtendedLiterals}\mathord{"}}\\\mathop{\mathord{``}\mathtt{NumericUnderscores}\mathord{"}}\\\mathop{\mathord{``}\mathtt{OverloadedStrings}\mathord{"}}\\\mathop{\mathord{``}\mathtt{OverloadedLabels}\mathord{"}}\end{gathered} \right\} + +.. _ghc-constraint-extension: + +constraint-extension + Constraint Language Extensions. + + .. math:: + + \left\{ \mathop{\mathord{``}\mathtt{FlexibleContexts}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{ConstraintKinds}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{QuantifiedConstraints}\mathord{"}} \right\} + +.. _ghc-type-signature-extension: + +type-signature-extension + Type Signature Language Extensions. + + .. math:: + + \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{ExplicitForAll}\mathord{"}}\\\mathop{\mathord{``}\mathtt{AllowAmbiguousTypes}\mathord{"}}\\\mathop{\mathord{``}\mathtt{KindSignatures}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ScopedTypeVariables}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ImplicitParams}\mathord{"}}\\\mathop{\mathord{``}\mathtt{PartialTypeSignatures}\mathord{"}}\\\mathop{\mathord{``}\mathtt{NamedWildCards}\mathord{"}}\end{gathered} \right\} + +.. _ghc-binding-generalisation-extension: + +binding-generalisation-extension + Language Extensions for bindings and generalisation + + .. math:: + + \left\{ \mathop{\mathord{``}\mathtt{MonomorphismRestriction}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{MonoLocalBinds}\mathord{"}} \right\} + +.. _ghc-template-haskell-extension: + +template-haskell-extension + Template Haskell Language Extensions. + + .. math:: + + \left\{ \mathop{\mathord{``}\mathtt{TemplateHaskell}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{TemplateHaskellQuotes}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{QuasiQuotes}\mathord{"}} \right\} + +.. _ghc-bang-strict-extension: + +bang-strict-extension + Bang pattern and Strict Haskell Language Extensions. + + .. math:: + + \left\{ \mathop{\mathord{``}\mathtt{BangPatterns}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{StrictData}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{Strict}\mathord{"}} \right\} + +.. _ghc-parallel-concurrent-extension: + +parallel-concurrent-extension + Parallel and Concurrent Language Extensions. + + .. math:: + + \mathop{\mathord{``}\mathtt{StaticPointers}\mathord{"}} + +.. _ghc-unboxed-primitive-extension: + +unboxed-primitive-extension + Unboxed types and Primitive operations Language Extensions. + + .. math:: + + \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{UnboxedTuples}\mathord{"}}\\\mathop{\mathord{``}\mathtt{UnboxedSums}\mathord{"}}\\\mathop{\mathord{``}\mathtt{UnliftedNewtypes}\mathord{"}}\\\mathop{\mathord{``}\mathtt{UnliftedDatatypes}\mathord{"}}\end{gathered} \right\} + +.. _ghc-foreign-extension: + +foreign-extension + Foreign function interface (FFI) Language Extensions. + + .. math:: + + \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{ForeignFunctionInterface}\mathord{"}}\\\mathop{\mathord{``}\mathtt{UnliftedFFITypes}\mathord{"}}\\\mathop{\mathord{``}\mathtt{GHCForeignImportPrim}\mathord{"}}\\\mathop{\mathord{``}\mathtt{InterruptibleFFI}\mathord{"}}\\\mathop{\mathord{``}\mathtt{CApiFFI}\mathord{"}}\end{gathered} \right\} + +.. _ghc-safe-extension: + +safe-extension + Safe Haskell Language Extensions. + + .. math:: + + \left\{ \mathop{\mathord{``}\mathtt{Safe}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{Trustworthy}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{Unsafe}\mathord{"}} \right\} + +.. _ghc-miscellaneous-extension: + +miscellaneous-extension + Miscellaneous Language Extensions. + + .. math:: + + \mathop{\mathord{``}\mathtt{DeriveGeneric}\mathord{"}} + +.. _ghc-bugs-extension: + +bugs-extension + Language Extensions related to GHC bugs and infelicities. + + .. math:: + + \mathop{\mathord{``}\mathtt{NondecreasingIndentation}\mathord{"}} + +.. _ghc-ungrouped-extension: + +ungrouped-extension + Language Extensions not belonging to other extension groups, includes undocumented extensions. + + .. math:: + + \left\{ \begin{gathered}\mathop{\mathord{``}\mathtt{DoRec}\mathord{"}}\\\mathop{\mathord{``}\mathtt{PolymorphicComponents}\mathord{"}}\\\mathop{\mathord{``}\mathtt{PatternSignatures}\mathord{"}}\\\mathop{\mathord{``}\mathtt{Generics}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ExtensibleRecords}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RestrictedTypeSynonyms}\mathord{"}}\\\mathop{\mathord{``}\mathtt{HereDocuments}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RecordPuns}\mathord{"}}\\\mathop{\mathord{``}\mathtt{MonoPatBinds}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RelaxedPolyRec}\mathord{"}}\\\mathop{\mathord{``}\mathtt{NewQualifiedOperators}\mathord{"}}\\\mathop{\mathord{``}\mathtt{XmlSyntax}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RegularPatterns}\mathord{"}}\\\mathop{\mathord{``}\mathtt{DoAndIfThenElse}\mathord{"}}\\\mathop{\mathord{``}\mathtt{SafeImports}\mathord{"}}\\\mathop{\mathord{``}\mathtt{ParallelArrays}\mathord{"}}\\\mathop{\mathord{``}\mathtt{AutoDeriveTypeable}\mathord{"}}\\\mathop{\mathord{``}\mathtt{JavaScriptFFI}\mathord{"}}\\\mathop{\mathord{``}\mathtt{MonadFailDesugaring}\mathord{"}}\\\mathop{\mathord{``}\mathtt{AlternativeLayoutRule}\mathord{"}}\\\mathop{\mathord{``}\mathtt{AlternativeLayoutRuleTransitional}\mathord{"}}\\\mathop{\mathord{``}\mathtt{RelaxedLayout}\mathord{"}}\end{gathered} \right\} + + +GHC build info fields +--------------------- + +These are cabal package build info fields that are more related to GHC, the +Haskell compiler, than they are to Cabal. + +.. _ghc-default-extensions: + +default-extensions + * Monoidal field + * Available since ``cabal-version: 1.10``. + * Documentation of :pkg-field:`library:default-extensions` + + .. math:: + + \mathrm{optcommalist}\left\{ \mathop{\mathit{enable\text{-}extension}}\mid\mathop{\mathit{disable\text{-}extension}} \right\} + +.. _ghc-default-language: + +default-language + * Optional field + * Available since ``cabal-version: 1.10``. + * Documentation of :pkg-field:`library:default-language` + + .. math:: + + \left\{ \mathop{\mathord{``}\mathtt{GHC2021}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{Haskell2010}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{Haskell98}\mathord{"}} \right\} + +.. _ghc-extensions: + +extensions + * Monoidal field + * Deprecated since ``cabal-version: 1.12``: Please use 'default-extensions' or 'other-extensions' fields. + * Removed in ``cabal-version: 3.0``: Please use 'default-extensions' or 'other-extensions' fields. + + .. math:: + + \mathrm{optcommalist}\left\{ \mathop{\mathit{enable\text{-}extension}}\mid\mathop{\mathit{disable\text{-}extension}} \right\} + +.. _ghc-other-extensions: + +other-extensions + * Monoidal field + * Documentation of :pkg-field:`library:other-extensions` + + .. math:: + + \mathrm{optcommalist}\left\{ \mathop{\mathit{enable\text{-}extension}}\mid\mathop{\mathit{disable\text{-}extension}} \right\} + +.. _ghc-other-languages: + +other-languages + * Monoidal field + * Available since ``cabal-version: 1.10``. + * Documentation of :pkg-field:`library:other-languages` + + .. math:: + + \mathrm{optcommalist}\left\{ \mathop{\mathord{``}\mathtt{GHC2021}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{Haskell2010}\mathord{"}}\mid\mathop{\mathord{``}\mathtt{Haskell98}\mathord{"}} \right\} + + + diff --git a/doc/index.rst b/doc/index.rst index 69109a67685..210d2e07f0f 100644 --- a/doc/index.rst +++ b/doc/index.rst @@ -29,7 +29,6 @@ Welcome to the Cabal User Guide external-commands setup-commands file-format-changelog - buildinfo-fields-reference .. toctree:: :caption: Cabal Explanation @@ -39,3 +38,11 @@ Welcome to the Cabal User Guide cabal-context package-concepts cabal-interface-stability + +.. toctree:: + :caption: Syntax Reference + :numbered: + :maxdepth: 2 + + cabal-package-syntax + ghc-syntax