{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}

module Distribution.Types.Dependency
  ( Dependency (..)
  , mkDependency
  , depPkgName
  , depVerRange
  , depLibraries
  , simplifyDependency
  , mainLibSet
  ) where

import Distribution.Compat.Prelude
import Prelude ()

import Distribution.Types.VersionRange (isAnyVersionLight)
import Distribution.Version (VersionRange, anyVersion, simplifyVersionRange)

import Distribution.CabalSpecVersion
import Distribution.Compat.CharParsing (char, spaces)
import Distribution.Compat.Parsing (between, option)
import Distribution.Parsec
import Distribution.Pretty
import Distribution.Types.LibraryName
import Distribution.Types.PackageName
import Distribution.Types.UnqualComponentName

import qualified Distribution.Compat.NonEmptySet as NES
import qualified Text.PrettyPrint as PP

-- | Describes a dependency on a source package (API)
--
-- /Invariant:/ package name does not appear as 'LSubLibName' in
-- set of library names.
--
-- /Note:/ 'Dependency' is not an instance of 'Ord', and so it cannot be used
-- in 'Set' or as the key to a 'Map'.  For these and similar use cases see
-- 'DependencyMap'.
data Dependency
  = -- | The set of libraries required from the package.
    -- Only the selected libraries will be built.
    -- It does not affect the cabal-install solver yet.
    Dependency
      PackageName
      VersionRange
      (NonEmptySet LibraryName)
  deriving ((forall x. Dependency -> Rep Dependency x)
-> (forall x. Rep Dependency x -> Dependency) -> Generic Dependency
forall x. Rep Dependency x -> Dependency
forall x. Dependency -> Rep Dependency x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Dependency -> Rep Dependency x
from :: forall x. Dependency -> Rep Dependency x
$cto :: forall x. Rep Dependency x -> Dependency
to :: forall x. Rep Dependency x -> Dependency
Generic, ReadPrec [Dependency]
ReadPrec Dependency
Int -> ReadS Dependency
ReadS [Dependency]
(Int -> ReadS Dependency)
-> ReadS [Dependency]
-> ReadPrec Dependency
-> ReadPrec [Dependency]
-> Read Dependency
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Dependency
readsPrec :: Int -> ReadS Dependency
$creadList :: ReadS [Dependency]
readList :: ReadS [Dependency]
$creadPrec :: ReadPrec Dependency
readPrec :: ReadPrec Dependency
$creadListPrec :: ReadPrec [Dependency]
readListPrec :: ReadPrec [Dependency]
Read, Int -> Dependency -> ShowS
[Dependency] -> ShowS
Dependency -> String
(Int -> Dependency -> ShowS)
-> (Dependency -> String)
-> ([Dependency] -> ShowS)
-> Show Dependency
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Dependency -> ShowS
showsPrec :: Int -> Dependency -> ShowS
$cshow :: Dependency -> String
show :: Dependency -> String
$cshowList :: [Dependency] -> ShowS
showList :: [Dependency] -> ShowS
Show, Dependency -> Dependency -> Bool
(Dependency -> Dependency -> Bool)
-> (Dependency -> Dependency -> Bool) -> Eq Dependency
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Dependency -> Dependency -> Bool
== :: Dependency -> Dependency -> Bool
$c/= :: Dependency -> Dependency -> Bool
/= :: Dependency -> Dependency -> Bool
Eq, Eq Dependency
Eq Dependency =>
(Dependency -> Dependency -> Ordering)
-> (Dependency -> Dependency -> Bool)
-> (Dependency -> Dependency -> Bool)
-> (Dependency -> Dependency -> Bool)
-> (Dependency -> Dependency -> Bool)
-> (Dependency -> Dependency -> Dependency)
-> (Dependency -> Dependency -> Dependency)
-> Ord Dependency
Dependency -> Dependency -> Bool
Dependency -> Dependency -> Ordering
Dependency -> Dependency -> Dependency
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Dependency -> Dependency -> Ordering
compare :: Dependency -> Dependency -> Ordering
$c< :: Dependency -> Dependency -> Bool
< :: Dependency -> Dependency -> Bool
$c<= :: Dependency -> Dependency -> Bool
<= :: Dependency -> Dependency -> Bool
$c> :: Dependency -> Dependency -> Bool
> :: Dependency -> Dependency -> Bool
$c>= :: Dependency -> Dependency -> Bool
>= :: Dependency -> Dependency -> Bool
$cmax :: Dependency -> Dependency -> Dependency
max :: Dependency -> Dependency -> Dependency
$cmin :: Dependency -> Dependency -> Dependency
min :: Dependency -> Dependency -> Dependency
Ord, Typeable, Typeable Dependency
Typeable Dependency =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Dependency -> c Dependency)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Dependency)
-> (Dependency -> Constr)
-> (Dependency -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Dependency))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c Dependency))
-> ((forall b. Data b => b -> b) -> Dependency -> Dependency)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Dependency -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Dependency -> r)
-> (forall u. (forall d. Data d => d -> u) -> Dependency -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> Dependency -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Dependency -> m Dependency)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Dependency -> m Dependency)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Dependency -> m Dependency)
-> Data Dependency
Dependency -> Constr
Dependency -> DataType
(forall b. Data b => b -> b) -> Dependency -> Dependency
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Dependency -> u
forall u. (forall d. Data d => d -> u) -> Dependency -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Dependency -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Dependency -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Dependency -> m Dependency
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Dependency -> m Dependency
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Dependency
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Dependency -> c Dependency
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Dependency)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dependency)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Dependency -> c Dependency
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Dependency -> c Dependency
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Dependency
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Dependency
$ctoConstr :: Dependency -> Constr
toConstr :: Dependency -> Constr
$cdataTypeOf :: Dependency -> DataType
dataTypeOf :: Dependency -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Dependency)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Dependency)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dependency)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dependency)
$cgmapT :: (forall b. Data b => b -> b) -> Dependency -> Dependency
gmapT :: (forall b. Data b => b -> b) -> Dependency -> Dependency
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Dependency -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Dependency -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Dependency -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Dependency -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Dependency -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Dependency -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Dependency -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Dependency -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Dependency -> m Dependency
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Dependency -> m Dependency
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Dependency -> m Dependency
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Dependency -> m Dependency
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Dependency -> m Dependency
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Dependency -> m Dependency
Data)

