Skip to content

Commit 807b9c8

Browse files
committed
Remove push-candidate command
Seems to just duplicate the functionality of `cabal upload`. Closes #65.
1 parent bbf8f0f commit 807b9c8

File tree

1 file changed

+1
-96
lines changed

1 file changed

+1
-96
lines changed

src/Main.hs

Lines changed: 1 addition & 96 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,7 @@
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

1616
import Prelude hiding (log)
1717

@@ -64,7 +64,6 @@ import Options.Applicative as OA
6464
import System.Directory
6565
import System.Environment (lookupEnv)
6666
import System.Exit (ExitCode (..), exitFailure)
67-
import System.FilePath
6867
import System.IO (hPutStrLn, stderr)
6968
import System.IO.Error (tryIOError, isDoesNotExistError)
7069
import qualified System.IO.Streams as Streams
@@ -134,34 +133,6 @@ hackageSendGET p a = do
134133
liftIO $ sendRequest c q1 emptyBody
135134
hcReqCnt += 1
136135

137-
hackagePutTgz :: ByteString -> ByteString -> HIO ByteString
138-
hackagePutTgz p tgz = do
139-
q1 <- liftIO $ buildRequest $ do
140-
http PUT p
141-
setUA
142-
-- setAccept "application/json" -- wishful thinking
143-
setContentType "application/x-tar"
144-
-- setContentEncoding "gzip"
145-
setContentLength (fromIntegral $ BS.length tgz)
146-
147-
lft <- use hcReqLeft
148-
unless (lft > 0) $
149-
fail "hackagePutTgz: request budget exhausted for current connection"
150-
151-
c <- openHConn
152-
liftIO $ sendRequest c q1 (bsBody tgz)
153-
resp <- liftIO $ try (receiveResponse c concatHandler')
154-
closeHConn
155-
hcReqCnt += 1
156-
157-
case resp of
158-
Right bs -> -- do
159-
-- liftIO $ BS.writeFile "raw.out" bs
160-
return bs
161-
162-
Left e@HttpClientError {} -> -- do
163-
return (BS8.pack $ show e)
164-
165136
hackageRecvResp :: HIO ByteString
166137
hackageRecvResp = do
167138
c <- openHConn
@@ -253,47 +224,6 @@ instance ToBuilder BSL.ByteString where
253224
bsBody :: ToBuilder a => a -> Streams.OutputStream Builder.Builder -> IO ()
254225
bsBody bs = Streams.write (Just (toBuilder bs))
255226

256-
-- | Upload a candidate to Hackage
257-
--
258-
-- This is a bit overkill, as one could easily just use @curl(1)@ for this:
259-
--
260-
-- > curl --form package=@"$PKGID".tar.gz -u "${CREDS}" https://hackage.haskell.org/packages/candidates/
261-
--
262-
hackagePushCandidate :: (ByteString,ByteString) -> (FilePath,ByteString) -> HIO ByteString
263-
hackagePushCandidate cred (tarname,rawtarball) = do
264-
when (boundary `BS.isInfixOf` rawtarball) $ fail "WTF... tarball contains boundary-pattern"
265-
266-
q1 <- liftIO $ buildRequest $ do
267-
http POST urlpath
268-
setUA
269-
uncurry setAuthorizationBasic cred
270-
setAccept "application/json" -- wishful thinking
271-
setContentType ("multipart/form-data; boundary="<>boundary) -- RFC2388
272-
setContentLength bodyLen
273-
274-
c <- reOpenHConn
275-
276-
liftIO $ sendRequest c q1 (bsBody body)
277-
278-
resp <- liftIO $ try (receiveResponse c (\r is -> (,) r <$> concatHandler r is))
279-
closeHConn
280-
281-
case resp of
282-
Right (rc,bs) -> do
283-
return (BS8.pack (show rc) <> bs)
284-
Left (HttpClientError code bs) -> return (BS8.pack ("code=" <> show code <> "\n") <> bs)
285-
-- Hackage currently timeouts w/ 503 guru meditation errors,
286-
-- which usually means that the transaction has succeeded
287-
where
288-
urlpath = "/packages/candidates/"
289-
290-
body = Builder.toLazyByteString $
291-
multiPartBuilder boundary [ ("package", [("filename", BS8.pack tarname)]
292-
, ["Content-Type: application/gzip"], rawtarball)]
293-
bodyLen = fromIntegral $ BSL.length body
294-
295-
boundary = "4d5bb1565a084d78868ff0178bdf4f61"
296-
297227
-- | Simplified RFC2388 multipart/form-data formatter
298228
--
299229
-- TODO: make a streaming-variant
@@ -498,10 +428,6 @@ data PushCOptions = PushCOptions
498428
, optPsCFiles :: [FilePath]
499429
} deriving Show
500430

