diff --git a/Cabal/Cabal.cabal b/Cabal/Cabal.cabal
index ef407d8ec91828d90497dea3d6746aa134d5ab50..1a90d9fa41f4c0d8b03f9eb1ad0dd6c82c1f905e 100644
--- a/Cabal/Cabal.cabal
+++ b/Cabal/Cabal.cabal
@@ -494,8 +494,8 @@ library
     Distribution.Types.GivenComponent
     Distribution.Types.PackageVersionConstraint
     Distribution.Utils.CharSet
-    Distribution.Utils.Regex
     Distribution.Utils.Generic
+    Distribution.Utils.GrammarRegex
     Distribution.Utils.NubList
     Distribution.Utils.ShortText
     Distribution.Utils.Progress
diff --git a/Cabal/Distribution/FieldGrammar/Described.hs b/Cabal/Distribution/FieldGrammar/Described.hs
index b107f288342e35a4e25175f058647efb9e63270e..8193be93bbaa2b1367a8fd4550aca2f453671010 100644
--- a/Cabal/Distribution/FieldGrammar/Described.hs
+++ b/Cabal/Distribution/FieldGrammar/Described.hs
@@ -4,7 +4,7 @@ module Distribution.FieldGrammar.Described (
     Described (..),
     describeDoc,
     -- * Regular expressions
-    Regex (..),
+    GrammarRegex (..),
     reEps,
     reChar,
     reChars,
@@ -38,7 +38,7 @@ import Prelude ()
 import Distribution.Parsec (Parsec)
 import Distribution.Pretty (Pretty)
 
-import Distribution.Utils.Regex
+import Distribution.Utils.GrammarRegex
 
 import qualified Distribution.Utils.CharSet as CS
 import qualified Text.PrettyPrint           as PP
@@ -46,7 +46,7 @@ import qualified Text.PrettyPrint           as PP
 -- | Class describing the pretty/parsec format of a.
 class (Pretty a, Parsec a) => Described a where
     -- | A pretty document of "regex" describing the field format
-    describe :: proxy a -> Regex void
+    describe :: proxy a -> GrammarRegex void
 
 -- | Pretty-print description.
 --
@@ -66,20 +66,20 @@ instance Described a => Described (Identity a) where
 -- Lists
 ------------------------------------------------------------------------------
 
-reSpacedList :: Regex a -> Regex a
+reSpacedList :: GrammarRegex a -> GrammarRegex a
 reSpacedList = REMunch RESpaces1
 
-reCommaList :: Regex a -> Regex a
+reCommaList :: GrammarRegex a -> GrammarRegex a
 reCommaList = RECommaList
 
-reOptCommaList :: Regex a -> Regex a
+reOptCommaList :: GrammarRegex a -> GrammarRegex a
 reOptCommaList = REOptCommaList
 
 -------------------------------------------------------------------------------
 -- Specific grammars
 -------------------------------------------------------------------------------
 
-reHsString :: Regex a
+reHsString :: GrammarRegex a
 reHsString = RENamed "hs-string" impl  where
     impl = reChar '"' <> REMunch reEps (REUnion [strChar, escChar]) <> reChar '"'
     strChar = RECharSet $ CS.difference CS.universe (CS.fromList "\"\\")
@@ -95,7 +95,7 @@ reHsString = RENamed "hs-string" impl  where
         , REUnion ["\\NUL", RENamed "ascii" "\\NUL"] -- TODO
         ]
 
-reUnqualComponent :: Regex a
+reUnqualComponent :: GrammarRegex a
 reUnqualComponent = RENamed "unqual-name" $
     REMunch1 (reChar '-') component
   where
@@ -108,13 +108,13 @@ reUnqualComponent = RENamed "unqual-name" $
         <> RECharSet CS.alpha
         <> REMunch reEps (RECharSet csAlphaNum)
 
-reDot :: Regex a
+reDot :: GrammarRegex a
 reDot = reChar '.'
 
-reComma :: Regex a
+reComma :: GrammarRegex a
 reComma = reChar ','
 
