{-# LANGUAGE TupleSections #-}
module Input.Download(downloadInput) where
import System.FilePath
import Control.Monad.Extra
import System.Directory
import Data.Conduit.Binary (sinkFile)
import qualified Network.HTTP.Conduit as C
import Network.Connection
import qualified Data.Conduit as C
import General.Util
import General.Timing
import Control.Monad.Trans.Resource
import Control.Exception.Extra
downloadInput :: Timing -> Bool -> Maybe Bool -> FilePath -> String -> URL -> IO FilePath
downloadInput :: Timing
-> Bool
-> Maybe Bool
-> FilePath
-> FilePath
-> FilePath
-> IO FilePath
downloadInput Timing
timing Bool
insecure Maybe Bool
download FilePath
dir FilePath
name FilePath
url = do
    let file :: FilePath
file = FilePath
dir FilePath -> FilePath -> FilePath
</> FilePath
"input-" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
name
    Bool
exists <- FilePath -> IO Bool
doesFileExist FilePath
file
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
exists Bool -> Bool -> Bool
&& Maybe Bool
download Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
False) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
        FilePath -> IO ()
forall a. Partial => FilePath -> IO a
errorIO (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"File is not already downloaded and --download=no given, downloading " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
url FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" to " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
exists Bool -> Bool -> Bool
|| Maybe Bool
download Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
        Timing -> FilePath -> IO () -> IO ()
forall (m :: * -> *) a.
MonadIO m =>
Timing -> FilePath -> m a -> m a
timed Timing
timing (FilePath
"Downloading " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
url) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
            Bool -> FilePath -> FilePath -> IO ()
downloadFile Bool
insecure (FilePath
file FilePath -> FilePath -> FilePath
<.> FilePath
"part") FilePath
url
            FilePath -> FilePath -> IO ()
renameFile (FilePath
file FilePath -> FilePath -> FilePath
<.> FilePath
"part") FilePath
file
    FilePath -> IO FilePath
forall (f :: * -> *) a. Applicative f => a -> f a
pure FilePath
file
downloadFile :: Bool -> FilePath -> String -> IO ()
downloadFile :: Bool -> FilePath -> FilePath -> IO ()
downloadFile Bool
insecure FilePath
file FilePath
url = do
    let request :: Request
request = FilePath -> Request
C.parseRequest_ FilePath
url
    Manager
manager <- ManagerSettings -> IO Manager
C.newManager (ManagerSettings -> IO Manager) -> ManagerSettings -> IO Manager
forall a b. (a -> b) -> a -> b
$ TLSSettings -> Maybe SockSettings -> ManagerSettings
C.mkManagerSettings (Bool -> Bool -> Bool -> TLSSettings
TLSSettingsSimple Bool
insecure Bool
False Bool
False) Maybe SockSettings
forall a. Maybe a
Nothing
    ResourceT IO () -> IO ()
forall (m :: * -> *) a. MonadUnliftIO m => ResourceT m a -> m a
runResourceT (ResourceT IO () -> IO ()) -> ResourceT IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
        Response (ConduitM () ByteString (ResourceT IO) ())
response <- Request
-> Manager
-> ResourceT
     IO (Response (ConduitM () ByteString (ResourceT IO) ()))
forall (m :: * -> *) i.
MonadResource m =>
Request -> Manager -> m (Response (ConduitM i ByteString m ()))
C.http Request
request Manager
manager
        ConduitT () Void (ResourceT IO) () -> ResourceT IO ()
forall (m :: * -> *) r. Monad m => ConduitT () Void m r -> m r
C.runConduit (ConduitT () Void (ResourceT IO) () -> ResourceT IO ())
-> ConduitT () Void (ResourceT IO) () -> ResourceT IO ()
forall a b. (a -> b) -> a -> b
$ Response (ConduitM () ByteString (ResourceT IO) ())
-> ConduitM () ByteString (ResourceT IO) ()
forall body. Response body -> body
C.responseBody Response (ConduitM () ByteString (ResourceT IO) ())
response ConduitM () ByteString (ResourceT IO) ()
-> ConduitM ByteString Void (ResourceT IO) ()
-> ConduitT () Void (ResourceT IO) ()
forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
C..| FilePath -> ConduitM ByteString Void (ResourceT IO) ()
forall (m :: * -> *) o.
MonadResource m =>
FilePath -> ConduitT ByteString o m ()
sinkFile FilePath
file