501-
data PushPCOptions = PushPCOptions
502-
{ optPPCFiles :: [FilePath]
503-
} deriving Show
504-
505431
data CheckROptions = CheckROptions
506432
{ optCRNew :: FilePath
507433
, optCROrig :: FilePath
@@ -521,7 +447,6 @@ data Command
521447
| PullCabal !PullCOptions
522448
| PushCabal !PushCOptions
523449
| SyncCabal !SyncCOptions
524-
| PushCandidate !PushPCOptions
525450
| CheckRevision !CheckROptions
526451
| IndexShaSum !IndexShaSumOptions
527452
| AddBound !AddBoundOptions
@@ -573,8 +498,6 @@ optionsParserInfo
573498
<*> switch (long "publish" <> help "publish revision (review-mode)")
574499
<*> some (OA.argument str (metavar "CABALFILES..." <> action "file")))
575500

576-
pushpcoParser = PushCandidate <$> (PushPCOptions <$> some (OA.argument str (metavar "TARBALLS..." <> action "file")))
577-
578501
checkrevParsser = CheckRevision <$> (CheckROptions <$> OA.argument str (metavar "NEWCABAL" <> action "file")
579502
<*> OA.argument str (metavar "OLDCABAL" <> action "file"))
580503

@@ -599,8 +522,6 @@ optionsParserInfo
599522
(progDesc "Upload revised .cabal files."))
600523
, command "sync-cabal" (info (helper <*> synccoParser)
601524
(progDesc "Update/sync local .cabal file with latest revision on Hackage."))
602-
, command "push-candidate" (info (helper <*> pushpcoParser)
603-
(progDesc "Upload package candidate(s)."))
604525
, command "list-versions" (info (helper <*> listcoParser)
605526
(progDesc "List versions for a package."))
606527
, command "check-revision" (info (helper <*> checkrevParsser)
@@ -754,22 +675,6 @@ mainWithOptions Options {..} = do
754675
BS8.putStrLn (tidyHtml tmp)
755676
putStrLn (replicate 80 '=')
756677

757-
PushCandidate (PushPCOptions {..}) -> do
758-
(username,password) <- maybe (fail "missing Hackage credentials") return =<< getHackageCreds
759-
putStrLn $ "Using Hackage credentials for username " ++ show username
760-
761-
forM_ optPPCFiles $ \fn -> do
762-
putStrLn $ "reading " ++ show fn ++ " ..."
763-
rawtar <- BS.readFile fn
764-
putStrLn $ "uplading to Hackage..."
765-
tmp <- runHConn (hackagePushCandidate (username,password) (takeFileName fn, rawtar))
766-
767-
putStrLn "Hackage response was:"
768-
putStrLn (replicate 80 '=')
769-
BS8.putStrLn tmp
770-
putStrLn (replicate 80 '=')
771-
772-
773678
CheckRevision (CheckROptions {..}) -> do
774679
old <- BS.readFile optCROrig
775680
new <- BS.readFile optCRNew

0 commit comments

Comments
 (0)