depPkgName :: Dependency -> PackageName
depPkgName :: Dependency -> PackageName
depPkgName (Dependency PackageName
pn VersionRange
_ NonEmptySet LibraryName
_) = PackageName
pn

depVerRange :: Dependency -> VersionRange
depVerRange :: Dependency -> VersionRange
depVerRange (Dependency PackageName
_ VersionRange
vr NonEmptySet LibraryName
_) = VersionRange
vr

depLibraries :: Dependency -> NonEmptySet LibraryName
depLibraries :: Dependency -> NonEmptySet LibraryName
depLibraries (Dependency PackageName
_ VersionRange
_ NonEmptySet LibraryName
cs) = NonEmptySet LibraryName
cs

-- | Smart constructor of 'Dependency'.
--
-- If 'PackageName' is appears as 'LSubLibName' in a set of sublibraries,
-- it is automatically converted to 'LMainLibName'.
--
-- @since 3.4.0.0
mkDependency :: PackageName -> VersionRange -> NonEmptySet LibraryName -> Dependency
mkDependency :: PackageName
-> VersionRange -> NonEmptySet LibraryName -> Dependency
mkDependency PackageName
pn VersionRange
vr NonEmptySet LibraryName
lb = PackageName
-> VersionRange -> NonEmptySet LibraryName -> Dependency
Dependency PackageName
pn VersionRange
vr ((LibraryName -> LibraryName)
-> NonEmptySet LibraryName -> NonEmptySet LibraryName
forall b a. Ord b => (a -> b) -> NonEmptySet a -> NonEmptySet b
NES.map LibraryName -> LibraryName
conv NonEmptySet LibraryName
lb)
  where
    pn' :: UnqualComponentName
pn' = PackageName -> UnqualComponentName
packageNameToUnqualComponentName PackageName
pn

    conv :: LibraryName -> LibraryName
conv l :: LibraryName
l@LibraryName
LMainLibName = LibraryName
l
    conv l :: LibraryName
l@(LSubLibName UnqualComponentName
ln)
      | UnqualComponentName
ln UnqualComponentName -> UnqualComponentName -> Bool
forall a. Eq a => a -> a -> Bool
== UnqualComponentName
pn' = LibraryName
LMainLibName
      | Bool
otherwise = LibraryName
l

instance Binary Dependency
instance Structured Dependency
instance NFData Dependency where rnf :: Dependency -> ()
rnf = Dependency -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf

