{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Distribution.Simple.Program.Types (
Program(..),
ProgramSearchPath,
ProgramSearchPathEntry(..),
simpleProgram,
ConfiguredProgram(..),
programPath,
suppressOverrideArgs,
ProgArg,
ProgramLocation(..),
simpleConfiguredProgram,
) where
import Prelude ()
import Distribution.Compat.Prelude
import Distribution.PackageDescription
import Distribution.Simple.Program.Find
import Distribution.Version
import Distribution.Verbosity
import qualified Data.Map as Map
data Program = Program {
Program -> String
programName :: String,
Program
-> Verbosity -> ProgramSearchPath -> IO (Maybe (String, [String]))
Evidence bound by a HsWrapper of the constraint type HasCallStack
Evidence bound by a HsWrapper of the constraint type HasCallStack
programFindLocation :: Verbosity -> ProgramSearchPath
-> IO (Maybe (FilePath, [FilePath])),
Program -> Verbosity -> String -> IO (Maybe Version)
Evidence bound by a HsWrapper of the constraint type HasCallStack
Evidence bound by a HsWrapper of the constraint type HasCallStack
programFindVersion :: Verbosity -> FilePath -> IO (Maybe Version),
Program -> Verbosity -> ConfiguredProgram -> IO ConfiguredProgram
Evidence bound by a HsWrapper of the constraint type HasCallStack
Evidence bound by a HsWrapper of the constraint type HasCallStack
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
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
/= :: ConfiguredProgram -> ConfiguredProgram -> Bool
$c/= :: ConfiguredProgram -> ConfiguredProgram -> Bool
== :: ConfiguredProgram -> ConfiguredProgram -> Bool
$c== :: ConfiguredProgram -> ConfiguredProgram -> Bool
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
External instance of the constraint type Eq Version
External instance of the constraint type Eq Char
External instance of the constraint type forall k a. (Eq k, Eq a) => Eq (Map k a)
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type Eq Version
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type Eq Char
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
Instance of class: Eq of the constraint type Eq ProgramLocation
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
$cto :: forall x. Rep ConfiguredProgram x -> ConfiguredProgram
$cfrom :: forall x. ConfiguredProgram -> Rep ConfiguredProgram x
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
readListPrec :: ReadPrec [ConfiguredProgram]
$creadListPrec :: ReadPrec [ConfiguredProgram]
readPrec :: ReadPrec ConfiguredProgram
$creadPrec :: ReadPrec ConfiguredProgram
readList :: ReadS [ConfiguredProgram]
$creadList :: ReadS [ConfiguredProgram]
readsPrec :: Int -> ReadS ConfiguredProgram
$creadsPrec :: Int -> ReadS ConfiguredProgram
External instance of the constraint type Ord Char
External instance of the constraint type Ord Char
External instance of the constraint type forall a. Ord a => Ord [a]
External instance of the constraint type forall a. Read a => Read (Maybe a)
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Char
External instance of the constraint type forall a b. (Read a, Read b) => Read (a, b)
External instance of the constraint type Read Version
External instance of the constraint type Read Char
External instance of the constraint type forall a. Ord a => Ord [a]
External instance of the constraint type Ord Char
External instance of the constraint type forall k e. (Ord k, Read k, Read e) => Read (Map k e)
External instance of the constraint type forall a b. (Read a, Read b) => Read (a, b)
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Char
External instance of the constraint type forall a. Read a => Read (Maybe a)
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Char
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Char
External instance of the constraint type Read Version
External instance of the constraint type forall a. Read a => Read (Maybe a)
External instance of the constraint type Read Char
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Char
External instance of the constraint type Monad ReadPrec
External instance of the constraint type Monad ReadPrec
Instance of class: Read of the constraint type Read ProgramLocation
Instance of class: Read of the constraint type Read 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
showList :: [ConfiguredProgram] -> ShowS
$cshowList :: [ConfiguredProgram] -> ShowS
show :: ConfiguredProgram -> String
$cshow :: ConfiguredProgram -> String
showsPrec :: Int -> ConfiguredProgram -> ShowS
$cshowsPrec :: Int -> ConfiguredProgram -> ShowS
External instance of the constraint type forall a. Show a => Show (Maybe a)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type forall a b. (Show a, Show b) => Show (a, b)
External instance of the constraint type Show Version
External instance of the constraint type Show Char
External instance of the constraint type forall k a. (Show k, Show a) => Show (Map k a)
External instance of the constraint type forall a b. (Show a, Show b) => Show (a, b)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type forall a. Show a => Show (Maybe a)
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type Show Version
External instance of the constraint type forall a. Show a => Show (Maybe a)
External instance of the constraint type Show Char
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type Ord Int
Instance of class: Show of the constraint type Show ProgramLocation
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
/= :: ProgramLocation -> ProgramLocation -> Bool
$c/= :: ProgramLocation -> ProgramLocation -> Bool
== :: ProgramLocation -> ProgramLocation -> Bool
$c== :: ProgramLocation -> ProgramLocation -> Bool
External instance of the constraint type Eq Char
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type Eq Char
External instance of the constraint type forall a. Eq a => Eq [a]
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
$cto :: forall x. Rep ProgramLocation x -> ProgramLocation
$cfrom :: forall x. ProgramLocation -> Rep ProgramLocation x
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
readListPrec :: ReadPrec [ProgramLocation]
$creadListPrec :: ReadPrec [ProgramLocation]
readPrec :: ReadPrec ProgramLocation
$creadPrec :: ReadPrec ProgramLocation
readList :: ReadS [ProgramLocation]
$creadList :: ReadS [ProgramLocation]
readsPrec :: Int -> ReadS ProgramLocation
$creadsPrec :: Int -> ReadS ProgramLocation
External instance of the constraint type Read Char
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Char
External instance of the constraint type Monad ReadPrec
External instance of the constraint type Read Char
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Monad ReadPrec
Instance of class: Read of the constraint type Read 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
showList :: [ProgramLocation] -> ShowS
$cshowList :: [ProgramLocation] -> ShowS
show :: ProgramLocation -> String
$cshow :: ProgramLocation -> String
showsPrec :: Int -> ProgramLocation -> ShowS
$cshowsPrec :: Int -> ProgramLocation -> ShowS
External instance of the constraint type Show Char
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Char
External instance of the constraint type Ord Int
External instance of the constraint type Show Char
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Ord Int
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 :: [String]
programOverrideArgs = [] }
simpleProgram :: String -> Program
simpleProgram :: String -> Program
simpleProgram String
name = Program :: String
-> (Verbosity
-> ProgramSearchPath -> IO (Maybe (String, [String])))
-> (Verbosity -> String -> IO (Maybe Version))
-> (Verbosity -> ConfiguredProgram -> IO ConfiguredProgram)
-> (Maybe Version -> PackageDescription -> [String] -> [String])
-> Program
Program {
programName :: String
programName = String
name,
programFindLocation :: Verbosity -> ProgramSearchPath -> IO (Maybe (String, [String]))
programFindLocation = \Verbosity
v ProgramSearchPath
p -> Verbosity
-> ProgramSearchPath -> String -> IO (Maybe (String, [String]))
findProgramOnSearchPath Verbosity
v ProgramSearchPath
p String
name,
programFindVersion :: Verbosity -> String -> IO (Maybe Version)
programFindVersion = \Verbosity
_ String
_ -> Maybe Version -> IO (Maybe Version)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return Maybe Version
forall a. Maybe a
Nothing,
programPostConf :: Verbosity -> ConfiguredProgram -> IO ConfiguredProgram
programPostConf = \Verbosity
_ ConfiguredProgram
p -> ConfiguredProgram -> IO ConfiguredProgram
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return ConfiguredProgram
p,
programNormaliseArgs :: Maybe Version -> PackageDescription -> [String] -> [String]
programNormaliseArgs = \Maybe Version
_ PackageDescription
_ -> [String] -> [String]
forall a. a -> a
id
}
simpleConfiguredProgram :: String -> ProgramLocation -> ConfiguredProgram
simpleConfiguredProgram :: String -> ProgramLocation -> ConfiguredProgram
simpleConfiguredProgram String
name ProgramLocation
loc = ConfiguredProgram :: String
-> Maybe Version
-> [String]
-> [String]
-> [(String, Maybe String)]
-> Map String String
-> ProgramLocation
-> [String]
-> ConfiguredProgram
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 = []
}