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

module Distribution.Types.ExeDependency
  ( ExeDependency (..)
  , qualifiedExeName
  ) where

import Distribution.Compat.Prelude
import Prelude ()

import Distribution.Parsec
import Distribution.Pretty
import Distribution.Types.ComponentName
import Distribution.Types.PackageName
import Distribution.Types.UnqualComponentName
import Distribution.Version (VersionRange, anyVersion, isAnyVersion)

import qualified Distribution.Compat.CharParsing as P
import qualified Text.PrettyPrint as PP

-- | Describes a dependency on an executable from a package
data ExeDependency
  = ExeDependency
      PackageName
      UnqualComponentName -- name of executable component of package
      VersionRange
  deriving ((forall x. ExeDependency -> Rep ExeDependency x)
-> (forall x. Rep ExeDependency x -> ExeDependency)
-> Generic ExeDependency
forall x. Rep ExeDependency x -> ExeDependency
forall x. ExeDependency -> Rep ExeDependency x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExeDependency -> Rep ExeDependency x
from :: forall x. ExeDependency -> Rep ExeDependency x
$cto :: forall x. Rep ExeDependency x -> ExeDependency
to :: forall x. Rep ExeDependency x -> ExeDependency
Generic, ReadPrec [ExeDependency]
ReadPrec ExeDependency
Int -> ReadS ExeDependency
ReadS [ExeDependency]
(Int -> ReadS ExeDependency)
-> ReadS [ExeDependency]
-> ReadPrec ExeDependency
-> ReadPrec [ExeDependency]
-> Read ExeDependency
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ExeDependency
readsPrec :: Int -> ReadS ExeDependency
$creadList :: ReadS [ExeDependency]
readList :: ReadS [ExeDependency]
$creadPrec :: ReadPrec ExeDependency
readPrec :: ReadPrec ExeDependency
$creadListPrec :: ReadPrec [ExeDependency]
readListPrec :: ReadPrec [ExeDependency]
Read, Int -> ExeDependency -> ShowS
[ExeDependency] -> ShowS
ExeDependency -> String
(Int -> ExeDependency -> ShowS)
-> (ExeDependency -> String)
-> ([ExeDependency] -> ShowS)
-> Show ExeDependency
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExeDependency -> ShowS
showsPrec :: Int -> ExeDependency -> ShowS
$cshow :: ExeDependency -> String
show :: ExeDependency -> String
$cshowList :: [ExeDependency] -> ShowS
showList :: [ExeDependency] -> ShowS
Show, ExeDependency -> ExeDependency -> Bool
(ExeDependency -> ExeDependency -> Bool)
-> (ExeDependency -> ExeDependency -> Bool) -> Eq ExeDependency
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExeDependency -> ExeDependency -> Bool
== :: ExeDependency -> ExeDependency -> Bool
$c/= :: ExeDependency -> ExeDependency -> Bool
/= :: ExeDependency -> ExeDependency -> Bool
Eq, Eq ExeDependency
Eq ExeDependency =>
(ExeDependency -> ExeDependency -> Ordering)
-> (ExeDependency -> ExeDependency -> Bool)
-> (ExeDependency -> ExeDependency -> Bool)
-> (ExeDependency -> ExeDependency -> Bool)
-> (ExeDependency -> ExeDependency -> Bool)
-> (ExeDependency -> ExeDependency -> ExeDependency)
-> (ExeDependency -> ExeDependency -> ExeDependency)
-> Ord ExeDependency
ExeDependency -> ExeDependency -> Bool
ExeDependency -> ExeDependency -> Ordering
ExeDependency -> ExeDependency -> ExeDependency
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 :: ExeDependency -> ExeDependency -> Ordering
compare :: ExeDependency -> ExeDependency -> Ordering
$c< :: ExeDependency -> ExeDependency -> Bool
< :: ExeDependency -> ExeDependency -> Bool
$c<= :: ExeDependency -> ExeDependency -> Bool
<= :: ExeDependency -> ExeDependency -> Bool
$c> :: ExeDependency -> ExeDependency -> Bool
> :: ExeDependency -> ExeDependency -> Bool
$c>= :: ExeDependency -> ExeDependency -> Bool
>= :: ExeDependency -> ExeDependency -> Bool
$cmax :: ExeDependency -> ExeDependency -> ExeDependency
max :: ExeDependency -> ExeDependency -> ExeDependency
$cmin :: ExeDependency -> ExeDependency -> ExeDependency
min :: ExeDependency -> ExeDependency -> ExeDependency
Ord, Typeable, Typeable ExeDependency
Typeable ExeDependency =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> ExeDependency -> c ExeDependency)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ExeDependency)
-> (ExeDependency -> Constr)
-> (ExeDependency -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c ExeDependency))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c ExeDependency))
-> ((forall b. Data b => b -> b) -> ExeDependency -> ExeDependency)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> ExeDependency -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> ExeDependency -> r)
-> (forall u. (forall d. Data d => d -> u) -> ExeDependency -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> ExeDependency -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> ExeDependency -> m ExeDependency)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ExeDependency -> m ExeDependency)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ExeDependency -> m ExeDependency)
-> Data ExeDependency
ExeDependency -> Constr
ExeDependency -> DataType
(forall b. Data b => b -> b) -> ExeDependency -> ExeDependency
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) -> ExeDependency -> u
forall u. (forall d. Data d => d -> u) -> ExeDependency -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ExeDependency -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ExeDependency -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ExeDependency -> m ExeDependency
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ExeDependency -> m ExeDependency
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExeDependency
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ExeDependency -> c ExeDependency
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ExeDependency)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ExeDependency)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ExeDependency -> c ExeDependency
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ExeDependency -> c ExeDependency
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExeDependency
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExeDependency
$ctoConstr :: ExeDependency -> Constr
toConstr :: ExeDependency -> Constr
$cdataTypeOf :: ExeDependency -> DataType
dataTypeOf :: ExeDependency -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ExeDependency)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ExeDependency)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ExeDependency)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ExeDependency)
$cgmapT :: (forall b. Data b => b -> b) -> ExeDependency -> ExeDependency
gmapT :: (forall b. Data b => b -> b) -> ExeDependency -> ExeDependency
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ExeDependency -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ExeDependency -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ExeDependency -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ExeDependency -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ExeDependency -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ExeDependency -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ExeDependency -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ExeDependency -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ExeDependency -> m ExeDependency
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ExeDependency -> m ExeDependency
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ExeDependency -> m ExeDependency
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ExeDependency -> m ExeDependency
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ExeDependency -> m ExeDependency
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ExeDependency -> m ExeDependency
Data)

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