-- |
--
-- >>> prettyShow $ Dependency (mkPackageName "pkg") anyVersion mainLibSet
-- "pkg"
--
-- >>> prettyShow $ Dependency (mkPackageName "pkg") anyVersion $ NES.insert (LSubLibName $ mkUnqualComponentName "sublib") mainLibSet
-- "pkg:{pkg, sublib}"
--
-- >>> prettyShow $ Dependency (mkPackageName "pkg") anyVersion $ NES.singleton (LSubLibName $ mkUnqualComponentName "sublib")
-- "pkg:sublib"
--
-- >>> prettyShow $ Dependency (mkPackageName "pkg") anyVersion $ NES.insert (LSubLibName $ mkUnqualComponentName "sublib-b") $ NES.singleton (LSubLibName $ mkUnqualComponentName "sublib-a")
-- "pkg:{sublib-a, sublib-b}"
instance Pretty Dependency where
  pretty :: Dependency -> Doc
pretty (Dependency PackageName
name VersionRange
ver NonEmptySet LibraryName
sublibs) = Doc -> Doc
withSubLibs (PackageName -> Doc
forall a. Pretty a => a -> Doc
pretty PackageName
name) Doc -> Doc -> Doc
<+> Doc
pver
    where
      -- TODO: change to isAnyVersion after #6736
      pver :: Doc
pver
        | VersionRange -> Bool
isAnyVersionLight VersionRange
ver = Doc
PP.empty
        | Bool
otherwise = VersionRange -> Doc
forall a. Pretty a => a -> Doc
pretty VersionRange
ver

      withSubLibs :: Doc -> Doc
withSubLibs Doc
doc = case NonEmptySet LibraryName -> [LibraryName]
forall a. NonEmptySet a -> [a]
NES.toList NonEmptySet LibraryName
sublibs of
        [LibraryName
LMainLibName] -> Doc
doc
        [LSubLibName UnqualComponentName
uq] -> Doc
doc Doc -> Doc -> Doc
<<>> Doc
PP.colon Doc -> Doc -> Doc
<<>> UnqualComponentName -> Doc
forall a. Pretty a => a -> Doc
pretty UnqualComponentName
uq
        [LibraryName]
_ -> Doc
doc Doc -> Doc -> Doc
<<>> Doc
PP.colon Doc -> Doc -> Doc
<<>> Doc -> Doc
PP.braces Doc
prettySublibs

      prettySublibs :: Doc
prettySublibs = [Doc] -> Doc
PP.hsep ([Doc] -> Doc) -> [Doc] -> Doc
forall a b. (a -> b) -> a -> b
$ Doc -> [Doc] -> [Doc]
PP.punctuate Doc
PP.comma ([Doc] -> [Doc]) -> [Doc] -> [Doc]
forall a b. (a -> b) -> a -> b
$ LibraryName -> Doc
prettySublib (LibraryName -> Doc) -> [LibraryName] -> [Doc]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NonEmptySet LibraryName -> [LibraryName]
forall a. NonEmptySet a -> [a]
NES.toList NonEmptySet LibraryName
sublibs

      prettySublib :: LibraryName -> Doc
prettySublib LibraryName
LMainLibName = String -> Doc
PP.text (String -> Doc) -> String -> Doc
forall a b. (a -> b) -> a -> b
$ PackageName -> String
unPackageName PackageName
name
      prettySublib (LSubLibName UnqualComponentName
un) = String -> Doc
PP.text (String -> Doc) -> String -> Doc
forall a b. (a -> b) -> a -> b
$ UnqualComponentName -> String
unUnqualComponentName UnqualComponentName
un

-- |
--
-- >>> simpleParsec "mylib:sub" :: Maybe Dependency
-- Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LSubLibName (UnqualComponentName "sub") :| [])))
--
-- >>> simpleParsec "mylib:{sub1,sub2}" :: Maybe Dependency
-- Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LSubLibName (UnqualComponentName "sub1") :| [LSubLibName (UnqualComponentName "sub2")])))
--
-- >>> simpleParsec "mylib:{ sub1 , sub2 }" :: Maybe Dependency
-- Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LSubLibName (UnqualComponentName "sub1") :| [LSubLibName (UnqualComponentName "sub2")])))
--
-- >>> simpleParsec "mylib:{ sub1 , sub2 } ^>= 42" :: Maybe Dependency
-- Just (Dependency (PackageName "mylib") (MajorBoundVersion (mkVersion [42])) (fromNonEmpty (LSubLibName (UnqualComponentName "sub1") :| [LSubLibName (UnqualComponentName "sub2")])))
--
-- >>> simpleParsec "mylib:{ } ^>= 42" :: Maybe Dependency
-- Nothing
--
-- >>> traverse_ print (map simpleParsec ["mylib:mylib", "mylib:{mylib}", "mylib:{mylib,sublib}" ] :: [Maybe Dependency])
-- Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LMainLibName :| [])))
-- Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LMainLibName :| [])))
-- Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LMainLibName :| [LSubLibName (UnqualComponentName "sublib")])))
--
-- Spaces around colon are not allowed:
--
-- >>> map simpleParsec ["mylib: sub", "mylib :sub", "mylib: {sub1,sub2}", "mylib :{sub1,sub2}"] :: [Maybe Dependency]
-- [Nothing,Nothing,Nothing,Nothing]
--
-- Sublibrary syntax is accepted since @cabal-version: 3.0@
--
-- >>> map (`simpleParsec'` "mylib:sub") [CabalSpecV2_4, CabalSpecV3_0] :: [Maybe Dependency]
-- [Nothing,Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LSubLibName (UnqualComponentName "sub") :| [])))]
instance Parsec Dependency where
  parsec :: forall (m :: * -> *). CabalParsing m => m Dependency
