{-# 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)

import qualified Distribution.Compat.CharParsing as P
import           Text.PrettyPrint           (text, (<+>))

-- | 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
$cto :: forall x. Rep ExeDependency x -> ExeDependency
$cfrom :: forall x. ExeDependency -> Rep ExeDependency x
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
readListPrec :: ReadPrec [ExeDependency]
$creadListPrec :: ReadPrec [ExeDependency]
readPrec :: ReadPrec ExeDependency
$creadPrec :: ReadPrec ExeDependency
readList :: ReadS [ExeDependency]
$creadList :: ReadS [ExeDependency]
readsPrec :: Int -> ReadS ExeDependency
$creadsPrec :: Int -> ReadS 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
showList :: [ExeDependency] -> ShowS
$cshowList :: [ExeDependency] -> ShowS
show :: ExeDependency -> String
$cshow :: ExeDependency -> String
showsPrec :: Int -> ExeDependency -> ShowS
$cshowsPrec :: Int -> ExeDependency -> ShowS
Show, ExeDependency -> ExeDependency -> Bool
(ExeDependency -> ExeDependency -> Bool)
-> (ExeDependency -> ExeDependency -> Bool) -> Eq ExeDependency
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExeDependency -> ExeDependency -> Bool
$c/= :: ExeDependency -> ExeDependency -> Bool
== :: ExeDependency -> ExeDependency -> Bool
$c== :: ExeDependency -> ExeDependency -> Bool
Eq, Typeable, Typeable ExeDependency
DataType
Constr
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 -> DataType
ExeDependency -> Constr
(forall b. Data b => b -> b) -> ExeDependency -> ExeDependency
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ExeDependency -> c ExeDependency
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cExeDependency :: Constr
$tExeDependency :: DataType
gmapMo :: (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
gmapMp :: (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
gmapM :: (forall d. Data d => d -> m d) -> ExeDependency -> m ExeDependency
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ExeDependency -> m ExeDependency
gmapQi :: Int -> (forall d. Data d => d -> u) -> ExeDependency -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ExeDependency -> u
gmapQ :: (forall d. Data d => d -> u) -> ExeDependency -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ExeDependency -> [u]
gmapQr :: (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
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ExeDependency -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ExeDependency -> r
gmapT :: (forall b. Data b => b -> b) -> ExeDependency -> ExeDependency
$cgmapT :: (forall b. Data b => b -> b) -> ExeDependency -> ExeDependency
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ExeDependency)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ExeDependency)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ExeDependency)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ExeDependency)
dataTypeOf :: ExeDependency -> DataType
$cdataTypeOf :: ExeDependency -> DataType
toConstr :: ExeDependency -> Constr
$ctoConstr :: ExeDependency -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExeDependency
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExeDependency
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ExeDependency -> c ExeDependency
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ExeDependency -> c ExeDependency
$cp1Data :: Typeable 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
<<>> String -> Doc
text String
":" Doc -> Doc -> Doc
<<>> UnqualComponentName -> Doc
forall a. Pretty a => a -> Doc
pretty UnqualComponentName
exe) Doc -> Doc -> Doc
<+> VersionRange -> Doc
forall a. Pretty a => a -> Doc
pretty VersionRange
ver

-- | 
--
-- Examples
--
-- >>> simpleParsec "happy:happy" :: Maybe ExeDependency
-- Just (ExeDependency (PackageName "happy") (UnqualComponentName "happy") AnyVersion)
--
-- >>> 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 :: m ExeDependency
parsec = do
        PackageName
name <- m PackageName
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec
        Char
_    <- Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
P.char Char
':'
        UnqualComponentName
exe  <- m UnqualComponentName
forall (m :: * -> *) a. (CabalParsing m, Parsec a) => m a
lexemeParsec
        VersionRange
ver  <- m VersionRange
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec m VersionRange -> m VersionRange -> m VersionRange
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> VersionRange -> m VersionRange
forall (f :: * -> *) a. Applicative f => a -> f a
pure VersionRange
anyVersion
        ExeDependency -> m ExeDependency
forall (m :: * -> *) a. Monad m => a -> m a
return (PackageName -> UnqualComponentName -> VersionRange -> ExeDependency
ExeDependency PackageName
name UnqualComponentName
exe VersionRange
ver)

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