instance Pretty ExeDependency where
  pretty :: ExeDependency -> Doc
pretty (ExeDependency PackageName
name UnqualComponentName
exe VersionRange
ver) =
    PackageName -> Doc
forall a. Pretty a => a -> Doc
pretty PackageName
name Doc -> Doc -> Doc
<<>> Doc
PP.colon Doc -> Doc -> Doc
<<>> UnqualComponentName -> Doc
forall a. Pretty a => a -> Doc
pretty UnqualComponentName
exe Doc -> Doc -> Doc
PP.<+> Doc
pver
    where
      pver :: Doc
pver
        | VersionRange -> Bool
isAnyVersion VersionRange
ver = Doc
PP.empty
        | Bool
otherwise = VersionRange -> Doc
forall a. Pretty a => a -> Doc
pretty VersionRange
ver

-- |
--
-- Examples
--
-- >>> simpleParsec "happy:happy" :: Maybe ExeDependency
-- Just (ExeDependency (PackageName "happy") (UnqualComponentName "happy") (OrLaterVersion (mkVersion [0])))
--
-- >>> simpleParsec "happy:happy >= 1.19.12" :: Maybe ExeDependency
-- Just (ExeDependency (PackageName "happy") (UnqualComponentName "happy") (OrLaterVersion (mkVersion [1,19,12])))
--
-- >>> simpleParsec "happy:happy>=1.19.12" :: Maybe ExeDependency
-- Just (ExeDependency (PackageName "happy") (UnqualComponentName "happy") (OrLaterVersion (mkVersion [1,19,12])))
--
-- >>> simpleParsec "happy : happy >= 1.19.12" :: Maybe ExeDependency
-- Nothing
--
-- >>> simpleParsec "happy: happy >= 1.19.12" :: Maybe ExeDependency
-- Nothing
--
-- >>> simpleParsec "happy :happy >= 1.19.12" :: Maybe ExeDependency
-- Nothing
instance Parsec ExeDependency where
  parsec :: forall (m :: * -> *). CabalParsing m => m ExeDependency
parsec = do
    name <- m PackageName
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
forall (m :: * -> *). CabalParsing m => m PackageName
parsec
    _ <- P.char ':'
    exe <- lexemeParsec
    ver <- parsec <|> pure anyVersion
    return (ExeDependency name exe ver)

qualifiedExeName :: ExeDependency -> ComponentName
qualifiedExeName :: ExeDependency -> ComponentName
qualifiedExeName (ExeDependency PackageName
_ UnqualComponentName
ucn VersionRange
_) = UnqualComponentName -> ComponentName
CExeName UnqualComponentName
ucn