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:
parent
36e05945b8
commit
f051b51645
11 changed files with 27 additions and 130 deletions
8
Annex.hs
8
Annex.hs
|
@ -5,7 +5,7 @@
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
{-# LANGUAGE CPP, GeneralizedNewtypeDeriving, PackageImports, BangPatterns #-}
|
{-# LANGUAGE GeneralizedNewtypeDeriving, PackageImports, BangPatterns #-}
|
||||||
|
|
||||||
module Annex (
|
module Annex (
|
||||||
Annex,
|
Annex,
|
||||||
|
@ -62,9 +62,7 @@ import Types.LockCache
|
||||||
import Types.DesktopNotify
|
import Types.DesktopNotify
|
||||||
import Types.CleanupActions
|
import Types.CleanupActions
|
||||||
import qualified Database.Keys.Handle as Keys
|
import qualified Database.Keys.Handle as Keys
|
||||||
#ifdef WITH_QUVI
|
|
||||||
import Utility.Quvi (QuviVersion)
|
import Utility.Quvi (QuviVersion)
|
||||||
#endif
|
|
||||||
import Utility.InodeCache
|
import Utility.InodeCache
|
||||||
import Utility.Url
|
import Utility.Url
|
||||||
|
|
||||||
|
@ -130,9 +128,7 @@ data AnnexState = AnnexState
|
||||||
, errcounter :: Integer
|
, errcounter :: Integer
|
||||||
, unusedkeys :: Maybe (S.Set Key)
|
, unusedkeys :: Maybe (S.Set Key)
|
||||||
, tempurls :: M.Map Key URLString
|
, tempurls :: M.Map Key URLString
|
||||||
#ifdef WITH_QUVI
|
|
||||||
, quviversion :: Maybe QuviVersion
|
, quviversion :: Maybe QuviVersion
|
||||||
#endif
|
|
||||||
, existinghooks :: M.Map Git.Hook.Hook Bool
|
, existinghooks :: M.Map Git.Hook.Hook Bool
|
||||||
, desktopnotify :: DesktopNotify
|
, desktopnotify :: DesktopNotify
|
||||||
, workers :: [Either AnnexState (Async AnnexState)]
|
, workers :: [Either AnnexState (Async AnnexState)]
|
||||||
|
@ -177,9 +173,7 @@ newState c r = AnnexState
|
||||||
, errcounter = 0
|
, errcounter = 0
|
||||||
, unusedkeys = Nothing
|
, unusedkeys = Nothing
|
||||||
, tempurls = M.empty
|
, tempurls = M.empty
|
||||||
#ifdef WITH_QUVI
|
|
||||||
, quviversion = Nothing
|
, quviversion = Nothing
|
||||||
#endif
|
|
||||||
, existinghooks = M.empty
|
, existinghooks = M.empty
|
||||||
, desktopnotify = mempty
|
, desktopnotify = mempty
|
||||||
, workers = []
|
, workers = []
|
||||||
|
|
|
@ -127,13 +127,9 @@ myUrl tlssettings webapp addr = unpack $ yesodRender webapp urlbase DashboardR [
|
||||||
|
|
||||||
getTlsSettings :: Annex (Maybe TLS.TLSSettings)
|
getTlsSettings :: Annex (Maybe TLS.TLSSettings)
|
||||||
getTlsSettings = do
|
getTlsSettings = do
|
||||||
#ifdef WITH_WEBAPP_SECURE
|
|
||||||
cert <- fromRepo gitAnnexWebCertificate
|
cert <- fromRepo gitAnnexWebCertificate
|
||||||
privkey <- fromRepo gitAnnexWebPrivKey
|
privkey <- fromRepo gitAnnexWebPrivKey
|
||||||
ifM (liftIO $ allM doesFileExist [cert, privkey])
|
ifM (liftIO $ allM doesFileExist [cert, privkey])
|
||||||
( return $ Just $ TLS.tlsSettings cert privkey
|
( return $ Just $ TLS.tlsSettings cert privkey
|
||||||
, return Nothing
|
, return Nothing
|
||||||
)
|
)
|
||||||
#else
|
|
||||||
return Nothing
|
|
||||||
#endif
|
|
||||||
|
|
|
@ -22,9 +22,6 @@ buildFlags = filter (not . null)
|
||||||
#else
|
#else
|
||||||
#warning Building without the webapp. You probably need to install Yesod..
|
#warning Building without the webapp. You probably need to install Yesod..
|
||||||
#endif
|
#endif
|
||||||
#ifdef WITH_WEBAPP_SECURE
|
|
||||||
, "Webapp-secure"
|
|
||||||
#endif
|
|
||||||
#ifdef WITH_PAIRING
|
#ifdef WITH_PAIRING
|
||||||
, "Pairing"
|
, "Pairing"
|
||||||
#else
|
#else
|
||||||
|
@ -79,16 +76,6 @@ buildFlags = filter (not . null)
|
||||||
#ifdef WITH_DNS
|
#ifdef WITH_DNS
|
||||||
, "DNS"
|
, "DNS"
|
||||||
#endif
|
#endif
|
||||||
#ifdef WITH_FEED
|
|
||||||
, "Feeds"
|
|
||||||
#else
|
|
||||||
#warning Building without Feeds.
|
|
||||||
#endif
|
|
||||||
#ifdef WITH_QUVI
|
|
||||||
, "Quvi"
|
|
||||||
#else
|
|
||||||
#warning Building without quvi.
|
|
||||||
#endif
|
|
||||||
#ifdef WITH_TDFA
|
#ifdef WITH_TDFA
|
||||||
, "TDFA"
|
, "TDFA"
|
||||||
#endif
|
#endif
|
||||||
|
@ -98,4 +85,8 @@ buildFlags = filter (not . null)
|
||||||
#ifdef WITH_EKG
|
#ifdef WITH_EKG
|
||||||
, "EKG"
|
, "EKG"
|
||||||
#endif
|
#endif
|
||||||
|
-- Always enabled now, but users may be used to seeing these flags
|
||||||
|
-- listed.
|
||||||
|
, "Feeds"
|
||||||
|
, "Quvi"
|
||||||
]
|
]
|
||||||
|
|
|
@ -85,9 +85,7 @@ import qualified Command.Vicfg
|
||||||
import qualified Command.Sync
|
import qualified Command.Sync
|
||||||
import qualified Command.Mirror
|
import qualified Command.Mirror
|
||||||
import qualified Command.AddUrl
|
import qualified Command.AddUrl
|
||||||
#ifdef WITH_FEED
|
|
||||||
import qualified Command.ImportFeed
|
import qualified Command.ImportFeed
|
||||||
#endif
|
|
||||||
import qualified Command.RmUrl
|
import qualified Command.RmUrl
|
||||||
import qualified Command.Import
|
import qualified Command.Import
|
||||||
import qualified Command.Map
|
import qualified Command.Map
|
||||||
|
@ -138,9 +136,7 @@ cmds testoptparser testrunner =
|
||||||
, Command.Sync.cmd
|
, Command.Sync.cmd
|
||||||
, Command.Mirror.cmd
|
, Command.Mirror.cmd
|
||||||
, Command.AddUrl.cmd
|
, Command.AddUrl.cmd
|
||||||
#ifdef WITH_FEED
|
|
||||||
, Command.ImportFeed.cmd
|
, Command.ImportFeed.cmd
|
||||||
#endif
|
|
||||||
, Command.RmUrl.cmd
|
, Command.RmUrl.cmd
|
||||||
, Command.Import.cmd
|
, Command.Import.cmd
|
||||||
, Command.Init.cmd
|
, Command.Init.cmd
|
||||||
|
|
|
@ -5,8 +5,6 @@
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
{-# LANGUAGE CPP #-}
|
|
||||||
|
|
||||||
module Command.AddUrl where
|
module Command.AddUrl where
|
||||||
|
|
||||||
import Network.URI
|
import Network.URI
|
||||||
|
@ -32,10 +30,8 @@ import Annex.FileMatcher
|
||||||
import Logs.Location
|
import Logs.Location
|
||||||
import Utility.Metered
|
import Utility.Metered
|
||||||
import qualified Annex.Transfer as Transfer
|
import qualified Annex.Transfer as Transfer
|
||||||
#ifdef WITH_QUVI
|
|
||||||
import Annex.Quvi
|
import Annex.Quvi
|
||||||
import qualified Utility.Quvi as Quvi
|
import qualified Utility.Quvi as Quvi
|
||||||
#endif
|
|
||||||
|
|
||||||
cmd :: Command
|
cmd :: Command
|
||||||
cmd = notBareRepo $ withGlobalOptions [jobsOption, jsonOption] $
|
cmd = notBareRepo $ withGlobalOptions [jobsOption, jsonOption] $
|
||||||
|
@ -192,15 +188,10 @@ startWeb o s = go $ fromMaybe bad $ parseURI urlstring
|
||||||
Url.parseURIRelaxed $ urlstring
|
Url.parseURIRelaxed $ urlstring
|
||||||
go url = case downloader of
|
go url = case downloader of
|
||||||
QuviDownloader -> usequvi
|
QuviDownloader -> usequvi
|
||||||
_ ->
|
_ -> ifM (quviSupported urlstring)
|
||||||
#ifdef WITH_QUVI
|
( usequvi
|
||||||
ifM (quviSupported urlstring)
|
, regulardownload url
|
||||||
( usequvi
|
)
|
||||||
, regulardownload url
|
|
||||||
)
|
|
||||||
#else
|
|
||||||
regulardownload url
|
|
||||||
#endif
|
|
||||||
regulardownload url = do
|
regulardownload url = do
|
||||||
pathmax <- liftIO $ fileNameLengthLimit "."
|
pathmax <- liftIO $ fileNameLengthLimit "."
|
||||||
urlinfo <- if relaxedOption o
|
urlinfo <- if relaxedOption o
|
||||||
|
@ -219,7 +210,6 @@ startWeb o s = go $ fromMaybe bad $ parseURI urlstring
|
||||||
)
|
)
|
||||||
showStart "addurl" file
|
showStart "addurl" file
|
||||||
next $ performWeb (relaxedOption o) urlstring file urlinfo
|
next $ performWeb (relaxedOption o) urlstring file urlinfo
|
||||||
#ifdef WITH_QUVI
|
|
||||||
badquvi = error $ "quvi does not know how to download url " ++ urlstring
|
badquvi = error $ "quvi does not know how to download url " ++ urlstring
|
||||||
usequvi = do
|
usequvi = do
|
||||||
page <- fromMaybe badquvi
|
page <- fromMaybe badquvi
|
||||||
|
@ -231,9 +221,6 @@ startWeb o s = go $ fromMaybe bad $ parseURI urlstring
|
||||||
Quvi.pageTitle page ++ "." ++ fromMaybe "m" (Quvi.linkSuffix link)
|
Quvi.pageTitle page ++ "." ++ fromMaybe "m" (Quvi.linkSuffix link)
|
||||||
showStart "addurl" file
|
showStart "addurl" file
|
||||||
next $ performQuvi (relaxedOption o) urlstring (Quvi.linkUrl link) 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 :: Bool -> URLString -> FilePath -> Url.UrlInfo -> CommandPerform
|
||||||
performWeb relaxed url file urlinfo = ifAnnexed file addurl geturl
|
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 $
|
addurl = addUrlChecked relaxed url webUUID $ \k -> return $
|
||||||
(Url.urlExists urlinfo, Url.urlSize urlinfo == keySize k)
|
(Url.urlExists urlinfo, Url.urlSize urlinfo == keySize k)
|
||||||
|
|
||||||
#ifdef WITH_QUVI
|
|
||||||
performQuvi :: Bool -> URLString -> URLString -> FilePath -> CommandPerform
|
performQuvi :: Bool -> URLString -> URLString -> FilePath -> CommandPerform
|
||||||
performQuvi relaxed pageurl videourl file = ifAnnexed file addurl geturl
|
performQuvi relaxed pageurl videourl file = ifAnnexed file addurl geturl
|
||||||
where
|
where
|
||||||
|
@ -251,9 +237,7 @@ performQuvi relaxed pageurl videourl file = ifAnnexed file addurl geturl
|
||||||
cleanup webUUID quviurl file key Nothing
|
cleanup webUUID quviurl file key Nothing
|
||||||
return True
|
return True
|
||||||
geturl = next $ isJust <$> addUrlFileQuvi relaxed quviurl videourl file
|
geturl = next $ isJust <$> addUrlFileQuvi relaxed quviurl videourl file
|
||||||
#endif
|
|
||||||
|
|
||||||
#ifdef WITH_QUVI
|
|
||||||
addUrlFileQuvi :: Bool -> URLString -> URLString -> FilePath -> Annex (Maybe Key)
|
addUrlFileQuvi :: Bool -> URLString -> URLString -> FilePath -> Annex (Maybe Key)
|
||||||
addUrlFileQuvi relaxed quviurl videourl file = stopUnless (doesNotExist file) $ do
|
addUrlFileQuvi relaxed quviurl videourl file = stopUnless (doesNotExist file) $ do
|
||||||
let key = Backend.URL.fromUrl quviurl Nothing
|
let key = Backend.URL.fromUrl quviurl Nothing
|
||||||
|
@ -282,7 +266,6 @@ addUrlFileQuvi relaxed quviurl videourl file = stopUnless (doesNotExist file) $
|
||||||
return (Just key)
|
return (Just key)
|
||||||
else return Nothing
|
else return Nothing
|
||||||
)
|
)
|
||||||
#endif
|
|
||||||
|
|
||||||
addUrlChecked :: Bool -> URLString -> UUID -> (Key -> Annex (Bool, Bool)) -> Key -> CommandPerform
|
addUrlChecked :: Bool -> URLString -> UUID -> (Key -> Annex (Bool, Bool)) -> Key -> CommandPerform
|
||||||
addUrlChecked relaxed url u checkexistssize key
|
addUrlChecked relaxed url u checkexistssize key
|
||||||
|
|
|
@ -33,11 +33,9 @@ import Command.AddUrl (addUrlFile, downloadRemoteFile, parseRelaxedOption, parse
|
||||||
import Annex.Perms
|
import Annex.Perms
|
||||||
import Annex.UUID
|
import Annex.UUID
|
||||||
import Backend.URL (fromUrl)
|
import Backend.URL (fromUrl)
|
||||||
#ifdef WITH_QUVI
|
|
||||||
import Annex.Quvi
|
import Annex.Quvi
|
||||||
import qualified Utility.Quvi as Quvi
|
import qualified Utility.Quvi as Quvi
|
||||||
import Command.AddUrl (addUrlFileQuvi)
|
import Command.AddUrl (addUrlFileQuvi)
|
||||||
#endif
|
|
||||||
import Types.MetaData
|
import Types.MetaData
|
||||||
import Logs.MetaData
|
import Logs.MetaData
|
||||||
import Annex.MetaData
|
import Annex.MetaData
|
||||||
|
@ -139,16 +137,12 @@ findDownloads u = go =<< downloadFeed u
|
||||||
Just (enclosureurl, _, _) -> return $
|
Just (enclosureurl, _, _) -> return $
|
||||||
Just $ ToDownload f u i $ Enclosure enclosureurl
|
Just $ ToDownload f u i $ Enclosure enclosureurl
|
||||||
Nothing -> mkquvi f i
|
Nothing -> mkquvi f i
|
||||||
#ifdef WITH_QUVI
|
|
||||||
mkquvi f i = case getItemLink i of
|
mkquvi f i = case getItemLink i of
|
||||||
Just link -> ifM (quviSupported link)
|
Just link -> ifM (quviSupported link)
|
||||||
( return $ Just $ ToDownload f u i $ QuviLink link
|
( return $ Just $ ToDownload f u i $ QuviLink link
|
||||||
, return Nothing
|
, return Nothing
|
||||||
)
|
)
|
||||||
Nothing -> return Nothing
|
Nothing -> return Nothing
|
||||||
#else
|
|
||||||
mkquvi _ _ = return Nothing
|
|
||||||
#endif
|
|
||||||
|
|
||||||
{- Feeds change, so a feed download cannot be resumed. -}
|
{- Feeds change, so a feed download cannot be resumed. -}
|
||||||
downloadFeed :: URLString -> Annex (Maybe Feed)
|
downloadFeed :: URLString -> Annex (Maybe Feed)
|
||||||
|
@ -193,7 +187,6 @@ performDownload opts cache todownload = case location todownload of
|
||||||
else []
|
else []
|
||||||
|
|
||||||
QuviLink pageurl -> do
|
QuviLink pageurl -> do
|
||||||
#ifdef WITH_QUVI
|
|
||||||
let quviurl = setDownloader pageurl QuviDownloader
|
let quviurl = setDownloader pageurl QuviDownloader
|
||||||
checkknown quviurl $ do
|
checkknown quviurl $ do
|
||||||
mp <- withQuviOptions Quvi.query [Quvi.quiet, Quvi.httponly] pageurl
|
mp <- withQuviOptions Quvi.query [Quvi.quiet, Quvi.httponly] pageurl
|
||||||
|
@ -206,9 +199,6 @@ performDownload opts cache todownload = case location todownload of
|
||||||
checkknown videourl $
|
checkknown videourl $
|
||||||
rundownload videourl ("." ++ fromMaybe "m" (Quvi.linkSuffix link)) $ \f ->
|
rundownload videourl ("." ++ fromMaybe "m" (Quvi.linkSuffix link)) $ \f ->
|
||||||
maybeToList <$> addUrlFileQuvi (relaxedOption opts) quviurl videourl f
|
maybeToList <$> addUrlFileQuvi (relaxedOption opts) quviurl videourl f
|
||||||
#else
|
|
||||||
return False
|
|
||||||
#endif
|
|
||||||
where
|
where
|
||||||
forced = Annex.getState Annex.force
|
forced = Annex.getState Annex.force
|
||||||
|
|
||||||
|
|
|
@ -34,9 +34,7 @@ import qualified Remote.BitTorrent
|
||||||
#ifdef WITH_WEBDAV
|
#ifdef WITH_WEBDAV
|
||||||
import qualified Remote.WebDAV
|
import qualified Remote.WebDAV
|
||||||
#endif
|
#endif
|
||||||
#ifdef WITH_TAHOE
|
|
||||||
import qualified Remote.Tahoe
|
import qualified Remote.Tahoe
|
||||||
#endif
|
|
||||||
import qualified Remote.Glacier
|
import qualified Remote.Glacier
|
||||||
import qualified Remote.Ddar
|
import qualified Remote.Ddar
|
||||||
import qualified Remote.Hook
|
import qualified Remote.Hook
|
||||||
|
@ -57,9 +55,7 @@ remoteTypes =
|
||||||
#ifdef WITH_WEBDAV
|
#ifdef WITH_WEBDAV
|
||||||
, Remote.WebDAV.remote
|
, Remote.WebDAV.remote
|
||||||
#endif
|
#endif
|
||||||
#ifdef WITH_TAHOE
|
|
||||||
, Remote.Tahoe.remote
|
, Remote.Tahoe.remote
|
||||||
#endif
|
|
||||||
, Remote.Glacier.remote
|
, Remote.Glacier.remote
|
||||||
, Remote.Ddar.remote
|
, Remote.Ddar.remote
|
||||||
, Remote.Hook.remote
|
, Remote.Hook.remote
|
||||||
|
|
|
@ -5,8 +5,6 @@
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
{-# LANGUAGE CPP #-}
|
|
||||||
|
|
||||||
module Remote.Web (remote, getWebUrls) where
|
module Remote.Web (remote, getWebUrls) where
|
||||||
|
|
||||||
import Annex.Common
|
import Annex.Common
|
||||||
|
@ -20,10 +18,8 @@ import Logs.Web
|
||||||
import Annex.UUID
|
import Annex.UUID
|
||||||
import Utility.Metered
|
import Utility.Metered
|
||||||
import qualified Annex.Url as Url
|
import qualified Annex.Url as Url
|
||||||
#ifdef WITH_QUVI
|
|
||||||
import Annex.Quvi
|
import Annex.Quvi
|
||||||
import qualified Utility.Quvi as Quvi
|
import qualified Utility.Quvi as Quvi
|
||||||
#endif
|
|
||||||
|
|
||||||
remote :: RemoteType
|
remote :: RemoteType
|
||||||
remote = RemoteType {
|
remote = RemoteType {
|
||||||
|
@ -82,13 +78,8 @@ downloadKey key _af dest p = unVerified $ get =<< getWebUrls key
|
||||||
let (u', downloader) = getDownloader u
|
let (u', downloader) = getDownloader u
|
||||||
case downloader of
|
case downloader of
|
||||||
QuviDownloader -> do
|
QuviDownloader -> do
|
||||||
#ifdef WITH_QUVI
|
|
||||||
flip (downloadUrl key p) dest
|
flip (downloadUrl key p) dest
|
||||||
=<< withQuviOptions Quvi.queryLinks [Quvi.httponly, Quvi.quiet] u'
|
=<< withQuviOptions Quvi.queryLinks [Quvi.httponly, Quvi.quiet] u'
|
||||||
#else
|
|
||||||
warning "quvi support needed for this url"
|
|
||||||
return False
|
|
||||||
#endif
|
|
||||||
_ -> downloadUrl key p [u'] dest
|
_ -> downloadUrl key p [u'] dest
|
||||||
|
|
||||||
downloadKeyCheap :: Key -> AssociatedFile -> FilePath -> Annex Bool
|
downloadKeyCheap :: Key -> AssociatedFile -> FilePath -> Annex Bool
|
||||||
|
@ -116,11 +107,7 @@ checkKey' key us = firsthit us (Right False) $ \u -> do
|
||||||
showChecking u'
|
showChecking u'
|
||||||
case downloader of
|
case downloader of
|
||||||
QuviDownloader ->
|
QuviDownloader ->
|
||||||
#ifdef WITH_QUVI
|
|
||||||
Right <$> withQuviOptions Quvi.check [Quvi.httponly, Quvi.quiet] u'
|
Right <$> withQuviOptions Quvi.check [Quvi.httponly, Quvi.quiet] u'
|
||||||
#else
|
|
||||||
return $ Left "quvi support needed for this url"
|
|
||||||
#endif
|
|
||||||
_ -> do
|
_ -> do
|
||||||
Url.withUrlOptions $ catchMsgIO .
|
Url.withUrlOptions $ catchMsgIO .
|
||||||
Url.checkBoth u' (keySize key)
|
Url.checkBoth u' (keySize key)
|
||||||
|
|
|
@ -31,10 +31,8 @@ import Blaze.ByteString.Builder.Char.Utf8 (fromText)
|
||||||
import Blaze.ByteString.Builder (Builder)
|
import Blaze.ByteString.Builder (Builder)
|
||||||
import Control.Arrow ((***))
|
import Control.Arrow ((***))
|
||||||
import Control.Concurrent
|
import Control.Concurrent
|
||||||
#ifdef WITH_WEBAPP_SECURE
|
|
||||||
import Data.SecureMem
|
import Data.SecureMem
|
||||||
import Data.Byteable
|
import Data.Byteable
|
||||||
#endif
|
|
||||||
#ifdef __ANDROID__
|
#ifdef __ANDROID__
|
||||||
import Data.Endian
|
import Data.Endian
|
||||||
#endif
|
#endif
|
||||||
|
@ -77,11 +75,7 @@ runWebApp tlssettings h app observer = withSocketsDo $ do
|
||||||
sockaddr <- fixSockAddr <$> getSocketName sock
|
sockaddr <- fixSockAddr <$> getSocketName sock
|
||||||
observer sockaddr
|
observer sockaddr
|
||||||
where
|
where
|
||||||
#ifdef WITH_WEBAPP_SECURE
|
|
||||||
go = (maybe runSettingsSocket (\ts -> runTLSSocket ts) tlssettings)
|
go = (maybe runSettingsSocket (\ts -> runTLSSocket ts) tlssettings)
|
||||||
#else
|
|
||||||
go = runSettingsSocket
|
|
||||||
#endif
|
|
||||||
|
|
||||||
fixSockAddr :: SockAddr -> SockAddr
|
fixSockAddr :: SockAddr -> SockAddr
|
||||||
#ifdef __ANDROID__
|
#ifdef __ANDROID__
|
||||||
|
@ -165,25 +159,13 @@ webAppSessionBackend _ = do
|
||||||
Just . Yesod.clientSessionBackend key . fst
|
Just . Yesod.clientSessionBackend key . fst
|
||||||
<$> Yesod.clientSessionDateCacher timeout
|
<$> Yesod.clientSessionDateCacher timeout
|
||||||
|
|
||||||
#ifdef WITH_WEBAPP_SECURE
|
|
||||||
type AuthToken = SecureMem
|
type AuthToken = SecureMem
|
||||||
#else
|
|
||||||
type AuthToken = T.Text
|
|
||||||
#endif
|
|
||||||
|
|
||||||
toAuthToken :: T.Text -> AuthToken
|
toAuthToken :: T.Text -> AuthToken
|
||||||
#ifdef WITH_WEBAPP_SECURE
|
|
||||||
toAuthToken = secureMemFromByteString . TE.encodeUtf8
|
toAuthToken = secureMemFromByteString . TE.encodeUtf8
|
||||||
#else
|
|
||||||
toAuthToken = id
|
|
||||||
#endif
|
|
||||||
|
|
||||||
fromAuthToken :: AuthToken -> T.Text
|
fromAuthToken :: AuthToken -> T.Text
|
||||||
#ifdef WITH_WEBAPP_SECURE
|
|
||||||
fromAuthToken = TE.decodeLatin1 . toBytes
|
fromAuthToken = TE.decodeLatin1 . toBytes
|
||||||
#else
|
|
||||||
fromAuthToken = id
|
|
||||||
#endif
|
|
||||||
|
|
||||||
{- Generates a random sha2_512 string, encapsulated in a SecureMem,
|
{- Generates a random sha2_512 string, encapsulated in a SecureMem,
|
||||||
- suitable to be used for an authentication secret. -}
|
- suitable to be used for an authentication secret. -}
|
||||||
|
|
6
debian/changelog
vendored
6
debian/changelog
vendored
|
@ -18,6 +18,12 @@ git-annex (6.20160115) UNRELEASED; urgency=medium
|
||||||
* Fix build with QuickCheck 2.8.2
|
* Fix build with QuickCheck 2.8.2
|
||||||
* matchexpression: New plumbing command to check if a preferred content
|
* matchexpression: New plumbing command to check if a preferred content
|
||||||
expression matches some data.
|
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
|
-- Joey Hess <id@joeyh.name> Fri, 15 Jan 2016 14:05:01 -0400
|
||||||
|
|
||||||
|
|
|
@ -43,9 +43,6 @@ Flag Assistant
|
||||||
Flag Webapp
|
Flag Webapp
|
||||||
Description: Enable git-annex webapp
|
Description: Enable git-annex webapp
|
||||||
|
|
||||||
Flag Webapp-secure
|
|
||||||
Description: Secure webapp
|
|
||||||
|
|
||||||
Flag Pairing
|
Flag Pairing
|
||||||
Description: Enable pairing
|
Description: Enable pairing
|
||||||
|
|
||||||
|
@ -69,15 +66,6 @@ Flag TestSuite
|
||||||
Flag TDFA
|
Flag TDFA
|
||||||
Description: Use regex-tdfa for wildcards
|
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
|
Flag TorrentParser
|
||||||
Description: Use haskell torrent library to parse torrent files
|
Description: Use haskell torrent library to parse torrent files
|
||||||
|
|
||||||
|
@ -117,13 +105,19 @@ Executable git-annex
|
||||||
bloomfilter, edit-distance,
|
bloomfilter, edit-distance,
|
||||||
resourcet, http-conduit, http-client, http-types,
|
resourcet, http-conduit, http-client, http-types,
|
||||||
time, old-locale,
|
time, old-locale,
|
||||||
esqueleto, persistent-sqlite, persistent, persistent-template
|
esqueleto, persistent-sqlite, persistent, persistent-template,
|
||||||
|
aeson,
|
||||||
|
feed
|
||||||
CC-Options: -Wall
|
CC-Options: -Wall
|
||||||
GHC-Options: -Wall -fno-warn-tabs
|
GHC-Options: -Wall -fno-warn-tabs
|
||||||
Extensions: PackageImports
|
Extensions: PackageImports
|
||||||
-- Some things don't work with the non-threaded RTS.
|
-- Some things don't work with the non-threaded RTS.
|
||||||
GHC-Options: -threaded
|
GHC-Options: -threaded
|
||||||
|
|
||||||
|
-- Fully optimize for production.
|
||||||
|
if flag(Production)
|
||||||
|
GHC-Options: -O2
|
||||||
|
|
||||||
-- Avoid linking with unused dynamic libaries.
|
-- Avoid linking with unused dynamic libaries.
|
||||||
-- (Only tested on Linux).
|
-- (Only tested on Linux).
|
||||||
if os(Linux)
|
if os(Linux)
|
||||||
|
@ -140,10 +134,6 @@ Executable git-annex
|
||||||
else
|
else
|
||||||
Build-Depends: cryptohash (>= 0.11.0)
|
Build-Depends: cryptohash (>= 0.11.0)
|
||||||
|
|
||||||
-- Fully optimize for production.
|
|
||||||
if flag(Production)
|
|
||||||
GHC-Options: -O2
|
|
||||||
|
|
||||||
if (os(windows))
|
if (os(windows))
|
||||||
Build-Depends: Win32, Win32-extras, unix-compat (>= 0.4.1.3), setenv,
|
Build-Depends: Win32, Win32-extras, unix-compat (>= 0.4.1.3), setenv,
|
||||||
process (>= 1.3.0.0)
|
process (>= 1.3.0.0)
|
||||||
|
@ -217,17 +207,15 @@ Executable git-annex
|
||||||
yesod-core (>= 1.2.19),
|
yesod-core (>= 1.2.19),
|
||||||
path-pieces (>= 0.1.4),
|
path-pieces (>= 0.1.4),
|
||||||
warp (>= 3.0.0.5),
|
warp (>= 3.0.0.5),
|
||||||
warp-tls,
|
warp-tls (>= 1.4),
|
||||||
wai, wai-extra,
|
wai, wai-extra,
|
||||||
blaze-builder, crypto-api, clientsession,
|
blaze-builder, crypto-api, clientsession,
|
||||||
template-haskell, aeson,
|
template-haskell,
|
||||||
shakespeare (>= 2.0.0)
|
shakespeare (>= 2.0.0),
|
||||||
|
securemem,
|
||||||
|
byteable
|
||||||
CPP-Options: -DWITH_WEBAPP
|
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)
|
if flag(Pairing)
|
||||||
Build-Depends: network-multicast, network-info
|
Build-Depends: network-multicast, network-info
|
||||||
CPP-Options: -DWITH_PAIRING
|
CPP-Options: -DWITH_PAIRING
|
||||||
|
@ -239,19 +227,7 @@ Executable git-annex
|
||||||
if flag(DNS)
|
if flag(DNS)
|
||||||
Build-Depends: dns
|
Build-Depends: dns
|
||||||
CPP-Options: -DWITH_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)
|
if flag(TorrentParser)
|
||||||
Build-Depends: torrent (>= 10000.0.0)
|
Build-Depends: torrent (>= 10000.0.0)
|
||||||
CPP-Options: -DWITH_TORRENTPARSER
|
CPP-Options: -DWITH_TORRENTPARSER
|
||||||
|
|
Loading…
Add table
Reference in a new issue