make LTS branch pre-releases
[cabal.git] / Cabal-syntax / src / Distribution / Types / UnitId.hs
blob36a1d003b2e1fb31b6e01686488f2b2d7bf91e70
1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE DeriveGeneric #-}
3 {-# LANGUAGE FlexibleContexts #-}
4 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
6 module Distribution.Types.UnitId
7 ( UnitId
8 , unUnitId
9 , mkUnitId
10 , DefUnitId
11 , unsafeMkDefUnitId
12 , unDefUnitId
13 , newSimpleUnitId
14 , mkLegacyUnitId
15 , getHSLibraryName
16 ) where
18 import Distribution.Compat.Prelude
19 import Distribution.Utils.ShortText
20 import Prelude ()
22 import qualified Distribution.Compat.CharParsing as P
23 import Distribution.Parsec
24 import Distribution.Pretty
25 import Distribution.Types.ComponentId
26 import Distribution.Types.PackageId
28 import Text.PrettyPrint (text)
30 -- | A unit identifier identifies a (possibly instantiated)
31 -- package/component that can be installed the installed package
32 -- database. There are several types of components that can be
33 -- installed:
35 -- * A traditional library with no holes, so that 'unitIdHash'
36 -- is @Nothing@. In the absence of Backpack, 'UnitId'
37 -- is the same as a 'ComponentId'.
39 -- * An indefinite, Backpack library with holes. In this case,
40 -- 'unitIdHash' is still @Nothing@, but in the install,
41 -- there are only interfaces, no compiled objects.
43 -- * An instantiated Backpack library with all the holes
44 -- filled in. 'unitIdHash' is a @Just@ a hash of the
45 -- instantiating mapping.
47 -- A unit is a component plus the additional information on how the
48 -- holes are filled in. Thus there is a one to many relationship: for a
49 -- particular component there are many different ways of filling in the
50 -- holes, and each different combination is a unit (and has a separate
51 -- 'UnitId').
53 -- 'UnitId' is distinct from 'OpenUnitId', in that it is always
54 -- installed, whereas 'OpenUnitId' are intermediate unit identities
55 -- that arise during mixin linking, and don't necessarily correspond
56 -- to any actually installed unit. Since the mapping is not actually
57 -- recorded in a 'UnitId', you can't actually substitute over them
58 -- (but you can substitute over 'OpenUnitId'). See also
59 -- "Distribution.Backpack.FullUnitId" for a mechanism for expanding an
60 -- instantiated 'UnitId' to retrieve its mapping.
62 -- Backwards compatibility note: if you need to get the string
63 -- representation of a UnitId to pass, e.g., as a @-package-id@
64 -- flag, use the 'display' function, which will work on all
65 -- versions of Cabal.
66 newtype UnitId = UnitId ShortText
67 deriving (Generic, Read, Show, Eq, Ord, Typeable, Data, NFData)
69 instance Binary UnitId
70 instance Structured UnitId
72 -- | The textual format for 'UnitId' coincides with the format
73 -- GHC accepts for @-package-id@.
74 instance Pretty UnitId where
75 pretty = text . unUnitId
77 -- | The textual format for 'UnitId' coincides with the format
78 -- GHC accepts for @-package-id@.
79 instance Parsec UnitId where
80 parsec = mkUnitId <$> P.munch1 isUnitChar
81 where
82 -- https://gitlab.haskell.org/ghc/ghc/issues/17752
83 isUnitChar '-' = True
84 isUnitChar '_' = True
85 isUnitChar '.' = True
86 isUnitChar '+' = True
87 isUnitChar c = isAlphaNum c
89 -- | If you need backwards compatibility, consider using 'display'
90 -- instead, which is supported by all versions of Cabal.
91 unUnitId :: UnitId -> String
92 unUnitId (UnitId s) = fromShortText s
94 mkUnitId :: String -> UnitId
95 mkUnitId = UnitId . toShortText
97 -- | 'mkUnitId'
99 -- @since 2.0.0.2
100 instance IsString UnitId where
101 fromString = mkUnitId
103 -- | Create a unit identity with no associated hash directly
104 -- from a 'ComponentId'.
105 newSimpleUnitId :: ComponentId -> UnitId
106 newSimpleUnitId = mkUnitId . unComponentId
108 -- | Make an old-style UnitId from a package identifier.
109 -- Assumed to be for the public library
110 mkLegacyUnitId :: PackageId -> UnitId
111 mkLegacyUnitId = newSimpleUnitId . mkComponentId . prettyShow
113 -- | Returns library name prefixed with HS, suitable for filenames
114 getHSLibraryName :: UnitId -> String
115 getHSLibraryName uid = "HS" ++ prettyShow uid
117 -- | A 'UnitId' for a definite package. The 'DefUnitId' invariant says
118 -- that a 'UnitId' identified this way is definite; i.e., it has no
119 -- unfilled holes.
120 newtype DefUnitId = DefUnitId {unDefUnitId :: UnitId}
121 deriving (Generic, Read, Show, Eq, Ord, Typeable, Data, Binary, NFData, Pretty)
123 instance Structured DefUnitId
125 -- Workaround for a GHC 8.0.1 bug, see
126 -- https://github.com/haskell/cabal/issues/4793#issuecomment-334258288
127 instance Parsec DefUnitId where
128 parsec = DefUnitId <$> parsec
130 -- | Unsafely create a 'DefUnitId' from a 'UnitId'. Your responsibility
131 -- is to ensure that the 'DefUnitId' invariant holds.
132 unsafeMkDefUnitId :: UnitId -> DefUnitId
133 unsafeMkDefUnitId = DefUnitId