{-# LANGUAGE OverloadedRecordDot #-}
module Cloudy.Cmd.CopyFile where
import Cloudy.Cli (CopyFileCliOpts (..), CopyFileDirection (..), Recursive (..))
import Cloudy.Cmd.Utils (SelectInstBy, findInstanceInfoForSelectInstBy, mkSelectInstBy)
import Cloudy.LocalConfFile (LocalConfFileOpts (..))
import Cloudy.Db (withCloudyDb, InstanceInfo (..), ScalewayInstance (..))
import Data.Text (unpack, Text)
import Data.Void (absurd)
import System.Posix.Process (executeFile)
import Control.Monad (when)
import Control.FromSum (fromMaybeM)
data CopyFileSettings = CopyFileSettings
{ CopyFileSettings -> SelectInstBy
selectInstBy :: SelectInstBy
, CopyFileSettings -> CopyFileDirection
direction :: CopyFileDirection
, CopyFileSettings -> Recursive
recursive :: Recursive
, CopyFileSettings -> [Text]
filesToCopyArgs :: [Text]
}
deriving stock Int -> CopyFileSettings -> ShowS
[CopyFileSettings] -> ShowS
CopyFileSettings -> String
(Int -> CopyFileSettings -> ShowS)
-> (CopyFileSettings -> String)
-> ([CopyFileSettings] -> ShowS)
-> Show CopyFileSettings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CopyFileSettings -> ShowS
showsPrec :: Int -> CopyFileSettings -> ShowS
$cshow :: CopyFileSettings -> String
show :: CopyFileSettings -> String
$cshowList :: [CopyFileSettings] -> ShowS
showList :: [CopyFileSettings] -> ShowS
Show
mkSettings :: LocalConfFileOpts -> CopyFileCliOpts -> IO CopyFileSettings
mkSettings :: LocalConfFileOpts -> CopyFileCliOpts -> IO CopyFileSettings
mkSettings LocalConfFileOpts
_localConfFileOpts CopyFileCliOpts
cliOpts = do
SelectInstBy
selectInstBy <- Maybe CloudyInstanceId -> Maybe Text -> IO SelectInstBy
mkSelectInstBy CopyFileCliOpts
cliOpts.id CopyFileCliOpts
cliOpts.name
CopyFileSettings -> IO CopyFileSettings
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
CopyFileSettings
{ SelectInstBy
$sel:selectInstBy:CopyFileSettings :: SelectInstBy
selectInstBy :: SelectInstBy
selectInstBy
, $sel:direction:CopyFileSettings :: CopyFileDirection
direction = CopyFileCliOpts
cliOpts.direction
, $sel:recursive:CopyFileSettings :: Recursive
recursive = CopyFileCliOpts
cliOpts.recursive
, $sel:filesToCopyArgs:CopyFileSettings :: [Text]
filesToCopyArgs = CopyFileCliOpts
cliOpts.filesToCopyArgs
}
runCopyFile :: LocalConfFileOpts -> CopyFileCliOpts -> IO ()
runCopyFile :: LocalConfFileOpts -> CopyFileCliOpts -> IO ()
runCopyFile LocalConfFileOpts
localConfFileOpts CopyFileCliOpts
cliOpts = do
CopyFileSettings
settings <- LocalConfFileOpts -> CopyFileCliOpts -> IO CopyFileSettings
mkSettings LocalConfFileOpts
localConfFileOpts CopyFileCliOpts
cliOpts
Text
ipAddr <- (Connection -> IO Text) -> IO Text
forall a. (Connection -> IO a) -> IO a
withCloudyDb ((Connection -> IO Text) -> IO Text)
-> (Connection -> IO Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ \Connection
conn -> do
InstanceInfo
instanceInfo <- Connection -> SelectInstBy -> IO InstanceInfo
findInstanceInfoForSelectInstBy Connection
conn CopyFileSettings
settings.selectInstBy
case InstanceInfo
instanceInfo of
CloudyAwsInstance CloudyInstance
_cloudyInstance Void
void -> Void -> IO Text
forall a. Void -> a
absurd Void
void
CloudyScalewayInstance CloudyInstance
_cloudyInstance ScalewayInstance
scalewayInstance -> Text -> IO Text
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ScalewayInstance
scalewayInstance.scalewayIpAddress
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([Text] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length CopyFileSettings
settings.filesToCopyArgs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
1) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
String -> IO ()
forall a. HasCallStack => String -> a
error String
"ERROR: must pass at least 2 files"
([Text]
firstFiles, Text
lastFile) <-
IO ([Text], Text) -> Maybe ([Text], Text) -> IO ([Text], Text)
forall (m :: * -> *) a. Applicative m => m a -> Maybe a -> m a
fromMaybeM
(String -> IO ([Text], Text)
forall a. HasCallStack => String -> a
error String
"ERROR: unsnoc should have succeeded since we check there are at least 2 files")
([Text] -> Maybe ([Text], Text)
forall a. [a] -> Maybe ([a], a)
unsnoc CopyFileSettings
settings.filesToCopyArgs)
let recursiveArg :: [Text]
recursiveArg =
case CopyFileSettings
settings.recursive of
Recursive
Recursive -> [Text
"-r"]
Recursive
NoRecursive -> []
scpFilesArgs :: [Text]
scpFilesArgs =
case CopyFileSettings
settings.direction of
CopyFileDirection
FromInstanceToLocal ->
(Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Text
file -> Text
"root@" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
ipAddr Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
file) [Text]
firstFiles [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<>
[Text
lastFile]
CopyFileDirection
ToInstanceFromLocal -> [Text]
firstFiles [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> [Text
"root@" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
ipAddr Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
lastFile]
scpArgs :: [String]
scpArgs =
(Text -> String) -> [Text] -> [String]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> String
unpack ([Text] -> [String]) -> [Text] -> [String]
forall a b. (a -> b) -> a -> b
$ [Text]
recursiveArg [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> [Text]
scpFilesArgs
String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"About to run scp command: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> [String] -> String
forall a. Show a => a -> String
show (String
"scp" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
scpArgs)
String -> Bool -> [String] -> Maybe [(String, String)] -> IO ()
forall a.
String -> Bool -> [String] -> Maybe [(String, String)] -> IO a
executeFile String
"scp" Bool
True [String]
scpArgs Maybe [(String, String)]
forall a. Maybe a
Nothing
unsnoc :: [a] -> Maybe ([a], a)
unsnoc :: forall a. [a] -> Maybe ([a], a)
unsnoc = (a -> Maybe ([a], a) -> Maybe ([a], a))
-> Maybe ([a], a) -> [a] -> Maybe ([a], a)
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\a
x -> ([a], a) -> Maybe ([a], a)
forall a. a -> Maybe a
Just (([a], a) -> Maybe ([a], a))
-> (Maybe ([a], a) -> ([a], a)) -> Maybe ([a], a) -> Maybe ([a], a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([a], a) -> (([a], a) -> ([a], a)) -> Maybe ([a], a) -> ([a], a)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([], a
x) (\(~([a]
a, a
b)) -> (a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
a, a
b))) Maybe ([a], a)
forall a. Maybe a
Nothing