make LTS branch pre-releases
[cabal.git] / Cabal-syntax / src / Distribution / Types / ComponentId.hs
blob47cf1d97ee3645e56d7939afdd1e09c510afe2f1
1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE DeriveGeneric #-}
3 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
5 module Distribution.Types.ComponentId
6 ( ComponentId
7 , unComponentId
8 , mkComponentId
9 ) where
11 import Distribution.Compat.Prelude
12 import Distribution.Utils.ShortText
13 import Prelude ()
15 import Distribution.Parsec
16 import Distribution.Pretty
18 import qualified Distribution.Compat.CharParsing as P
19 import Text.PrettyPrint (text)
21 -- | A 'ComponentId' uniquely identifies the transitive source
22 -- code closure of a component (i.e. libraries, executables).
24 -- For non-Backpack components, this corresponds one to one with
25 -- the 'UnitId', which serves as the basis for install paths,
26 -- linker symbols, etc.
28 -- Use 'mkComponentId' and 'unComponentId' to convert from/to a
29 -- 'String'.
31 -- This type is opaque since @Cabal-2.0@
33 -- @since 2.0.0.2
34 newtype ComponentId = ComponentId ShortText
35 deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)
37 -- | Construct a 'ComponentId' from a 'String'
39 -- 'mkComponentId' is the inverse to 'unComponentId'
41 -- Note: No validations are performed to ensure that the resulting
42 -- 'ComponentId' is valid
44 -- @since 2.0.0.2
45 mkComponentId :: String -> ComponentId
46 mkComponentId = ComponentId . toShortText
48 -- | Convert 'ComponentId' to 'String'
50 -- @since 2.0.0.2
51 unComponentId :: ComponentId -> String
52 unComponentId (ComponentId s) = fromShortText s
54 -- | 'mkComponentId'
56 -- @since 2.0.0.2
57 instance IsString ComponentId where
58 fromString = mkComponentId
60 instance Binary ComponentId
61 instance Structured ComponentId
63 instance Pretty ComponentId where
64 pretty = text . unComponentId
66 instance Parsec ComponentId where
67 parsec = mkComponentId `fmap` P.munch1 abi_char
68 where
69 abi_char c = isAlphaNum c || c `elem` "-_."
71 instance NFData ComponentId where
72 rnf = rnf . unComponentId