1111-- Copyright : Herbert Valerio Riedel, Andreas Abel
1212-- SPDX-License-Identifier: GPL-3.0-or-later
1313--
14- module Main where
14+ module Main ( main ) where
1515
1616import Prelude hiding (log )
1717
@@ -67,7 +67,6 @@ import Options.Applicative as OA
6767import System.Directory
6868import System.Environment (lookupEnv )
6969import System.Exit (ExitCode (.. ), exitFailure )
70- import System.FilePath
7170import System.IO (hPutStrLn , stderr )
7271import System.IO.Error (tryIOError , isDoesNotExistError )
7372import qualified System.IO.Streams as Streams
@@ -137,34 +136,6 @@ hackageSendGET p a = do
137136 liftIO $ sendRequest c q1 emptyBody
138137 hcReqCnt += 1
139138
140- hackagePutTgz :: ByteString -> ByteString -> HIO ByteString
141- hackagePutTgz p tgz = do
142- q1 <- liftIO $ buildRequest $ do
143- http PUT p
144- setUA
145- -- setAccept "application/json" -- wishful thinking
146- setContentType " application/x-tar"
147- -- setContentEncoding "gzip"
148- setContentLength (fromIntegral $ BS. length tgz)
149-
150- lft <- use hcReqLeft
151- unless (lft > 0 ) $
152- fail " hackagePutTgz: request budget exhausted for current connection"
153-
154- c <- openHConn
155- liftIO $ sendRequest c q1 (bsBody tgz)
156- resp <- liftIO $ try (receiveResponse c concatHandler')
157- closeHConn
158- hcReqCnt += 1
159-
160- case resp of
161- Right bs -> -- do
162- -- liftIO $ BS.writeFile "raw.out" bs
163- return bs
164-
165- Left e@ HttpClientError {} -> -- do
166- return (BS8. pack $ show e)
167-
168139hackageRecvResp :: HIO ByteString
169140hackageRecvResp = do
170141 c <- openHConn
@@ -256,47 +227,6 @@ instance ToBuilder BSL.ByteString where
256227bsBody :: ToBuilder a => a -> Streams. OutputStream Builder. Builder -> IO ()
257228bsBody bs = Streams. write (Just (toBuilder bs))
258229
259- -- | Upload a candidate to Hackage
260- --
261- -- This is a bit overkill, as one could easily just use @curl(1)@ for this:
262- --
263- -- > curl --form package=@"$PKGID".tar.gz -u "${CREDS}" https://hackage.haskell.org/packages/candidates/
264- --
265- hackagePushCandidate :: (ByteString ,ByteString ) -> (FilePath ,ByteString ) -> HIO ByteString
266- hackagePushCandidate cred (tarname,rawtarball) = do
267- when (boundary `BS.isInfixOf` rawtarball) $ fail " WTF... tarball contains boundary-pattern"
268-
269- q1 <- liftIO $ buildRequest $ do
270- http POST urlpath
271- setUA
272- uncurry setAuthorizationBasic cred
273- setAccept " application/json" -- wishful thinking
274- setContentType (" multipart/form-data; boundary=" <> boundary) -- RFC2388
275- setContentLength bodyLen
276-
277- c <- reOpenHConn
278-
279- liftIO $ sendRequest c q1 (bsBody body)
280-
281- resp <- liftIO $ try (receiveResponse c (\ r is -> (,) r <$> concatHandler r is))
282- closeHConn
283-
284- case resp of
285- Right (rc,bs) -> do
286- return (BS8. pack (show rc) <> bs)
287- Left (HttpClientError code bs) -> return (BS8. pack (" code=" <> show code <> " \n " ) <> bs)
288- -- Hackage currently timeouts w/ 503 guru meditation errors,
289- -- which usually means that the transaction has succeeded
290- where
291- urlpath = " /packages/candidates/"
292-
293- body = Builder. toLazyByteString $
294- multiPartBuilder boundary [ (" package" , [(" filename" , BS8. pack tarname)]
295- , [" Content-Type: application/gzip" ], rawtarball)]
296- bodyLen = fromIntegral $ BSL. length body
297-
298- boundary = " 4d5bb1565a084d78868ff0178bdf4f61"
299-
300230-- | Simplified RFC2388 multipart/form-data formatter
301231--
302232-- TODO: make a streaming-variant
@@ -501,10 +431,6 @@ data PushCOptions = PushCOptions
501431 , optPsCFiles :: [FilePath ]
502432 } deriving Show
503433
504- data PushPCOptions = PushPCOptions
505- { optPPCFiles :: [FilePath ]
506- } deriving Show
507-
508434data CheckROptions = CheckROptions
509435 { optCRNew :: FilePath
510436 , optCROrig :: FilePath
@@ -524,7 +450,6 @@ data Command
524450 | PullCabal ! PullCOptions
525451 | PushCabal ! PushCOptions
526452 | SyncCabal ! SyncCOptions
527- | PushCandidate ! PushPCOptions
528453 | CheckRevision ! CheckROptions
529454 | IndexShaSum ! IndexShaSumOptions
530455 | AddBound ! AddBoundOptions
@@ -576,8 +501,6 @@ optionsParserInfo
576501 <*> switch (long " publish" <> help " publish revision (review-mode)" )
577502 <*> some (OA. argument str (metavar " CABALFILES..." <> action " file" )))
578503
579- pushpcoParser = PushCandidate <$> (PushPCOptions <$> some (OA. argument str (metavar " TARBALLS..." <> action " file" )))
580-
581504 checkrevParsser = CheckRevision <$> (CheckROptions <$> OA. argument str (metavar " NEWCABAL" <> action " file" )
582505 <*> OA. argument str (metavar " OLDCABAL" <> action " file" ))
583506
@@ -602,8 +525,6 @@ optionsParserInfo
602525 (progDesc " Upload revised .cabal files." ))
603526 , command " sync-cabal" (info (helper <*> synccoParser)
604527 (progDesc " Update/sync local .cabal file with latest revision on Hackage." ))
605- , command " push-candidate" (info (helper <*> pushpcoParser)
606- (progDesc " Upload package candidate(s)." ))
607528 , command " list-versions" (info (helper <*> listcoParser)
608529 (progDesc " List versions for a package." ))
609530 , command " check-revision" (info (helper <*> checkrevParsser)
@@ -773,22 +694,6 @@ mainWithOptions Options{ optHost, optCommand } = do
773694 BS8. putStrLn (tidyHtml tmp)
774695 putStrLn (replicate 80 ' =' )
775696
776- PushCandidate (PushPCOptions { optPPCFiles }) -> do
777- (username,password) <- maybe (fail " missing Hackage credentials" ) return =<< getHackageCreds
778- putStrLn $ " Using Hackage credentials for username " ++ show username
779-
780- forM_ optPPCFiles $ \ fn -> do
781- putStrLn $ " reading " ++ show fn ++ " ..."
782- rawtar <- BS. readFile fn
783- putStrLn $ " uplading to Hackage..."
784- tmp <- runHConn (hackagePushCandidate (username,password) (takeFileName fn, rawtar))
785-
786- putStrLn " Hackage response was:"
787- putStrLn (replicate 80 ' =' )
788- BS8. putStrLn tmp
789- putStrLn (replicate 80 ' =' )
790-
791-
792697 CheckRevision (CheckROptions { optCRNew, optCROrig }) -> do
793698 old <- BS. readFile optCROrig
794699 new <- BS. readFile optCRNew
0 commit comments