diff options
Diffstat (limited to 'compiler/Language')
-rw-r--r-- | compiler/Language/Haskell/Syntax.hs | 2 | ||||
-rw-r--r-- | compiler/Language/Haskell/Syntax/ImpExp.hs | 5 | ||||
-rw-r--r-- | compiler/Language/Haskell/Syntax/ImpExp.hs-boot | 6 | ||||
-rw-r--r-- | compiler/Language/Haskell/Syntax/Module/Name.hs | 60 |
4 files changed, 63 insertions, 10 deletions
diff --git a/compiler/Language/Haskell/Syntax.hs b/compiler/Language/Haskell/Syntax.hs index d5129cbb13..82e9f5558d 100644 --- a/compiler/Language/Haskell/Syntax.hs +++ b/compiler/Language/Haskell/Syntax.hs @@ -22,6 +22,7 @@ module Language.Haskell.Syntax ( module Language.Haskell.Syntax.Expr, module Language.Haskell.Syntax.ImpExp, module Language.Haskell.Syntax.Lit, + module Language.Haskell.Syntax.Module.Name, module Language.Haskell.Syntax.Pat, module Language.Haskell.Syntax.Type, module Language.Haskell.Syntax.Extension, @@ -32,6 +33,7 @@ import Language.Haskell.Syntax.Decls import Language.Haskell.Syntax.Binds import Language.Haskell.Syntax.Expr import Language.Haskell.Syntax.ImpExp +import Language.Haskell.Syntax.Module.Name import Language.Haskell.Syntax.Lit import Language.Haskell.Syntax.Extension import Language.Haskell.Syntax.Pat diff --git a/compiler/Language/Haskell/Syntax/ImpExp.hs b/compiler/Language/Haskell/Syntax/ImpExp.hs index 7e529701c4..b31c417936 100644 --- a/compiler/Language/Haskell/Syntax/ImpExp.hs +++ b/compiler/Language/Haskell/Syntax/ImpExp.hs @@ -3,6 +3,7 @@ module Language.Haskell.Syntax.ImpExp where import Language.Haskell.Syntax.Extension +import Language.Haskell.Syntax.Module.Name import Data.Eq (Eq) import Data.Ord (Ord) @@ -14,7 +15,6 @@ import Data.String (String) import Data.Int (Int) import GHC.Hs.Doc -- ROMES:TODO Discuss in #21592 whether this is parsed AST or base AST -import GHC.Data.FastString {- ************************************************************************ @@ -26,9 +26,6 @@ Import and export declaration lists One per import declaration in a module. -} --- | A ModuleName is essentially a simple string, e.g. @Data.List@. -newtype ModuleName = ModuleName FastString deriving Show - -- | Located Import Declaration type LImportDecl pass = XRec pass (ImportDecl pass) -- ^ When in a list this may have diff --git a/compiler/Language/Haskell/Syntax/ImpExp.hs-boot b/compiler/Language/Haskell/Syntax/ImpExp.hs-boot index 9cc78600b8..68bd7fdc53 100644 --- a/compiler/Language/Haskell/Syntax/ImpExp.hs-boot +++ b/compiler/Language/Haskell/Syntax/ImpExp.hs-boot @@ -1,7 +1,5 @@ module Language.Haskell.Syntax.ImpExp where -import GHC.Data.FastString - import Data.Eq import Data.Ord import Text.Show @@ -16,7 +14,3 @@ instance Eq IsBootInterface instance Ord IsBootInterface instance Show IsBootInterface instance Data IsBootInterface - -newtype ModuleName = ModuleName FastString - -instance Show ModuleName diff --git a/compiler/Language/Haskell/Syntax/Module/Name.hs b/compiler/Language/Haskell/Syntax/Module/Name.hs new file mode 100644 index 0000000000..65e64d8700 --- /dev/null +++ b/compiler/Language/Haskell/Syntax/Module/Name.hs @@ -0,0 +1,60 @@ +module Language.Haskell.Syntax.Module.Name where + +import Prelude + +import Data.Data +import Data.Char (isAlphaNum) +import Control.DeepSeq +import qualified Text.ParserCombinators.ReadP as Parse +import System.FilePath + +import GHC.Utils.Misc (abstractConstr) +import GHC.Data.FastString + +-- | A ModuleName is essentially a simple string, e.g. @Data.List@. +newtype ModuleName = ModuleName FastString deriving (Show, Eq) + +instance Ord ModuleName where + nm1 `compare` nm2 = stableModuleNameCmp nm1 nm2 + +instance Data ModuleName where + -- don't traverse? + toConstr _ = abstractConstr "ModuleName" + gunfold _ _ = error "gunfold" + dataTypeOf _ = mkNoRepType "ModuleName" + +instance NFData ModuleName where + rnf x = x `seq` () + +stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering +-- ^ Compares module names lexically, rather than by their 'Unique's +stableModuleNameCmp n1 n2 = moduleNameFS n1 `lexicalCompareFS` moduleNameFS n2 + +moduleNameFS :: ModuleName -> FastString +moduleNameFS (ModuleName mod) = mod + +moduleNameString :: ModuleName -> String +moduleNameString (ModuleName mod) = unpackFS mod + +mkModuleName :: String -> ModuleName +mkModuleName s = ModuleName (mkFastString s) + +mkModuleNameFS :: FastString -> ModuleName +mkModuleNameFS s = ModuleName s + +-- |Returns the string version of the module name, with dots replaced by slashes. +-- +moduleNameSlashes :: ModuleName -> String +moduleNameSlashes = dots_to_slashes . moduleNameString + where dots_to_slashes = map (\c -> if c == '.' then pathSeparator else c) + +-- |Returns the string version of the module name, with dots replaced by colons. +-- +moduleNameColons :: ModuleName -> String +moduleNameColons = dots_to_colons . moduleNameString + where dots_to_colons = map (\c -> if c == '.' then ':' else c) + +parseModuleName :: Parse.ReadP ModuleName +parseModuleName = fmap mkModuleName + $ Parse.munch1 (\c -> isAlphaNum c || c `elem` "_.") + |