blob: b773f4444e87d5dc71df72fcab56deeea31e9922 (
plain) (
blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
|
{-# LANGUAGE QuasiQuotes #-}
module Tool where
import Data.Error.Tree
import Label
import PossehlAnalyticsPrelude
import System.Environment qualified as Env
import System.Exit qualified as Exit
import System.FilePath ((</>))
import System.Posix qualified as Posix
import ValidationParseT
data Tool = Tool
{ -- | absolute path to the executable
toolPath :: FilePath
}
deriving stock (Show)
-- | Reads all tools from the @toolsEnvVar@ variable or aborts.
readTools ::
Label "toolsEnvVar" Text ->
-- | Parser for Tools we bring with us at build time.
--
-- These are executables that we need available, and that we have to ship with the distribution of @pa-cli@.
ToolParserT IO tools ->
IO tools
readTools env toolParser =
Env.lookupEnv (env.toolsEnvVar & textToString) >>= \case
Nothing -> do
Exit.die [fmt|Please set {env.toolsEnvVar} to a directory with all tools we need (see `Tools` in the code).|]
Just toolsDir ->
(Posix.fileExist toolsDir & ifTrueOrErr () [fmt|{env.toolsEnvVar} directory does not exist: {toolsDir}|])
& thenValidateM
( \() ->
(Posix.getFileStatus toolsDir <&> Posix.isDirectory)
& ifTrueOrErr () [fmt|{env.toolsEnvVar} does not point to a directory: {toolsDir}|]
)
& thenValidateM
(\() -> toolParser.unToolParser toolsDir)
<&> first (errorTree [fmt|Could not find all tools in {env.toolsEnvVar}|])
>>= \case
Failure err -> Exit.die (err & prettyErrorTree & textToString)
Success t -> pure t
newtype ToolParserT m a = ToolParserT
{ unToolParser ::
FilePath ->
m (Validation (NonEmpty Error) a)
}
deriving
(Functor, Applicative)
via (ValidationParseT FilePath m)
-- | Given a file path and the name of the tool executable, see whether it is an executable and return its full path.
readTool :: Text -> ToolParserT IO Tool
readTool exeName = ToolParserT $ \toolDir -> do
let toolPath :: FilePath = toolDir </> (exeName & textToString)
let read' = True
let write = False
let exec = True
Posix.fileExist toolPath
& ifTrueOrErr () [fmt|Tool does not exist: {toolPath}|]
& thenValidateM
( \() ->
Posix.fileAccess toolPath read' write exec
& ifTrueOrErr (Tool {..}) [fmt|Tool is not readable/executable: {toolPath}|]
)
-- | helper
ifTrueOrErr :: (Functor f) => a -> Text -> f Bool -> f (Validation (NonEmpty Error) a)
ifTrueOrErr true err io =
io <&> \case
True -> Success true
False -> Failure $ singleton $ newError err
|