make LTS branch pre-releases
[cabal.git] / Cabal-syntax / src / Distribution / ModuleName.hs
blob90082d29f065d5c56e9a0765fd38fc09bcd49d08
1 {-# LANGUAGE BangPatterns #-}
2 {-# LANGUAGE DeriveDataTypeable #-}
3 {-# LANGUAGE DeriveGeneric #-}
4 {-# LANGUAGE ScopedTypeVariables #-}
6 -----------------------------------------------------------------------------
8 -- |
9 -- Module : Distribution.ModuleName
10 -- Copyright : Duncan Coutts 2008
11 -- License : BSD3
13 -- Maintainer : cabal-devel@haskell.org
14 -- Portability : portable
16 -- Data type for Haskell module names.
17 module Distribution.ModuleName
18 ( ModuleName
19 , fromString
20 , fromComponents
21 , components
22 , toFilePath
23 , main
25 -- * Internal
26 , validModuleComponent
27 ) where
29 import Distribution.Compat.Prelude
30 import Prelude ()
32 import Distribution.Parsec
33 import Distribution.Pretty
34 import Distribution.Utils.ShortText (ShortText, fromShortText, toShortText)
35 import System.FilePath (pathSeparator)
37 import qualified Distribution.Compat.CharParsing as P
38 import qualified Distribution.Compat.DList as DList
39 import qualified Text.PrettyPrint as Disp
41 -- | A valid Haskell module name.
42 newtype ModuleName = ModuleName ShortText
43 deriving (Eq, Generic, Ord, Read, Show, Typeable, Data)
45 unModuleName :: ModuleName -> String
46 unModuleName (ModuleName s) = fromShortText s
48 instance Binary ModuleName
49 instance Structured ModuleName
51 instance NFData ModuleName where
52 rnf (ModuleName ms) = rnf ms
54 instance Pretty ModuleName where
55 pretty = Disp.text . unModuleName
57 instance Parsec ModuleName where
58 parsec = parsecModuleName
60 parsecModuleName :: forall m. CabalParsing m => m ModuleName
61 parsecModuleName = state0 DList.empty
62 where
63 upper :: m Char
64 !upper = P.satisfy isUpper
66 ch :: m Char
67 !ch = P.satisfy (\c -> validModuleChar c || c == '.')
69 alt :: m ModuleName -> m ModuleName -> m ModuleName
70 !alt = (<|>)
72 state0 :: DList.DList Char -> m ModuleName
73 state0 acc = do
74 c <- upper
75 state1 (DList.snoc acc c)
77 state1 :: DList.DList Char -> m ModuleName
78 state1 acc = state1' acc `alt` return (fromString (DList.toList acc))
80 state1' :: DList.DList Char -> m ModuleName
81 state1' acc = do
82 c <- ch
83 case c of
84 '.' -> state0 (DList.snoc acc c)
85 _ -> state1 (DList.snoc acc c)
87 validModuleChar :: Char -> Bool
88 validModuleChar c = isAlphaNum c || c == '_' || c == '\''
90 validModuleComponent :: String -> Bool
91 validModuleComponent [] = False
92 validModuleComponent (c : cs) = isUpper c && all validModuleChar cs
94 -- | Construct a 'ModuleName' from a valid module name 'String'.
96 -- This is just a convenience function intended for valid module strings. It is
97 -- an error if it is used with a string that is not a valid module name. If you
98 -- are parsing user input then use 'Distribution.Text.simpleParse' instead.
99 instance IsString ModuleName where
100 fromString = ModuleName . toShortText
102 -- | Construct a 'ModuleName' from valid module components, i.e. parts
103 -- separated by dots.
104 fromComponents :: [String] -> ModuleName
105 fromComponents comps = fromString (intercalate "." comps)
106 {-# DEPRECATED fromComponents "Exists for cabal-install only" #-}
108 -- | The module name @Main@.
109 main :: ModuleName
110 main = ModuleName (fromString "Main")
112 -- | The individual components of a hierarchical module name. For example
114 -- > components (fromString "A.B.C") = ["A", "B", "C"]
115 components :: ModuleName -> [String]
116 components mn = split (unModuleName mn)
117 where
118 split cs = case break (== '.') cs of
119 (chunk, []) -> chunk : []
120 (chunk, _ : rest) -> chunk : split rest
122 -- | Convert a module name to a file path, but without any file extension.
123 -- For example:
125 -- > toFilePath (fromString "A.B.C") = "A/B/C"
126 toFilePath :: ModuleName -> FilePath
127 toFilePath = map f . unModuleName
128 where
129 f '.' = pathSeparator
130 f c = c