{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
module Distribution.Simple.Program.Types
(
Program (..)
, ProgramSearchPath
, ProgramSearchPathEntry (..)
, ConfiguredProgram (..)
, programPath
, suppressOverrideArgs
, ProgArg
, ProgramLocation (..)
, simpleConfiguredProgram
) where
import Distribution.Compat.Prelude
import Prelude ()
import Distribution.PackageDescription
import Distribution.Verbosity
import Distribution.Version
import qualified Data.Map as Map
data Program = Program
{ Program -> String
programName :: String
, Program
-> Verbosity -> ProgramSearchPath -> IO (Maybe (String, [String]))
programFindLocation
:: Verbosity
-> ProgramSearchPath
-> IO (Maybe (FilePath, [FilePath]))
, Program -> Verbosity -> String -> IO (Maybe Version)
programFindVersion :: Verbosity -> FilePath -> IO (Maybe Version)
, Program -> Verbosity -> ConfiguredProgram -> IO ConfiguredProgram
programPostConf :: Verbosity -> ConfiguredProgram -> IO ConfiguredProgram
, Program
-> Maybe Version -> PackageDescription -> [String] -> [String]
programNormaliseArgs :: Maybe Version -> PackageDescription -> [String] -> [String]
}
instance Show Program where
show :: Program -> String
show (Program String
name Verbosity -> ProgramSearchPath -> IO (Maybe (String, [String]))
_ Verbosity -> String -> IO (Maybe Version)
_ Verbosity -> ConfiguredProgram -> IO ConfiguredProgram
_ Maybe Version -> PackageDescription -> [String] -> [String]
_) = String
"Program: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
name
type ProgArg = String
type ProgramSearchPath = [ProgramSearchPathEntry]
data ProgramSearchPathEntry
=
ProgramSearchPathDir FilePath
|
ProgramSearchPathDefault
deriving (Int -> ProgramSearchPathEntry -> ShowS
ProgramSearchPath -> ShowS
ProgramSearchPathEntry -> String
(Int -> ProgramSearchPathEntry -> ShowS)
-> (ProgramSearchPathEntry -> String)
-> (ProgramSearchPath -> ShowS)
-> Show ProgramSearchPathEntry
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProgramSearchPathEntry -> ShowS
showsPrec :: Int -> ProgramSearchPathEntry -> ShowS
$cshow :: ProgramSearchPathEntry -> String
show :: ProgramSearchPathEntry -> String
$cshowList :: ProgramSearchPath -> ShowS
showList :: ProgramSearchPath -> ShowS
Show, ProgramSearchPathEntry -> ProgramSearchPathEntry -> Bool
(ProgramSearchPathEntry -> ProgramSearchPathEntry -> Bool)
-> (ProgramSearchPathEntry -> ProgramSearchPathEntry -> Bool)
-> Eq ProgramSearchPathEntry
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProgramSearchPathEntry -> ProgramSearchPathEntry -> Bool
== :: ProgramSearchPathEntry -> ProgramSearchPathEntry -> Bool
$c/= :: ProgramSearchPathEntry -> ProgramSearchPathEntry -> Bool
/= :: ProgramSearchPathEntry -> ProgramSearchPathEntry -> Bool
Eq, (forall x. ProgramSearchPathEntry -> Rep ProgramSearchPathEntry x)
-> (forall x.
Rep ProgramSearchPathEntry x -> ProgramSearchPathEntry)
-> Generic ProgramSearchPathEntry
forall x. Rep ProgramSearchPathEntry x -> ProgramSearchPathEntry
forall x. ProgramSearchPathEntry -> Rep ProgramSearchPathEntry x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ProgramSearchPathEntry -> Rep ProgramSearchPathEntry x
from :: forall x. ProgramSearchPathEntry -> Rep ProgramSearchPathEntry x
$cto :: forall x. Rep ProgramSearchPathEntry x -> ProgramSearchPathEntry
to :: forall x. Rep ProgramSearchPathEntry x -> ProgramSearchPathEntry
Generic, Typeable)
instance Binary ProgramSearchPathEntry
instance Structured ProgramSearchPathEntry
data ConfiguredProgram = ConfiguredProgram
{ ConfiguredProgram -> String
programId :: String
, ConfiguredProgram -> Maybe Version
programVersion :: Maybe Version
, ConfiguredProgram -> [String]
programDefaultArgs :: [String]
, ConfiguredProgram -> [String]
programOverrideArgs :: [String]
, ConfiguredProgram -> [(String, Maybe String)]
programOverrideEnv :: [(String, Maybe String)]
, ConfiguredProgram -> Map String String
programProperties :: Map.Map String String
, ConfiguredProgram -> ProgramLocation
programLocation :: ProgramLocation
, ConfiguredProgram -> [String]
programMonitorFiles :: [FilePath]
}
deriving (ConfiguredProgram -> ConfiguredProgram -> Bool
(ConfiguredProgram -> ConfiguredProgram -> Bool)
-> (ConfiguredProgram -> ConfiguredProgram -> Bool)
-> Eq ConfiguredProgram
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConfiguredProgram -> ConfiguredProgram -> Bool
== :: ConfiguredProgram -> ConfiguredProgram -> Bool
$c/= :: ConfiguredProgram -> ConfiguredProgram -> Bool
/= :: ConfiguredProgram -> ConfiguredProgram -> Bool
Eq, (forall x. ConfiguredProgram -> Rep ConfiguredProgram x)
-> (forall x. Rep ConfiguredProgram x -> ConfiguredProgram)
-> Generic ConfiguredProgram
forall x. Rep ConfiguredProgram x -> ConfiguredProgram
forall x. ConfiguredProgram -> Rep ConfiguredProgram x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ConfiguredProgram -> Rep ConfiguredProgram x
from :: forall x. ConfiguredProgram -> Rep ConfiguredProgram x
$cto :: forall x. Rep ConfiguredProgram x -> ConfiguredProgram
to :: forall x. Rep ConfiguredProgram x -> ConfiguredProgram
Generic, ReadPrec [ConfiguredProgram]
ReadPrec ConfiguredProgram
Int -> ReadS ConfiguredProgram
ReadS [ConfiguredProgram]
(Int -> ReadS ConfiguredProgram)
-> ReadS [ConfiguredProgram]
-> ReadPrec ConfiguredProgram
-> ReadPrec [ConfiguredProgram]
-> Read ConfiguredProgram
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ConfiguredProgram
readsPrec :: Int -> ReadS ConfiguredProgram
$creadList :: ReadS [ConfiguredProgram]
readList :: ReadS [ConfiguredProgram]
$creadPrec :: ReadPrec ConfiguredProgram
readPrec :: ReadPrec ConfiguredProgram
$creadListPrec :: ReadPrec [ConfiguredProgram]
readListPrec :: ReadPrec [ConfiguredProgram]
Read, Int -> ConfiguredProgram -> ShowS
[ConfiguredProgram] -> ShowS
ConfiguredProgram -> String
(Int -> ConfiguredProgram -> ShowS)
-> (ConfiguredProgram -> String)
-> ([ConfiguredProgram] -> ShowS)
-> Show ConfiguredProgram
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConfiguredProgram -> ShowS
showsPrec :: Int -> ConfiguredProgram -> ShowS
$cshow :: ConfiguredProgram -> String
show :: ConfiguredProgram -> String
$cshowList :: [ConfiguredProgram] -> ShowS
showList :: [ConfiguredProgram] -> ShowS
Show, Typeable)
instance Binary ConfiguredProgram
instance Structured ConfiguredProgram
data ProgramLocation
=
UserSpecified {ProgramLocation -> String
locationPath :: FilePath}
|
FoundOnSystem {locationPath :: FilePath}
deriving (ProgramLocation -> ProgramLocation -> Bool
(ProgramLocation -> ProgramLocation -> Bool)
-> (ProgramLocation -> ProgramLocation -> Bool)
-> Eq ProgramLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProgramLocation -> ProgramLocation -> Bool
== :: ProgramLocation -> ProgramLocation -> Bool
$c/= :: ProgramLocation -> ProgramLocation -> Bool
/= :: ProgramLocation -> ProgramLocation -> Bool
Eq, (forall x. ProgramLocation -> Rep ProgramLocation x)
-> (forall x. Rep ProgramLocation x -> ProgramLocation)
-> Generic ProgramLocation
forall x. Rep ProgramLocation x -> ProgramLocation
forall x. ProgramLocation -> Rep ProgramLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ProgramLocation -> Rep ProgramLocation x
from :: forall x. ProgramLocation -> Rep ProgramLocation x
$cto :: forall x. Rep ProgramLocation x -> ProgramLocation
to :: forall x. Rep ProgramLocation x -> ProgramLocation
Generic, ReadPrec [ProgramLocation]
ReadPrec ProgramLocation
Int -> ReadS ProgramLocation
ReadS [ProgramLocation]
(Int -> ReadS ProgramLocation)
-> ReadS [ProgramLocation]
-> ReadPrec ProgramLocation
-> ReadPrec [ProgramLocation]
-> Read ProgramLocation
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ProgramLocation
readsPrec :: Int -> ReadS ProgramLocation
$creadList :: ReadS [ProgramLocation]
readList :: ReadS [ProgramLocation]
$creadPrec :: ReadPrec ProgramLocation
readPrec :: ReadPrec ProgramLocation
$creadListPrec :: ReadPrec [ProgramLocation]
readListPrec :: ReadPrec [ProgramLocation]
Read, Int -> ProgramLocation -> ShowS
[ProgramLocation] -> ShowS
ProgramLocation -> String
(Int -> ProgramLocation -> ShowS)
-> (ProgramLocation -> String)
-> ([ProgramLocation] -> ShowS)
-> Show ProgramLocation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProgramLocation -> ShowS
showsPrec :: Int -> ProgramLocation -> ShowS
$cshow :: ProgramLocation -> String
show :: ProgramLocation -> String
$cshowList :: [ProgramLocation] -> ShowS
showList :: [ProgramLocation] -> ShowS
Show, Typeable)
instance Binary ProgramLocation
instance Structured ProgramLocation
programPath :: ConfiguredProgram -> FilePath
programPath :: ConfiguredProgram -> String
programPath = ProgramLocation -> String
locationPath (ProgramLocation -> String)
-> (ConfiguredProgram -> ProgramLocation)
-> ConfiguredProgram
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfiguredProgram -> ProgramLocation
programLocation
suppressOverrideArgs :: ConfiguredProgram -> ConfiguredProgram
suppressOverrideArgs :: ConfiguredProgram -> ConfiguredProgram
suppressOverrideArgs ConfiguredProgram
prog = ConfiguredProgram
prog{programOverrideArgs = []}
simpleConfiguredProgram :: String -> ProgramLocation -> ConfiguredProgram
simpleConfiguredProgram :: String -> ProgramLocation -> ConfiguredProgram
simpleConfiguredProgram String
name ProgramLocation
loc =
ConfiguredProgram
{ programId :: String
programId = String
name
, programVersion :: Maybe Version
programVersion = Maybe Version
forall a. Maybe a
Nothing
, programDefaultArgs :: [String]
programDefaultArgs = []
, programOverrideArgs :: [String]
programOverrideArgs = []
, programOverrideEnv :: [(String, Maybe String)]
programOverrideEnv = []
, programProperties :: Map String String
programProperties = Map String String
forall k a. Map k a
Map.empty
, programLocation :: ProgramLocation
programLocation = ProgramLocation
loc
, programMonitorFiles :: [String]
programMonitorFiles = []
}