-reSpacedComma :: Regex a
+reSpacedComma :: GrammarRegex a
 reSpacedComma = RESpaces <> reComma <> RESpaces
 
 -------------------------------------------------------------------------------
diff --git a/Cabal/Distribution/ModuleName.hs b/Cabal/Distribution/ModuleName.hs
index 3c817f03a7231ec148722023b6ac1e765a4db64f..7ec9f04458c3ec0210ca0c25109de70e1edbab1a 100644
--- a/Cabal/Distribution/ModuleName.hs
+++ b/Cabal/Distribution/ModuleName.hs
@@ -85,7 +85,7 @@ parsecModuleName = state0 DList.empty where
 
 instance Described ModuleName where
     describe _ = REMunch1 (reChar '.') component where
-        component = RECharSet csUpper <> reMunchCS (csAlphaNum <> fromString "_'")
+        component = RECharSet csUpper <> REMunch reEps (REUnion [RECharSet csAlphaNum, RECharSet (fromString "_'")])
 
 validModuleChar :: Char -> Bool
 validModuleChar c = isAlphaNum c || c == '_' || c == '\''
diff --git a/Cabal/Distribution/Parsec/Newtypes.hs b/Cabal/Distribution/Parsec/Newtypes.hs
index fd6e9194da2090820d7d015f8b3550e1def9a71c..3c2a8f9d195d8741b23193423b270d1bd9f10e42 100644
--- a/Cabal/Distribution/Parsec/Newtypes.hs
+++ b/Cabal/Distribution/Parsec/Newtypes.hs
@@ -71,7 +71,7 @@ class    Sep sep  where
 
     parseSep :: CabalParsing m => Proxy sep -> m a -> m [a]
 
-    describeSep :: Proxy sep -> Regex a -> Regex a
+    describeSep :: Proxy sep -> GrammarRegex a -> GrammarRegex a
 
 instance Sep CommaVCat where
     prettySep  _ = vcat . punctuate comma
