Skip to content
Snippets Groups Projects
Commit f8eb9aa9 authored by Duncan Coutts's avatar Duncan Coutts
Browse files

Add ModuleName.fromString and deprecate ModuleName.simple

Also document the functions in the ModuleName module.
parent e35bdd52
No related merge requests found
......@@ -40,10 +40,11 @@ OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -}
module Distribution.ModuleName (
ModuleName,
simple,
fromString,
components,
toFilePath,
main,
simple,
) where
import Distribution.Text
......@@ -57,9 +58,9 @@ import System.FilePath
( pathSeparator )
import Data.List
( intersperse )
import Control.Exception
( assert )
-- | A valid Haskell module name.
--
newtype ModuleName = ModuleName [String]
deriving (Eq, Ord, Read, Show)
......@@ -74,18 +75,56 @@ instance Text ModuleName where
where
component = do
c <- Parse.satisfy Char.isUpper
cs <- Parse.munch (\x -> Char.isAlphaNum x || x == '_' || x == '\'')
cs <- Parse.munch validModuleChar
return (c:cs)
validModuleChar :: Char -> Bool
validModuleChar c = Char.isAlphaNum c || c == '_' || c == '\''
validModuleComponent :: String -> Bool
validModuleComponent [] = False
validModuleComponent (c:cs) = Char.isUpper c
&& all validModuleChar cs
{-# DEPRECATED simple "use ModuleName.fromString instead" #-}
simple :: String -> ModuleName
simple name = assert (all (/='.') name)
(ModuleName [name])
simple str = ModuleName [str]
-- | Construct a 'ModuleName' from a valid module name 'String'.
--
-- This is just a convenience function intended for valid module strings. It is
-- an error if it is used with a string that is not a valid module name. If you
-- are parsing user input then use 'Distribution.Text.simpleParse' instead.
--
fromString :: String -> ModuleName
fromString string
| all validModuleComponent components' = ModuleName components'
| otherwise = error badName
where
components' = split string
badName = "ModuleName.fromString: invalid module name " ++ show string
split cs = case break (=='.') cs of
(chunk,[]) -> chunk : []
(chunk,_:rest) -> chunk : split rest
-- | The module name @Main@.
--
main :: ModuleName
main = ModuleName ["Main"]
-- | The individual components of a hierarchical module name. For example
--
-- > components (fromString "A.B.C") = ["A", "B", "C"]
--
components :: ModuleName -> [String]
components (ModuleName ms) = ms
-- | Convert a module name to a file path, but without any file extension.
-- For example:
--
-- > toFilePath (fromString "A.B.C") = "A/B/C"
--
toFilePath :: ModuleName -> FilePath
toFilePath = concat . intersperse [pathSeparator] . components
......@@ -98,7 +98,8 @@ cppHeaderName = "cabal_macros.h"
-- |The name of the auto-generated module associated with a package
autogenModuleName :: PackageDescription -> ModuleName
autogenModuleName pkg_descr =
ModuleName.simple $ "Paths_" ++ map fixchar (display (packageName pkg_descr))
ModuleName.fromString $
"Paths_" ++ map fixchar (display (packageName pkg_descr))
where fixchar '-' = '_'
fixchar c = c
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment