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

module Distribution.Types.Executable
  ( Executable (..)
  , emptyExecutable
  , exeModules
  , exeModulesAutogen
  ) where

import Distribution.Compat.Prelude
import Prelude ()

import Distribution.ModuleName
import Distribution.Types.BuildInfo
import Distribution.Types.ExecutableScope
import Distribution.Types.UnqualComponentName

import qualified Distribution.Types.BuildInfo.Lens as L

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

instance L.HasBuildInfo Executable where
  buildInfo :: Lens' Executable BuildInfo
buildInfo BuildInfo -> f BuildInfo
f Executable
l = (\BuildInfo
x -> Executable
l{buildInfo = x}) (BuildInfo -> Executable) -> f BuildInfo -> f Executable
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BuildInfo -> f BuildInfo
f (Executable -> BuildInfo
buildInfo Executable
l)

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

instance Monoid Executable where
  mempty :: Executable
mempty = Executable
forall a. (Generic a, GMonoid (Rep a)) => a
gmempty
  mappend :: Executable -> Executable -> Executable
mappend = Executable -> Executable -> Executable
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup Executable where
  Executable
a <> :: Executable -> Executable -> Executable
<> Executable
b =
    Executable
      { exeName :: UnqualComponentName
exeName = Executable
-> Executable
-> (Executable -> UnqualComponentName)
-> FilePath
-> UnqualComponentName
forall b a.
(Monoid b, Eq b, Show b) =>
a -> a -> (a -> b) -> FilePath -> b
combineNames Executable
a Executable
b Executable -> UnqualComponentName
exeName FilePath
"executable"
      , modulePath :: FilePath
modulePath = Executable -> Executable -> (Executable -> FilePath) -> ShowS
forall b a.
(Monoid b, Eq b, Show b) =>
a -> a -> (a -> b) -> FilePath -> b
combineNames Executable
a Executable
b Executable -> FilePath
modulePath FilePath
"modulePath"
      , exeScope :: ExecutableScope
exeScope = (Executable -> ExecutableScope) -> ExecutableScope
forall {a}. Monoid a => (Executable -> a) -> a
combine Executable -> ExecutableScope
exeScope
      , buildInfo :: BuildInfo
buildInfo = (Executable -> BuildInfo) -> BuildInfo
forall {a}. Monoid a => (Executable -> a) -> a
combine Executable -> BuildInfo
buildInfo
      }
    where
      combine :: (Executable -> a) -> a
combine Executable -> a
field = Executable -> a
field Executable
a a -> a -> a
forall a. Monoid a => a -> a -> a
`mappend` Executable -> a
field Executable
b

emptyExecutable :: Executable
emptyExecutable :: Executable
emptyExecutable = Executable
forall a. Monoid a => a
mempty

-- | Get all the module names from an exe
exeModules :: Executable -> [ModuleName]
exeModules :: Executable -> [ModuleName]
exeModules Executable
exe = BuildInfo -> [ModuleName]
otherModules (Executable -> BuildInfo
buildInfo Executable
exe)

-- | Get all the auto generated module names from an exe
-- This are a subset of 'exeModules'.
exeModulesAutogen :: Executable -> [ModuleName]
exeModulesAutogen :: Executable -> [ModuleName]
exeModulesAutogen Executable
exe = BuildInfo -> [ModuleName]
autogenModules (Executable -> BuildInfo
buildInfo Executable
exe)