diff --git a/Cabal/Distribution/Utils/Regex.hs b/Cabal/Distribution/Utils/GrammarRegex.hs
similarity index 78%
rename from Cabal/Distribution/Utils/Regex.hs
rename to Cabal/Distribution/Utils/GrammarRegex.hs
index 11e6c9c87841a816e2c12c2e63828db8bcfa8409..02b262ab93cddfdedba5a7f982fc657b49dce82b 100644
--- a/Cabal/Distribution/Utils/Regex.hs
+++ b/Cabal/Distribution/Utils/GrammarRegex.hs
@@ -3,9 +3,9 @@
 {-# LANGUAGE DeriveTraversable   #-}
 {-# LANGUAGE OverloadedStrings   #-}
 {-# LANGUAGE ScopedTypeVariables #-}
-module Distribution.Utils.Regex (
+module Distribution.Utils.GrammarRegex (
     -- * Regular expressions
-    Regex (..),
+    GrammarRegex (..),
     reEps,
     reChar,
     reChars,
@@ -26,31 +26,31 @@ import qualified Distribution.Utils.CharSet as CS
 import qualified Text.PrettyPrint           as PP
 
 -------------------------------------------------------------------------------
--- Regex
+-- GrammarRegex
 -------------------------------------------------------------------------------
 
 -- | Recursive regular expressions tuned for 'Described' use-case.
-data Regex a
-    = REAppend  [Regex a]                 -- ^ append @ab@
-    | REUnion   [Regex a]                 -- ^ union @a|b@
+data GrammarRegex a
+    = REAppend  [GrammarRegex a]          -- ^ append @ab@
+    | REUnion   [GrammarRegex a]          -- ^ union @a|b@
 
     -- repetition
-    | REMunch   (Regex a) (Regex a)       -- ^ star @a*@, with a separator
-    | REMunch1  (Regex a) (Regex a)       -- ^ plus @a+@, with a separator
-    | REMunchR Int (Regex a) (Regex a)    -- ^ 1-n, with a separator
-    | REOpt     (Regex a)                 -- ^ optional @r?@
+    | REMunch   (GrammarRegex a) (GrammarRegex a)       -- ^ star @a*@, with a separator
+    | REMunch1  (GrammarRegex a) (GrammarRegex a)       -- ^ plus @a+@, with a separator
+    | REMunchR Int (GrammarRegex a) (GrammarRegex a)    -- ^ 1-n, with a separator
+    | REOpt     (GrammarRegex a)                        -- ^ optional @r?@
 
-    | REString  String                    -- ^ literal string @abcd@
-    | RECharSet CS.CharSet           -- ^ charset @[:alnum:]@
-    | REVar     a                         -- ^ variable
-    | RENamed   String (Regex a)          -- ^ named expression
-    | RERec     String (Regex (Maybe a))  -- ^ recursive expressions
+    | REString  String                           -- ^ literal string @abcd@
+    | RECharSet CS.CharSet                       -- ^ charset @[:alnum:]@
+    | REVar     a                                -- ^ variable
+    | RENamed   String (GrammarRegex a)          -- ^ named expression
+    | RERec     String (GrammarRegex (Maybe a))  -- ^ recursive expressions
 
     -- cabal syntax specifics
     | RESpaces                            -- ^ zero-or-more spaces
     | RESpaces1                           -- ^ one-or-more spaces
-    | RECommaList (Regex a)               -- ^ comma list (note, leading or trailing commas)
-    | REOptCommaList (Regex a)            -- ^ opt comma list
+    | RECommaList (GrammarRegex a)        -- ^ comma list (note, leading or trailing commas)
+    | REOptCommaList (GrammarRegex a)     -- ^ opt comma list
 
     | RETodo                              -- ^ unspecified
   deriving (Eq, Ord, Show, Functor, Foldable, Traversable)
@@ -59,15 +59,15 @@ data Regex a
 -- Instances
 -------------------------------------------------------------------------------
 
-instance IsString (Regex a)  where
+instance IsString (GrammarRegex a)  where
     fromString = REString
 
-instance Semigroup (Regex a) where
+instance Semigroup (GrammarRegex a) where
     x <> y = REAppend (unAppend x ++ unAppend y) where
         unAppend (REAppend rs) = rs
         unAppend r             = [r]
 
-instance Monoid (Regex a) where
+instance Monoid (GrammarRegex a) where
     mempty = REAppend []
     mappend = (<>)
 
@@ -75,29 +75,29 @@ instance Monoid (Regex a) where
 -- Smart constructors
 -------------------------------------------------------------------------------
 
-reEps :: Regex a
+reEps :: GrammarRegex a
 reEps = REAppend []
 
-reChar :: Char -> Regex a
+reChar :: Char -> GrammarRegex a
 reChar = RECharSet . CS.singleton
 
-reChars :: [Char] -> Regex a
+reChars :: [Char] -> GrammarRegex a
 reChars = RECharSet . CS.fromList
 
-reMunch1CS :: CS.CharSet -> Regex a
+reMunch1CS :: CS.CharSet -> GrammarRegex a
 reMunch1CS = REMunch1 reEps . RECharSet
 
-reMunchCS :: CS.CharSet -> Regex a
+reMunchCS :: CS.CharSet -> GrammarRegex a
 reMunchCS = REMunch reEps . RECharSet
 
 -------------------------------------------------------------------------------
 -- Variables
 -------------------------------------------------------------------------------
 
-reVar0 :: Regex (Maybe a)
+reVar0 :: GrammarRegex (Maybe a)
 reVar0 = REVar Nothing
 
-reVar1 :: Regex (Maybe (Maybe a))
+reVar1 :: GrammarRegex (Maybe (Maybe a))
 reVar1 = REVar (Just Nothing)
 
 -------------------------------------------------------------------------------
@@ -114,9 +114,9 @@ reVar1 = REVar (Just Nothing)
 -- >>> regexDoc $ REString "foo" <> REString "bar"
 -- \mathop{\mathord{``}\mathtt{foo}\mathord{"}}\mathop{\mathord{``}\mathtt{bar}\mathord{"}}
 --
-regexDoc :: Regex Void -> PP.Doc
+regexDoc :: GrammarRegex Void -> PP.Doc
 regexDoc = go 0 . vacuous where
-    go :: Int -> Regex PP.Doc -> PP.Doc
+    go :: Int -> GrammarRegex PP.Doc -> PP.Doc
     go _ (REAppend [])    = ""
     go d (REAppend rs)    = parensIf (d > 2) $ PP.hcat (map (go 2) rs)
     go d (REUnion [r])    = go d r
@@ -186,6 +186,7 @@ charsetDoc :: CS.CharSet -> PP.Doc
 charsetDoc acs
     | acs == CS.alpha    = terminalDoc "alpha"
     | acs == CS.alphanum = terminalDoc "alpha-num"
+    | acs == CS.upper    = terminalDoc "upper"
 charsetDoc acs = case CS.toIntervalList acs of
     []               -> "\\emptyset"
     [(x,y)] | x == y -> inquotes $ mathtt $ charDoc x
diff --git a/Cabal/doc/buildinfo-fields-reference.rst b/Cabal/doc/buildinfo-fields-reference.rst
index be0e1584124af569792e2b5a9525b16182a7c32c..f73b8f5216012cb1ef684eeb49b48af2e93b7179 100644
--- a/Cabal/doc/buildinfo-fields-reference.rst
+++ b/Cabal/doc/buildinfo-fields-reference.rst
@@ -143,7 +143,7 @@ module-name
     Haskell module name as recognized by Cabal parser.
 
     .. math::
-        \mathsf{\color{red}{TODO}}
+        {\left(\mathop{\mathit{upper}}{\left\{ \mathop{\mathit{alpha\text{-}num}}\mid[\mathop{\mathord{``}\mathtt{\text{'}}\mathord{"}}\mathop{\mathord{``}\mathtt{\text{_}}\mathord{"}}] \right\}}^\ast_{}\right)}^+_{\mathop{\mathord{``}\mathtt{\text{.}}\mathord{"}}}
 
 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.
@@ -190,14 +190,14 @@ autogen-modules
     * Documentation of :pkg-field:`autogen-modules`
 
     .. math::
-        \mathrm{commalist}\mathsf{\color{red}{TODO}}
+        \mathrm{commalist}\left({\left(\mathop{\mathit{upper}}{\left\{ \mathop{\mathit{alpha\text{-}num}}\mid[\mathop{\mathord{``}\mathtt{\text{'}}\mathord{"}}\mathop{\mathord{``}\mathtt{\text{_}}\mathord{"}}] \right\}}^\ast_{}\right)}^+_{\mathop{\mathord{``}\mathtt{\text{.}}\mathord{"}}}\right)
 
 build-depends
     * Monoidal field
     * Documentation of :pkg-field:`build-depends`
 
     .. math::
-        \mathrm{commalist}\left(\mathop{\mathit{pkg\text{-}name}}{\left(\circ\mathop{\mathord{``}\mathtt{\text{:}}\mathord{"}}\circ\left\{ \mathop{\mathit{unqual\text{-}name}}\mid\mathop{\mathord{``}\mathtt{\{}\mathord{"}}\circ\mathrm{commalist}\mathop{\mathit{unqual\text{-}name}}\circ\mathop{\mathord{``}\mathtt{\}}\mathord{"}} \right\}\right)}^?{\left(\circ\mathop{\mathit{version\text{-}range}}\right)}^?\right)
+        \mathrm{commalist}\left(\mathop{\mathit{pkg\text{-}name}}{\left(\mathop{\mathord{``}\mathtt{\text{:}}\mathord{"}}\left\{ \mathop{\mathit{unqual\text{-}name}}\mid\mathop{\mathord{``}\mathtt{\{}\mathord{"}}\circ{\mathop{\mathit{unqual\text{-}name}}}^\ast_{\left(\circ\mathop{\mathord{``}\mathtt{\text{,}}\mathord{"}}\circ\right)}\circ\mathop{\mathord{``}\mathtt{\}}\mathord{"}} \right\}\right)}^?{\left(\bullet\mathop{\mathit{version\text{-}range}}\right)}^?\right)
 
 build-tool-depends
     * Monoidal field
@@ -473,7 +473,7 @@ other-modules
     * Documentation of :pkg-field:`other-modules`
 
     .. math::
-        \mathrm{commalist}\mathsf{\color{red}{TODO}}
+        \mathrm{commalist}\left({\left(\mathop{\mathit{upper}}{\left\{ \mathop{\mathit{alpha\text{-}num}}\mid[\mathop{\mathord{``}\mathtt{\text{'}}\mathord{"}}\mathop{\mathord{``}\mathtt{\text{_}}\mathord{"}}] \right\}}^\ast_{}\right)}^+_{\mathop{\mathord{``}\mathtt{\text{.}}\mathord{"}}}\right)
 
 pkgconfig-depends
     * Monoidal field
@@ -488,7 +488,7 @@ virtual-modules
     * Documentation of :pkg-field:`virtual-modules`
 
     .. math::
-        \mathrm{commalist}\mathsf{\color{red}{TODO}}
+        \mathrm{commalist}\left({\left(\mathop{\mathit{upper}}{\left\{ \mathop{\mathit{alpha\text{-}num}}\mid[\mathop{\mathord{``}\mathtt{\text{'}}\mathord{"}}\mathop{\mathord{``}\mathtt{\text{_}}\mathord{"}}] \right\}}^\ast_{}\right)}^+_{\mathop{\mathord{``}\mathtt{\text{.}}\mathord{"}}}\right)
 
 
 Package description fields
@@ -511,7 +511,7 @@ build-type
 
 cabal-version
     * Optional field
-    * Default: ``-any``
+    * Default: ``>=1.0``
     * Documentation of :pkg-field:`cabal-version`
 
     .. math::
@@ -637,7 +637,7 @@ test-module
     * Documentation of :pkg-field:`test-module`
 
     .. math::
-        \mathsf{\color{red}{TODO}}
+        {\left(\mathop{\mathit{upper}}{\left\{ \mathop{\mathit{alpha\text{-}num}}\mid[\mathop{\mathord{``}\mathtt{\text{'}}\mathord{"}}\mathop{\mathord{``}\mathtt{\text{_}}\mathord{"}}] \right\}}^\ast_{}\right)}^+_{\mathop{\mathord{``}\mathtt{\text{.}}\mathord{"}}}
 
 type
     * Optional field
diff --git a/Cabal/tests/UnitTests/Distribution/Described.hs b/Cabal/tests/UnitTests/Distribution/Described.hs
index 657a671f336a77d13f10930afb9bc3de5dd92795..979e3aacd53a6dec6188bdf6da397f51deea7c3b 100644
--- a/Cabal/tests/UnitTests/Distribution/Described.hs
+++ b/Cabal/tests/UnitTests/Distribution/Described.hs
@@ -11,7 +11,7 @@ import Test.QuickCheck       (Arbitrary (..), Gen, Property, choose, counterexam
 import Test.Tasty            (TestTree, testGroup)
 import Test.Tasty.QuickCheck (testProperty)
 
-import Distribution.FieldGrammar.Described (Described (..), Regex (..), reComma, reSpacedComma, reSpacedList)
+import Distribution.FieldGrammar.Described (Described (..), GrammarRegex (..), reComma, reSpacedComma, reSpacedList)
 import Distribution.Parsec                 (eitherParsec)
 import Distribution.Pretty                 (prettyShow)
 
@@ -101,9 +101,9 @@ genInt lo hi = choose (lo, hi)
 -- Conversion
 -------------------------------------------------------------------------------
 
-convert :: Regex Void -> RE.RE Void
+convert :: GrammarRegex Void -> RE.RE Void
 convert = go id . vacuous where
-    go :: Ord b => (a -> b) -> Regex a -> RE.RE b
+    go :: Ord b => (a -> b) -> GrammarRegex a -> RE.RE b
     go f (REAppend rs)      = foldr (\r acc -> go f r <> acc) RE.Eps rs
     go f (REUnion rs)       = foldr (\r acc -> go f r RE.\/ acc) RE.Null rs
     go _ (RECharSet cs)     = RE.Ch (convertCS cs)
@@ -140,17 +140,17 @@ convert = go id . vacuous where
 
     go _ RETodo             = RE.Null
 
-expandedCommaList :: Regex a -> Regex a
+expandedCommaList :: GrammarRegex a -> GrammarRegex a
 expandedCommaList = REUnion . expandedCommaList'
 
-expandedCommaList' :: Regex a -> [Regex a]
+expandedCommaList' :: GrammarRegex a -> [GrammarRegex a]
 expandedCommaList' r =
     [ REMunch reSpacedComma r
     , reComma <> RESpaces <> REMunch1 reSpacedComma r
     , REMunch1 reSpacedComma r <> RESpaces <> reComma
     ]
 
-expandedOptCommaList :: Regex a -> Regex a
+expandedOptCommaList :: GrammarRegex a -> GrammarRegex a
 expandedOptCommaList r = REUnion $ reSpacedList r : expandedCommaList' r
 
 convertCS :: CS.CharSet -> RE.CharSet
diff --git a/buildinfo-reference-generator/src/Main.hs b/buildinfo-reference-generator/src/Main.hs
index 763dd0b9825dd3a0e5255188b45a388a41206e98..16e79e9707e8cfe909d4097425bdc1f26e47e536 100644
--- a/buildinfo-reference-generator/src/Main.hs
+++ b/buildinfo-reference-generator/src/Main.hs
@@ -25,7 +25,7 @@ import qualified Text.PrettyPrint as PP
 import qualified Zinza as Z
 
 import Distribution.FieldGrammar.Described
-import Distribution.Utils.Regex
+import Distribution.Utils.GrammarRegex
 
 import Distribution.ModuleName         (ModuleName)
 import Distribution.Types.Version      (Version)
@@ -78,7 +78,7 @@ main = do
           putStrLn "Usage: generator <tmpl>"
           exitFailure
 
-zproduction :: String -> Regex Void -> String -> ZProduction
+zproduction :: String -> GrammarRegex Void -> String -> ZProduction
 zproduction name re desc = ZProduction
     { zprodName        = name
     , zprodSyntax      = show (regexDoc re')
@@ -90,17 +90,17 @@ zproduction name re desc = ZProduction
         _           -> re
 
 -- also in UnitTests.Distribution.Described
-expandedCommaList :: Regex a -> Regex a
+expandedCommaList :: GrammarRegex a -> GrammarRegex a
 expandedCommaList = REUnion . expandedCommaList'
 
-expandedCommaList' :: Regex a -> [Regex a]
+expandedCommaList' :: GrammarRegex a -> [GrammarRegex a]
 expandedCommaList' r =
     [ REMunch reSpacedComma r
     , reComma <> RESpaces <> REMunch1 reSpacedComma r
     , REMunch1 reSpacedComma r <> RESpaces <> reComma
     ]
 
-expandedOptCommaList :: Regex a -> Regex a
+expandedOptCommaList :: GrammarRegex a -> GrammarRegex a
 expandedOptCommaList r = REUnion $ reSpacedList r : expandedCommaList' r
 
 -------------------------------------------------------------------------------
diff --git a/buildinfo-reference-generator/template.zinza b/buildinfo-reference-generator/template.zinza
index f1387af27ad4292f3e98cbcd1d97df9ae847fb10..6716b1da22b7ae48bead98c5bc5b64ae99243746 100644
--- a/buildinfo-reference-generator/template.zinza
+++ b/buildinfo-reference-generator/template.zinza
@@ -1,8 +1,7 @@
 .. _buildinfo-field-reference:
 
-==================================================
- BuildInfo field reference
-==================================================
+Field Syntax Reference
+======================
 
 Notation
 ---------------
diff --git a/cabal-install/Distribution/Client/Types/RepoName.hs b/cabal-install/Distribution/Client/Types/RepoName.hs
index 26eb66f999e9f53ec176b883f42796dbedf44a0c..753fdd6639a245508f5f213c2663551f6fa97d52 100644
--- a/cabal-install/Distribution/Client/Types/RepoName.hs
+++ b/cabal-install/Distribution/Client/Types/RepoName.hs
@@ -7,7 +7,7 @@ module Distribution.Client.Types.RepoName (
 import Distribution.Client.Compat.Prelude
 import Prelude ()
 
-import Distribution.FieldGrammar.Described (Described (..), Regex (..), csAlpha, csAlphaNum, reMunchCS)
+import Distribution.FieldGrammar.Described (Described (..), GrammarRegex (..), csAlpha, csAlphaNum, reMunchCS)
 import Distribution.Parsec                 (Parsec (..))
 import Distribution.Pretty                 (Pretty (..))
 
diff --git a/cabal-install/tests/UnitTests/Distribution/Client/Described.hs b/cabal-install/tests/UnitTests/Distribution/Client/Described.hs
index 3ebf9cf178c53ad261c352d3f44ff435742a4f38..21cd41c0eb28d82d4cfcb461ec605a4b82a02b81 100644
--- a/cabal-install/tests/UnitTests/Distribution/Client/Described.hs
+++ b/cabal-install/tests/UnitTests/Distribution/Client/Described.hs
@@ -11,7 +11,7 @@ import Test.QuickCheck       (Arbitrary (..), Gen, Property, choose, counterexam
 import Test.Tasty            (TestTree, testGroup)
 import Test.Tasty.QuickCheck (testProperty)
 
-import Distribution.FieldGrammar.Described (Described (..), Regex (..), reComma, reSpacedComma, reSpacedList)
+import Distribution.FieldGrammar.Described (Described (..), GrammarRegex (..), reComma, reSpacedComma, reSpacedList)
 import Distribution.Parsec                 (eitherParsec)
 import Distribution.Pretty                 (prettyShow)
 
@@ -97,9 +97,9 @@ genInt lo hi = choose (lo, hi)
 -- Conversion
 -------------------------------------------------------------------------------
 
-convert :: Regex Void -> RE.RE Void
+convert :: GrammarRegex Void -> RE.RE Void
 convert = go id . vacuous where
-    go :: Ord b => (a -> b) -> Regex a -> RE.RE b
+    go :: Ord b => (a -> b) -> GrammarRegex a -> RE.RE b
     go f (REAppend rs)      = foldr (\r acc -> go f r <> acc) RE.Eps rs
     go f (REUnion rs)       = foldr (\r acc -> go f r RE.\/ acc) RE.Null rs
     go _ (RECharSet cs)     = RE.Ch (convertCS cs)
@@ -136,17 +136,17 @@ convert = go id . vacuous where
 
     go _ RETodo             = RE.Null
 
-expandedCommaList :: Regex a -> Regex a
+expandedCommaList :: GrammarRegex a -> GrammarRegex a
 expandedCommaList = REUnion . expandedCommaList'
 
-expandedCommaList' :: Regex a -> [Regex a]
+expandedCommaList' :: GrammarRegex a -> [GrammarRegex a]
 expandedCommaList' r =
     [ REMunch reSpacedComma r
     , reComma <> RESpaces <> REMunch1 reSpacedComma r
     , REMunch1 reSpacedComma r <> RESpaces <> reComma
     ]
 
-expandedOptCommaList :: Regex a -> Regex a
+expandedOptCommaList :: GrammarRegex a -> GrammarRegex a
 expandedOptCommaList r = REUnion $ reSpacedList r : expandedCommaList' r
 
 convertCS :: CS.CharSet -> RE.CharSet