Brandon Chinn pushed to branch wip/T26503 at Glasgow Haskell Compiler / GHC

Commits:

4 changed files:

Changes:

  • compiler/GHC/Hs/Lit.hs
    ... ... @@ -38,6 +38,7 @@ import GHC.Utils.Panic (panic)
    38 38
     import GHC.Hs.Extension
    
    39 39
     import Language.Haskell.Syntax.Expr ( HsExpr )
    
    40 40
     import Language.Haskell.Syntax.Extension
    
    41
    +import Language.Haskell.Syntax.Module.Name (ModuleName)
    
    41 42
     import Language.Haskell.Syntax.Lit
    
    42 43
     
    
    43 44
     {-
    
    ... ... @@ -87,6 +88,7 @@ instance Eq HsLitTc where
    87 88
     data HsStringMeta = HsStringMeta
    
    88 89
       { strMetaSourceText :: SourceText
    
    89 90
       , strMetaMultiline  :: Bool
    
    91
    +  , strMetaQualified  :: Maybe ModuleName
    
    90 92
       }
    
    91 93
       deriving (Data)
    
    92 94
     
    

  • compiler/GHC/Parser.y
    ... ... @@ -4148,6 +4148,17 @@ literal :: { Located (HsLit GhcPs) }
    4148 4148
                                                         $ getPRIMSTRING $1 }
    
    4149 4149
             | PRIMFLOAT         { sL1 $1 $ HsFloatPrim  noExtField $ getPRIMFLOAT $1 }
    
    4150 4150
             | PRIMDOUBLE        { sL1 $1 $ HsDoublePrim noExtField $ getPRIMDOUBLE $1 }
    
    4151
    +        | modid '.' STRING          { hintQualifiedStrings *>
    
    4152
    +                                      sLL $1 $2
    
    4153
    +                                        (HsString
    
    4154
    +                                            (defaultStrMeta (getSTRINGs $1))
    
    4155
    +                                            (getSTRING $1)) }
    
    4156
    +        | modid '.' STRING_MULTI    { hintQualifiedStrings *>
    
    4157
    +                                      hintMultilineStrings *>
    
    4158
    +                                      sLL $1 $2
    
    4159
    +                                        (HsString
    
    4160
    +                                            (defaultStrMeta (getSTRINGMULTIs $1)){strMetaMultiline = True}
    
    4161
    +                                            (getSTRING $1)) }
    
    4151 4162
     
    
    4152 4163
     -----------------------------------------------------------------------------
    
    4153 4164
     -- Layout
    
    ... ... @@ -4505,6 +4516,18 @@ hintQualifiedDo tok = do
    4505 4516
           ITmdo (Just m) -> Just $ ftext m <> text ".mdo"
    
    4506 4517
           t -> Nothing
    
    4507 4518
     
    
    4519
    +-- Hint about the MultilineStrings extension
    
    4520
    +hintMultilineStrings :: SrcSpan -> P ()
    
    4521
    +hintMultilineStrings span = do
    
    4522
    +  enabled <- getBit MultilineStringsBit
    
    4523
    +  unless enabled $ addError $ mkPlainErrorMsgEnvelope span PsErrMultilineStrings
    
    4524
    +
    
    4525
    +-- Hint about the QualifiedStrings extension
    
    4526
    +hintQualifiedStrings :: SrcSpan -> P ()
    
    4527
    +hintQualifiedStrings span = do
    
    4528
    +  enabled <- getBit QualifiedStringsBit
    
    4529
    +  unless enabled $ addError $ mkPlainErrorMsgEnvelope span PsErrQualifiedStrings
    
    4530
    +
    
    4508 4531
     -- When two single quotes don't followed by tyvar or gtycon, we report the
    
    4509 4532
     -- error as empty character literal, or TH quote that missing proper type
    
    4510 4533
     -- variable or constructor. See #13450.
    

  • compiler/GHC/Parser/Errors/Types.hs
    ... ... @@ -441,6 +441,12 @@ data PsMessage
    441 441
        -- | Multi-way if-expression found but MultiWayIf not enabled
    
    442 442
        | PsErrMultiWayIf
    
    443 443
     
    
    444
    +   -- | Multiline string literal found but MultilineStrings not enabled
    
    445
    +   | PsErrMultilineStrings
    
    446
    +
    
    447
    +   -- | Qualified string literal found but QualifiedStrings not enabled
    
    448
    +   | PsErrQualifiedStrings
    
    449
    +
    
    444 450
        -- | Explicit forall found but no extension allowing it is enabled
    
    445 451
        | PsErrExplicitForall !Bool
    
    446 452
                              -- ^ is Unicode forall?
    

  • libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
    ... ... @@ -696,6 +696,7 @@ data Lit = CharL Char -- ^ @\'c\'@
    696 696
              | StringPrimL [Word8]  -- ^ @"string"#@. A primitive C-style string, type 'Addr#'
    
    697 697
              | BytesPrimL Bytes     -- ^ Some raw bytes, type 'Addr#':
    
    698 698
              | CharPrimL Char       -- ^ @\'c\'#@
    
    699
    +         | QualStringL ModName String -- ^ @M."string"#@
    
    699 700
         deriving( Show, Eq, Ord, Generic )
    
    700 701
     
    
    701 702
         -- We could add Int, Float, Double etc, as we do in HsLit,