remove 3 build flags

* Removed the webapp-secure build flag, rolling it into the webapp build
  flag.
* Removed the quvi and tahoe build flags, which only adds aeson to
  the core dependencies.
* Removed the feed build flag, which only adds feed to the core
  dependencies.

Build flags have cost in both code complexity and also make Setup configure
have to work harder to find a usable set of build flags when some
dependencies are missing.
This commit is contained in:
Joey Hess 2016-01-26 08:14:57 -04:00
parent 36e05945b8
commit f051b51645
Failed to extract signature
11 changed files with 27 additions and 130 deletions

View file

@ -5,7 +5,7 @@
- Licensed under the GNU GPL version 3 or higher.
-}
{-# LANGUAGE CPP, GeneralizedNewtypeDeriving, PackageImports, BangPatterns #-}
{-# LANGUAGE GeneralizedNewtypeDeriving, PackageImports, BangPatterns #-}
module Annex (
Annex,
@ -62,9 +62,7 @@ import Types.LockCache
import Types.DesktopNotify
import Types.CleanupActions
import qualified Database.Keys.Handle as Keys
#ifdef WITH_QUVI
import Utility.Quvi (QuviVersion)
#endif
import Utility.InodeCache
import Utility.Url
@ -130,9 +128,7 @@ data AnnexState = AnnexState
, errcounter :: Integer
, unusedkeys :: Maybe (S.Set Key)
, tempurls :: M.Map Key URLString
#ifdef WITH_QUVI
, quviversion :: Maybe QuviVersion
#endif
, existinghooks :: M.Map Git.Hook.Hook Bool
, desktopnotify :: DesktopNotify
, workers :: [Either AnnexState (Async AnnexState)]
@ -177,9 +173,7 @@ newState c r = AnnexState
, errcounter = 0
, unusedkeys = Nothing
, tempurls = M.empty
#ifdef WITH_QUVI
, quviversion = Nothing
#endif
, existinghooks = M.empty
, desktopnotify = mempty
, workers = []

View file

@ -127,13 +127,9 @@ myUrl tlssettings webapp addr = unpack $ yesodRender webapp urlbase DashboardR [
getTlsSettings :: Annex (Maybe TLS.TLSSettings)
getTlsSettings = do
#ifdef WITH_WEBAPP_SECURE
cert <- fromRepo gitAnnexWebCertificate
privkey <- fromRepo gitAnnexWebPrivKey
ifM (liftIO $ allM doesFileExist [cert, privkey])
( return $ Just $ TLS.tlsSettings cert privkey
, return Nothing
)
#else
return Nothing
#endif

View file

@ -22,9 +22,6 @@ buildFlags = filter (not . null)
#else
#warning Building without the webapp. You probably need to install Yesod..
#endif
#ifdef WITH_WEBAPP_SECURE
, "Webapp-secure"
#endif
#ifdef WITH_PAIRING
, "Pairing"
#else
@ -79,16 +76,6 @@ buildFlags = filter (not . null)
#ifdef WITH_DNS
, "DNS"
#endif
#ifdef WITH_FEED
, "Feeds"
#else
#warning Building without Feeds.
#endif
#ifdef WITH_QUVI
, "Quvi"
#else
#warning Building without quvi.
#endif
#ifdef WITH_TDFA
, "TDFA"
#endif
@ -98,4 +85,8 @@ buildFlags = filter (not . null)
#ifdef WITH_EKG
, "EKG"
#endif
-- Always enabled now, but users may be used to seeing these flags
-- listed.
, "Feeds"
, "Quvi"
]

View file

@ -85,9 +85,7 @@ import qualified Command.Vicfg
import qualified Command.Sync
import qualified Command.Mirror
import qualified Command.AddUrl
#ifdef WITH_FEED
import qualified Command.ImportFeed
#endif
import qualified Command.RmUrl
import qualified Command.Import
import qualified Command.Map
@ -138,9 +136,7 @@ cmds testoptparser testrunner =
, Command.Sync.cmd
, Command.Mirror.cmd
, Command.AddUrl.cmd
#ifdef WITH_FEED
, Command.ImportFeed.cmd
#endif
, Command.RmUrl.cmd
, Command.Import.cmd
, Command.Init.cmd

View file

@ -5,8 +5,6 @@
- Licensed under the GNU GPL version 3 or higher.
-}
{-# LANGUAGE CPP #-}
module Command.AddUrl where
import Network.URI
@ -32,10 +30,8 @@ import Annex.FileMatcher
import Logs.Location
import Utility.Metered
import qualified Annex.Transfer as Transfer
#ifdef WITH_QUVI
import Annex.Quvi
import qualified Utility.Quvi as Quvi
#endif
cmd :: Command
cmd = notBareRepo $ withGlobalOptions [jobsOption, jsonOption] $
@ -192,15 +188,10 @@ startWeb o s = go $ fromMaybe bad $ parseURI urlstring
Url.parseURIRelaxed $ urlstring
go url = case downloader of
QuviDownloader -> usequvi
_ ->
#ifdef WITH_QUVI
ifM (quviSupported urlstring)
( usequvi
, regulardownload url
)
#else
regulardownload url
#endif
_ -> ifM (quviSupported urlstring)
( usequvi
, regulardownload url
)
regulardownload url = do
pathmax <- liftIO $ fileNameLengthLimit "."
urlinfo <- if relaxedOption o
@ -219,7 +210,6 @@ startWeb o s = go $ fromMaybe bad $ parseURI urlstring
)
showStart "addurl" file
next $ performWeb (relaxedOption o) urlstring file urlinfo
#ifdef WITH_QUVI
badquvi = error $ "quvi does not know how to download url " ++ urlstring
usequvi = do
page <- fromMaybe badquvi
@ -231,9 +221,6 @@ startWeb o s = go $ fromMaybe bad $ parseURI urlstring
Quvi.pageTitle page ++ "." ++ fromMaybe "m" (Quvi.linkSuffix link)
showStart "addurl" file
next $ performQuvi (relaxedOption o) urlstring (Quvi.linkUrl link) file
#else
usequvi = error "not built with quvi support"
#endif
performWeb :: Bool -> URLString -> FilePath -> Url.UrlInfo -> CommandPerform
performWeb relaxed url file urlinfo = ifAnnexed file addurl geturl
@ -242,7 +229,6 @@ performWeb relaxed url file urlinfo = ifAnnexed file addurl geturl
addurl = addUrlChecked relaxed url webUUID $ \k -> return $
(Url.urlExists urlinfo, Url.urlSize urlinfo == keySize k)
#ifdef WITH_QUVI
performQuvi :: Bool -> URLString -> URLString -> FilePath -> CommandPerform
performQuvi relaxed pageurl videourl file = ifAnnexed file addurl geturl
where
@ -251,9 +237,7 @@ performQuvi relaxed pageurl videourl file = ifAnnexed file addurl geturl
cleanup webUUID quviurl file key Nothing
return True
geturl = next $ isJust <$> addUrlFileQuvi relaxed quviurl videourl file
#endif
#ifdef WITH_QUVI
addUrlFileQuvi :: Bool -> URLString -> URLString -> FilePath -> Annex (Maybe Key)
addUrlFileQuvi relaxed quviurl videourl file = stopUnless (doesNotExist file) $ do
let key = Backend.URL.fromUrl quviurl Nothing
@ -282,7 +266,6 @@ addUrlFileQuvi relaxed quviurl videourl file = stopUnless (doesNotExist file) $
return (Just key)
else return Nothing
)
#endif
addUrlChecked :: Bool -> URLString -> UUID -> (Key -> Annex (Bool, Bool)) -> Key -> CommandPerform
addUrlChecked relaxed url u checkexistssize key

View file

@ -33,11 +33,9 @@ import Command.AddUrl (addUrlFile, downloadRemoteFile, parseRelaxedOption, parse
import Annex.Perms
import Annex.UUID
import Backend.URL (fromUrl)
#ifdef WITH_QUVI
import Annex.Quvi
import qualified Utility.Quvi as Quvi
import Command.AddUrl (addUrlFileQuvi)
#endif
import Types.MetaData
import Logs.MetaData
import Annex.MetaData
@ -139,16 +137,12 @@ findDownloads u = go =<< downloadFeed u
Just (enclosureurl, _, _) -> return $
Just $ ToDownload f u i $ Enclosure enclosureurl
Nothing -> mkquvi f i
#ifdef WITH_QUVI
mkquvi f i = case getItemLink i of
Just link -> ifM (quviSupported link)
( return $ Just $ ToDownload f u i $ QuviLink link
, return Nothing
)
Nothing -> return Nothing
#else
mkquvi _ _ = return Nothing
#endif
{- Feeds change, so a feed download cannot be resumed. -}
downloadFeed :: URLString -> Annex (Maybe Feed)
@ -193,7 +187,6 @@ performDownload opts cache todownload = case location todownload of
else []
QuviLink pageurl -> do
#ifdef WITH_QUVI
let quviurl = setDownloader pageurl QuviDownloader
checkknown quviurl $ do
mp <- withQuviOptions Quvi.query [Quvi.quiet, Quvi.httponly] pageurl
@ -206,9 +199,6 @@ performDownload opts cache todownload = case location todownload of
checkknown videourl $
rundownload videourl ("." ++ fromMaybe "m" (Quvi.linkSuffix link)) $ \f ->
maybeToList <$> addUrlFileQuvi (relaxedOption opts) quviurl videourl f
#else
return False
#endif
where
forced = Annex.getState Annex.force

View file

@ -34,9 +34,7 @@ import qualified Remote.BitTorrent
#ifdef WITH_WEBDAV
import qualified Remote.WebDAV
#endif
#ifdef WITH_TAHOE
import qualified Remote.Tahoe
#endif
import qualified Remote.Glacier
import qualified Remote.Ddar
import qualified Remote.Hook
@ -57,9 +55,7 @@ remoteTypes =
#ifdef WITH_WEBDAV
, Remote.WebDAV.remote
#endif
#ifdef WITH_TAHOE
, Remote.Tahoe.remote
#endif
, Remote.Glacier.remote
, Remote.Ddar.remote
, Remote.Hook.remote

View file

@ -5,8 +5,6 @@
- Licensed under the GNU GPL version 3 or higher.
-}
{-# LANGUAGE CPP #-}
module Remote.Web (remote, getWebUrls) where
import Annex.Common
@ -20,10 +18,8 @@ import Logs.Web
import Annex.UUID
import Utility.Metered
import qualified Annex.Url as Url
#ifdef WITH_QUVI
import Annex.Quvi
import qualified Utility.Quvi as Quvi
#endif
remote :: RemoteType
remote = RemoteType {
@ -82,13 +78,8 @@ downloadKey key _af dest p = unVerified $ get =<< getWebUrls key
let (u', downloader) = getDownloader u
case downloader of
QuviDownloader -> do
#ifdef WITH_QUVI
flip (downloadUrl key p) dest
=<< withQuviOptions Quvi.queryLinks [Quvi.httponly, Quvi.quiet] u'
#else
warning "quvi support needed for this url"
return False
#endif
_ -> downloadUrl key p [u'] dest
downloadKeyCheap :: Key -> AssociatedFile -> FilePath -> Annex Bool
@ -116,11 +107,7 @@ checkKey' key us = firsthit us (Right False) $ \u -> do
showChecking u'
case downloader of
QuviDownloader ->
#ifdef WITH_QUVI
Right <$> withQuviOptions Quvi.check [Quvi.httponly, Quvi.quiet] u'
#else
return $ Left "quvi support needed for this url"
#endif
_ -> do
Url.withUrlOptions $ catchMsgIO .
Url.checkBoth u' (keySize key)

View file

@ -31,10 +31,8 @@ import Blaze.ByteString.Builder.Char.Utf8 (fromText)
import Blaze.ByteString.Builder (Builder)
import Control.Arrow ((***))
import Control.Concurrent
#ifdef WITH_WEBAPP_SECURE
import Data.SecureMem
import Data.Byteable
#endif
#ifdef __ANDROID__
import Data.Endian
#endif
@ -77,11 +75,7 @@ runWebApp tlssettings h app observer = withSocketsDo $ do
sockaddr <- fixSockAddr <$> getSocketName sock
observer sockaddr
where
#ifdef WITH_WEBAPP_SECURE
go = (maybe runSettingsSocket (\ts -> runTLSSocket ts) tlssettings)
#else
go = runSettingsSocket
#endif
fixSockAddr :: SockAddr -> SockAddr
#ifdef __ANDROID__
@ -165,25 +159,13 @@ webAppSessionBackend _ = do
Just . Yesod.clientSessionBackend key . fst
<$> Yesod.clientSessionDateCacher timeout
#ifdef WITH_WEBAPP_SECURE
type AuthToken = SecureMem
#else
type AuthToken = T.Text
#endif
toAuthToken :: T.Text -> AuthToken
#ifdef WITH_WEBAPP_SECURE
toAuthToken = secureMemFromByteString . TE.encodeUtf8
#else
toAuthToken = id
#endif
fromAuthToken :: AuthToken -> T.Text
#ifdef WITH_WEBAPP_SECURE
fromAuthToken = TE.decodeLatin1 . toBytes
#else
fromAuthToken = id
#endif
{- Generates a random sha2_512 string, encapsulated in a SecureMem,
- suitable to be used for an authentication secret. -}

6
debian/changelog vendored
View file

@ -18,6 +18,12 @@ git-annex (6.20160115) UNRELEASED; urgency=medium
* Fix build with QuickCheck 2.8.2
* matchexpression: New plumbing command to check if a preferred content
expression matches some data.
* Removed the webapp-secure build flag, rolling it into the webapp build
flag.
* Removed the quvi and tahoe build flags, which only adds aeson to
the core dependencies.
* Removed the feed build flag, which only adds feed to the core
dependencies.
-- Joey Hess <id@joeyh.name> Fri, 15 Jan 2016 14:05:01 -0400

View file

@ -43,9 +43,6 @@ Flag Assistant
Flag Webapp
Description: Enable git-annex webapp
Flag Webapp-secure
Description: Secure webapp
Flag Pairing
Description: Enable pairing
@ -69,15 +66,6 @@ Flag TestSuite
Flag TDFA
Description: Use regex-tdfa for wildcards
Flag Feed
Description: Enable podcast feed support
Flag Quvi
Description: Enable use of quvi to download videos
Flag Tahoe
Description: Enable the tahoe special remote
Flag TorrentParser
Description: Use haskell torrent library to parse torrent files
@ -117,13 +105,19 @@ Executable git-annex
bloomfilter, edit-distance,
resourcet, http-conduit, http-client, http-types,
time, old-locale,
esqueleto, persistent-sqlite, persistent, persistent-template
esqueleto, persistent-sqlite, persistent, persistent-template,
aeson,
feed
CC-Options: -Wall
GHC-Options: -Wall -fno-warn-tabs
Extensions: PackageImports
-- Some things don't work with the non-threaded RTS.
GHC-Options: -threaded
-- Fully optimize for production.
if flag(Production)
GHC-Options: -O2
-- Avoid linking with unused dynamic libaries.
-- (Only tested on Linux).
if os(Linux)
@ -140,10 +134,6 @@ Executable git-annex
else
Build-Depends: cryptohash (>= 0.11.0)
-- Fully optimize for production.
if flag(Production)
GHC-Options: -O2
if (os(windows))
Build-Depends: Win32, Win32-extras, unix-compat (>= 0.4.1.3), setenv,
process (>= 1.3.0.0)
@ -217,17 +207,15 @@ Executable git-annex
yesod-core (>= 1.2.19),
path-pieces (>= 0.1.4),
warp (>= 3.0.0.5),
warp-tls,
warp-tls (>= 1.4),
wai, wai-extra,
blaze-builder, crypto-api, clientsession,
template-haskell, aeson,
shakespeare (>= 2.0.0)
template-haskell,
shakespeare (>= 2.0.0),
securemem,
byteable
CPP-Options: -DWITH_WEBAPP
if flag(Webapp) && flag (Webapp-secure)
Build-Depends: warp-tls (>= 1.4), securemem, byteable
CPP-Options: -DWITH_WEBAPP_SECURE
if flag(Pairing)
Build-Depends: network-multicast, network-info
CPP-Options: -DWITH_PAIRING
@ -239,19 +227,7 @@ Executable git-annex
if flag(DNS)
Build-Depends: dns
CPP-Options: -DWITH_DNS
if flag(Feed)
Build-Depends: feed (>= 0.3.4)
CPP-Options: -DWITH_FEED
if flag(Quvi)
Build-Depends: aeson
CPP-Options: -DWITH_QUVI
if flag(Tahoe)
Build-Depends: aeson
CPP-Options: -DWITH_TAHOE
if flag(TorrentParser)
Build-Depends: torrent (>= 10000.0.0)
CPP-Options: -DWITH_TORRENTPARSER