parsec = do
    name <- m PackageName
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
forall (m :: * -> *). CabalParsing m => m PackageName
parsec

    libs <- option mainLibSet $ do
      _ <- char ':'
      versionGuardMultilibs
      NES.singleton <$> parseLib <|> parseMultipleLibs

    spaces -- https://github.com/haskell/cabal/issues/5846
    ver <- parsec <|> pure anyVersion
    return $ mkDependency name ver libs
    where
      parseLib :: m LibraryName
parseLib = UnqualComponentName -> LibraryName
LSubLibName (UnqualComponentName -> LibraryName)
-> m UnqualComponentName -> m LibraryName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m UnqualComponentName
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
forall (m :: * -> *). CabalParsing m => m UnqualComponentName
parsec
      parseMultipleLibs :: m (NonEmptySet LibraryName)
parseMultipleLibs =
        m ()
-> m Char
-> m (NonEmptySet LibraryName)
-> m (NonEmptySet LibraryName)
forall (m :: * -> *) bra ket a.
Applicative m =>
m bra -> m ket -> m a -> m a
between
          (Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
'{' m Char -> m () -> m ()
forall a b. m a -> m b -> m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> m ()
forall (m :: * -> *). CharParsing m => m ()
spaces)
          (m ()
forall (m :: * -> *). CharParsing m => m ()
spaces m () -> m Char -> m Char
forall a b. m a -> m b -> m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
'}')
          (NonEmpty LibraryName -> NonEmptySet LibraryName
forall a. Ord a => NonEmpty a -> NonEmptySet a
NES.fromNonEmpty (NonEmpty LibraryName -> NonEmptySet LibraryName)
-> m (NonEmpty LibraryName) -> m (NonEmptySet LibraryName)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m LibraryName -> m (NonEmpty LibraryName)
forall (m :: * -> *) a. CabalParsing m => m a -> m (NonEmpty a)
parsecCommaNonEmpty m LibraryName
parseLib)

versionGuardMultilibs :: CabalParsing m => m ()
versionGuardMultilibs :: forall (m :: * -> *). CabalParsing m => m ()
versionGuardMultilibs = do
  csv <- m CabalSpecVersion
forall (m :: * -> *). CabalParsing m => m CabalSpecVersion
askCabalSpecVersion
  when (csv < CabalSpecV3_0) $
    fail $
      unwords
        [ "Sublibrary dependency syntax used."
        , "To use this syntax the package needs to specify at least 'cabal-version: 3.0'."
        , "Alternatively, if you are depending on an internal library, you can write"
        , "directly the library name as it were a package."
        ]

-- | Library set with main library.
--
-- @since 3.4.0.0
mainLibSet :: NonEmptySet LibraryName
mainLibSet :: NonEmptySet LibraryName
mainLibSet = LibraryName -> NonEmptySet LibraryName
forall a. a -> NonEmptySet a
NES.singleton LibraryName
LMainLibName

-- | Simplify the 'VersionRange' expression in a 'Dependency'.
-- See 'simplifyVersionRange'.
simplifyDependency :: Dependency -> Dependency
simplifyDependency :: Dependency -> Dependency
simplifyDependency (Dependency PackageName
name VersionRange
range NonEmptySet LibraryName
comps) =
  PackageName
-> VersionRange -> NonEmptySet LibraryName -> Dependency
Dependency PackageName
name (VersionRange -> VersionRange
simplifyVersionRange VersionRange
range) NonEmptySet LibraryName
comps