Merge branch 'no-cbits'

This commit is contained in:
Joey Hess 2016-03-05 11:22:32 -04:00
commit be80c29dbc
Failed to extract signature
15 changed files with 93 additions and 483 deletions

View file

@ -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 Annex.Ingest ( module Annex.Ingest (
LockedDown(..), LockedDown(..),
LockDownConfig(..), LockDownConfig(..),
@ -42,13 +40,9 @@ import Utility.InodeCache
import Annex.ReplaceFile import Annex.ReplaceFile
import Utility.Tmp import Utility.Tmp
import Utility.CopyFile import Utility.CopyFile
import Utility.Touch
import Git.FilePath import Git.FilePath
import Annex.InodeSentinal import Annex.InodeSentinal
#ifdef WITH_CLIBS
#ifndef __ANDROID__
import Utility.Touch
#endif
#endif
import Control.Exception (IOException) import Control.Exception (IOException)
@ -282,11 +276,7 @@ makeLink file key mcache = flip catchNonAsync (restoreFile file key) $ do
-- touch symlink to have same time as the original file, -- touch symlink to have same time as the original file,
-- as provided in the InodeCache -- as provided in the InodeCache
case mcache of case mcache of
#if defined(WITH_CLIBS) && ! defined(__ANDROID__)
Just c -> liftIO $ touch file (TimeSpec $ inodeCacheToMtime c) False Just c -> liftIO $ touch file (TimeSpec $ inodeCacheToMtime c) False
#else
Just _ -> noop
#endif
Nothing -> noop Nothing -> noop
return l return l

View file

@ -25,7 +25,7 @@ import Assistant.Threads.RemoteControl
import Assistant.Threads.SanityChecker import Assistant.Threads.SanityChecker
import Assistant.Threads.Cronner import Assistant.Threads.Cronner
import Assistant.Threads.ProblemFixer import Assistant.Threads.ProblemFixer
#ifdef WITH_CLIBS #ifndef mingw32_HOST_OS
import Assistant.Threads.MountWatcher import Assistant.Threads.MountWatcher
#endif #endif
import Assistant.Threads.NetWatcher import Assistant.Threads.NetWatcher
@ -170,7 +170,7 @@ startDaemon assistant foreground startdelay cannotrun listenhost startbrowser =
, assist $ sanityCheckerDailyThread urlrenderer , assist $ sanityCheckerDailyThread urlrenderer
, assist sanityCheckerHourlyThread , assist sanityCheckerHourlyThread
, assist $ problemFixerThread urlrenderer , assist $ problemFixerThread urlrenderer
#ifdef WITH_CLIBS #ifndef mingw32_HOST_OS
, assist $ mountWatcherThread urlrenderer , assist $ mountWatcherThread urlrenderer
#endif #endif
, assist netWatcherThread , assist netWatcherThread

View file

@ -24,9 +24,7 @@ import qualified Git.Branch
import Config.Files import Config.Files
import Utility.FreeDesktop import Utility.FreeDesktop
import Utility.DiskFree import Utility.DiskFree
#ifdef WITH_CLIBS
import Utility.Mounts import Utility.Mounts
#endif
import Utility.DataUnits import Utility.DataUnits
import Remote (prettyUUID) import Remote (prettyUUID)
import Annex.UUID import Annex.UUID
@ -359,7 +357,6 @@ driveList :: IO [RemovableDrive]
-- Could use wmic, but it only works for administrators. -- Could use wmic, but it only works for administrators.
driveList = mapM (\d -> genRemovableDrive $ d:":\\") ['A'..'Z'] driveList = mapM (\d -> genRemovableDrive $ d:":\\") ['A'..'Z']
#else #else
#ifdef WITH_CLIBS
driveList = mapM (genRemovableDrive . mnt_dir) =<< filter sane <$> getMounts driveList = mapM (genRemovableDrive . mnt_dir) =<< filter sane <$> getMounts
where where
-- filter out some things that are surely not removable drives -- filter out some things that are surely not removable drives
@ -379,9 +376,6 @@ driveList = mapM (genRemovableDrive . mnt_dir) =<< filter sane <$> getMounts
| dir == "/sdcard" = False | dir == "/sdcard" = False
#endif #endif
| otherwise = True | otherwise = True
#else
driveList = return []
#endif
#endif #endif
genRemovableDrive :: FilePath -> IO RemovableDrive genRemovableDrive :: FilePath -> IO RemovableDrive

View file

@ -18,11 +18,7 @@ import Annex.Content
import Annex.Perms import Annex.Perms
import qualified Annex.Queue import qualified Annex.Queue
import qualified Database.Keys import qualified Database.Keys
#ifdef WITH_CLIBS
#ifndef __ANDROID__
import Utility.Touch import Utility.Touch
#endif
#endif
cmd :: Command cmd :: Command
cmd = notDirect $ noCommit $ withGlobalOptions annexedMatchingOptions $ cmd = notDirect $ noCommit $ withGlobalOptions annexedMatchingOptions $
@ -90,20 +86,16 @@ makeHardLink file key = do
fixSymlink :: FilePath -> FilePath -> CommandPerform fixSymlink :: FilePath -> FilePath -> CommandPerform
fixSymlink file link = do fixSymlink file link = do
liftIO $ do liftIO $ do
#ifdef WITH_CLIBS #if ! defined(mingw32_HOST_OS) && ! defined(__ANDROID__)
#ifndef __ANDROID__
-- preserve mtime of symlink -- preserve mtime of symlink
mtime <- catchMaybeIO $ TimeSpec . modificationTime mtime <- catchMaybeIO $ TimeSpec . modificationTime
<$> getSymbolicLinkStatus file <$> getSymbolicLinkStatus file
#endif
#endif #endif
createDirectoryIfMissing True (parentDir file) createDirectoryIfMissing True (parentDir file)
removeFile file removeFile file
createSymbolicLink link file createSymbolicLink link file
#ifdef WITH_CLIBS #if ! defined(mingw32_HOST_OS) && ! defined(__ANDROID__)
#ifndef __ANDROID__
maybe noop (\t -> touch file t False) mtime maybe noop (\t -> touch file t False) mtime
#endif
#endif #endif
next $ cleanupSymlink file next $ cleanupSymlink file

View file

@ -1,70 +1,23 @@
{- disk free space checking {- disk free space checking shim
- -
- Copyright 2012, 2014 Joey Hess <id@joeyh.name> - Copyright 2016 Joey Hess <id@joeyh.name>
- -
- License: BSD-2-clause - License: BSD-2-clause
-} -}
{-# LANGUAGE ForeignFunctionInterface, CPP #-} {-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.DiskFree ( module Utility.DiskFree (
getDiskFree, getDiskFree,
getDiskSize getDiskSize
) where ) where
#ifdef WITH_CLIBS import System.DiskSpace
import Utility.Applicative
import Common import Utility.Exception
import Foreign.C.Types
import Foreign.C.String
import Foreign.C.Error
foreign import ccall safe "libdiskfree.h diskfree" c_diskfree
:: CString -> IO CULLong
foreign import ccall safe "libdiskfree.h disksize" c_disksize
:: CString -> IO CULLong
getVal :: (CString -> IO CULLong) -> FilePath -> IO (Maybe Integer)
getVal getter path = withFilePath path $ \c_path -> do
free <- getter c_path
ifM (safeErrno <$> getErrno)
( return $ Just $ toInteger free
, return Nothing
)
where
safeErrno (Errno v) = v == 0
getDiskFree :: FilePath -> IO (Maybe Integer) getDiskFree :: FilePath -> IO (Maybe Integer)
getDiskFree = getVal c_diskfree getDiskFree = catchMaybeIO . getAvailSpace
getDiskSize :: FilePath -> IO (Maybe Integer) getDiskSize :: FilePath -> IO (Maybe Integer)
getDiskSize = getVal c_disksize getDiskSize = fmap diskTotal <$$> catchMaybeIO . getDiskUsage
#else
#ifdef mingw32_HOST_OS
import Common
import System.Win32.File
getDiskFree :: FilePath -> IO (Maybe Integer)
getDiskFree path = catchMaybeIO $ do
(sectors, bytes, nfree, _ntotal) <- getDiskFreeSpace (Just path)
return $ toInteger sectors * toInteger bytes * toInteger nfree
getDiskSize :: FilePath -> IO (Maybe Integer)
getDiskSize _ = return Nothing
#else
#warning Building without disk free space checking support
getDiskFree :: FilePath -> IO (Maybe Integer)
getDiskFree _ = return Nothing
getDiskSize :: FilePath -> IO (Maybe Integer)
getDiskSize _ = return Nothing
#endif
#endif

21
Utility/Mounts.hs Normal file
View file

@ -0,0 +1,21 @@
{- portability shim for System.MountPoints
-
- Copyright 2016 Joey Hess <id@joeyh.name>
-
- License: BSD-2-clause
-}
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.Mounts (getMounts, Mntent(..)) where
import qualified System.MountPoints
import System.MountPoints (Mntent(..))
getMounts :: IO [Mntent]
#ifndef __ANDROID__
getMounts = System.MountPoints.getMounts
#else
getMounts = System.MountPoints.getProcMounts
#endif

View file

@ -1,97 +0,0 @@
{- Interface to mtab (and fstab)
-
- Deprecated; moving to mountpoints library on hackage.
-
- Derived from hsshellscript, originally written by
- Volker Wysk <hsss@volker-wysk.de>
-
- Modified to support BSD, Mac OS X, and Android by
- Joey Hess <id@joeyh.name>
-
- Licensed under the GNU LGPL version 2.1 or higher.
-
-}
{-# LANGUAGE ForeignFunctionInterface #-}
module Utility.Mounts (
Mntent(..),
getMounts
) where
#ifndef __ANDROID__
import Control.Monad
import Foreign
import Foreign.C
#include "libmounts.h"
#else
import Utility.Exception
import Data.Maybe
import Control.Applicative
#endif
import Prelude
{- This is a stripped down mntent, containing only
- fields available everywhere. -}
data Mntent = Mntent
{ mnt_fsname :: String
, mnt_dir :: FilePath
, mnt_type :: String
} deriving (Show, Eq, Ord)
#ifndef __ANDROID__
getMounts :: IO [Mntent]
getMounts = do
h <- c_mounts_start
when (h == nullPtr) $
throwErrno "getMounts"
mntent <- getmntent h []
_ <- c_mounts_end h
return mntent
where
getmntent h c = do
ptr <- c_mounts_next h
if (ptr == nullPtr)
then return $ reverse c
else do
mnt_fsname_str <- #{peek struct mntent, mnt_fsname} ptr >>= peekCString
mnt_dir_str <- #{peek struct mntent, mnt_dir} ptr >>= peekCString
mnt_type_str <- #{peek struct mntent, mnt_type} ptr >>= peekCString
let ent = Mntent
{ mnt_fsname = mnt_fsname_str
, mnt_dir = mnt_dir_str
, mnt_type = mnt_type_str
}
getmntent h (ent:c)
{- Using unsafe imports because the C functions are belived to never block.
- Note that getmntinfo is called with MNT_NOWAIT to avoid possibly blocking;
- while getmntent only accesses a file in /etc (or /proc) that should not
- block. -}
foreign import ccall unsafe "libmounts.h mounts_start" c_mounts_start
:: IO (Ptr ())
foreign import ccall unsafe "libmounts.h mounts_next" c_mounts_next
:: Ptr () -> IO (Ptr ())
foreign import ccall unsafe "libmounts.h mounts_end" c_mounts_end
:: Ptr () -> IO CInt
#else
{- Android does not support getmntent (well, it's a no-op stub in Bionic).
-
- But, the linux kernel's /proc/mounts is available to be parsed.
-}
getMounts :: IO [Mntent]
getMounts = catchDefaultIO [] $
mapMaybe (parse . words) . lines <$> readFile "/proc/mounts"
where
parse (device:mountpoint:fstype:_rest) = Just $ Mntent
{ mnt_fsname = device
, mnt_dir = mountpoint
, mnt_type = fstype
}
parse _ = Nothing
#endif

52
Utility/Touch.hs Normal file
View file

@ -0,0 +1,52 @@
{- More control over touching a file.
-
- Copyright 2011 Joey Hess <id@joeyh.name>
-
- License: BSD-2-clause
-}
{-# LANGUAGE CPP #-}
module Utility.Touch (
TimeSpec(..),
touchBoth,
touch
) where
#if ! defined(mingw32_HOST_OS) && ! defined(__ANDROID__)
#if MIN_VERSION_unix(2,7,0)
import System.Posix.Files
import System.Posix.Types
newtype TimeSpec = TimeSpec EpochTime
{- Changes the access and modification times of an existing file.
Can follow symlinks, or not. Throws IO error on failure. -}
touchBoth :: FilePath -> TimeSpec -> TimeSpec -> Bool -> IO ()
touchBoth file (TimeSpec atime) (TimeSpec mtime) follow
| follow = setFileTimes file atime mtime
| otherwise = setSymbolicLinkTimesHiRes file (realToFrac atime) (realToFrac mtime)
touch :: FilePath -> TimeSpec -> Bool -> IO ()
touch file mtime = touchBoth file mtime mtime
#else
import Utility.Touch.Old
#endif
#else
import System.PosixCompat
newtype TimeSpec = TimeSpec EpochTime
{- Noop for Windows -}
touchBoth FilePath -> TimeSpec -> TimeSpec -> Bool -> IO ()
touchBoth _ _ _ _ = return ()
touch :: FilePath -> TimeSpec -> Bool -> IO ()
touch _ _ = return ()
#endif

View file

@ -1,4 +1,4 @@
{- More control over touching a file. {- Compatability interface for old version of unix, to be removed eventally.
- -
- Copyright 2011 Joey Hess <id@joeyh.name> - Copyright 2011 Joey Hess <id@joeyh.name>
- -
@ -7,32 +7,12 @@
{-# LANGUAGE ForeignFunctionInterface, CPP #-} {-# LANGUAGE ForeignFunctionInterface, CPP #-}
module Utility.Touch ( module Utility.Touch.Old (
TimeSpec(..), TimeSpec(..),
touchBoth, touchBoth,
touch touch
) where ) where
#if MIN_VERSION_unix(2,7,0)
import System.Posix.Files
import System.Posix.Types
newtype TimeSpec = TimeSpec EpochTime
{- Changes the access and modification times of an existing file.
Can follow symlinks, or not. Throws IO error on failure. -}
touchBoth :: FilePath -> TimeSpec -> TimeSpec -> Bool -> IO ()
touchBoth file (TimeSpec atime) (TimeSpec mtime) follow
| follow = setFileTimes file atime mtime
| otherwise = setSymbolicLinkTimesHiRes file (realToFrac atime) (realToFrac mtime)
touch :: FilePath -> TimeSpec -> Bool -> IO ()
touch file mtime = touchBoth file mtime mtime
#else
{- Compatability interface for old version of unix, to be removed eventally. -}
#include <sys/types.h> #include <sys/types.h>
#include <sys/stat.h> #include <sys/stat.h>
#include <fcntl.h> #include <fcntl.h>
@ -141,5 +121,3 @@ touchBoth file atime mtime follow =
touchBoth _ _ _ _ = return () touchBoth _ _ _ _ = return ()
#endif #endif
#endif #endif
#endif

View file

@ -1,84 +0,0 @@
/* disk free space checking, C mini-library
*
* Copyright 2012, 2014 Joey Hess <id@joeyh.name>
*
* License: BSD-2-clause
*/
/* Include appropriate headers for the OS, and define what will be used to
* check the free space. */
#if defined (__FreeBSD__)
# include <sys/param.h>
# include <sys/mount.h>
# define STATCALL statfs /* statfs64 not yet tested on a real FreeBSD machine */
# define STATSTRUCT statfs
# define BSIZE f_bsize
#else
#if defined __ANDROID__
# warning free space checking code not available for Android
# define UNKNOWN
#else
#if defined (__linux__) || defined (__APPLE__) || defined (__FreeBSD_kernel__) || (defined (__SVR4) && defined (__sun))
/* Linux or OSX or Debian kFreeBSD or Solaris */
/* This is a POSIX standard, so might also work elsewhere too. */
# include <sys/statvfs.h>
# define STATCALL statvfs
# define STATSTRUCT statvfs
# define BSIZE f_frsize
#else
# warning free space checking code not available for this OS
# define UNKNOWN
#endif
#endif
#endif
#include <errno.h>
#include <stdio.h>
unsigned long long int get(const char *path, int req) {
#ifdef UNKNOWN
errno = 1;
return 0;
#else
unsigned long long int v, blocksize;
struct STATSTRUCT buf;
if (STATCALL(path, &buf) != 0)
return 0; /* errno is set */
else
errno = 0;
switch (req) {
case 0:
v = buf.f_blocks;
break;
case 1:
v = buf.f_bavail;
break;
default:
v = 0;
}
blocksize = buf.BSIZE;
return v * blocksize;
#endif
}
/* Checks the amount of disk that is available to regular (non-root) users.
* (If there's an error, or this is not supported,
* returns 0 and sets errno to nonzero.)
*/
unsigned long long int diskfree(const char *path) {
return get(path, 1);
}
/* Gets the total size of the disk. */
unsigned long long int disksize(const char *path) {
return get(path, 0);
}
/*
main () {
printf("%lli\n", diskfree("."));
}
*/

View file

@ -1 +0,0 @@
unsigned long long int diskfree(const char *path);

View file

@ -1,103 +0,0 @@
/* mounted filesystems, C mini-library
*
* Copyright (c) 1980, 1989, 1993, 1994
* The Regents of the University of California. All rights reserved.
* Copyright (c) 2001
* David Rufino <daverufino@btinternet.com>
* Copyright 2012
* Joey Hess <id@joeyh.name>
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
* 3. Neither the name of the University nor the names of its contributors
* may be used to endorse or promote products derived from this software
* without specific prior written permission.
*
* THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
* ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
* IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
* ARE DISCLAIMED. IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
* FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
* DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
* OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
* HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
* LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
* OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
* SUCH DAMAGE.
*/
#include "libmounts.h"
#ifdef GETMNTENT
/* direct passthrough the getmntent */
FILE *mounts_start (void) {
return setmntent("/etc/mtab", "r");
}
int mounts_end (FILE *fp) {
return endmntent(fp);
}
struct mntent *mounts_next (FILE *fp) {
return getmntent(fp);
}
#endif
#ifdef GETMNTINFO
/* getmntent emulation using getmntinfo */
FILE *mounts_start (void) {
return ((FILE *)0x1); /* dummy non-NULL FILE pointer, not used */
}
int mounts_end (FILE *fp) {
return 1;
}
static struct mntent _mntent;
static struct mntent *statfs_to_mntent (struct statfs *mntbuf) {
_mntent.mnt_fsname = mntbuf->f_mntfromname;
_mntent.mnt_dir = mntbuf->f_mntonname;
_mntent.mnt_type = mntbuf->f_fstypename;
_mntent.mnt_opts = NULL;
_mntent.mnt_freq = 0;
_mntent.mnt_passno = 0;
return (&_mntent);
}
static int pos = -1;
static int mntsize = -1;
struct statfs *mntbuf = NULL;
struct mntent *mounts_next (FILE *fp) {
if (pos == -1 || mntsize == -1)
mntsize = getmntinfo(&mntbuf, MNT_NOWAIT);
++pos;
if (pos == mntsize) {
pos = mntsize = -1;
mntbuf = NULL;
return NULL;
}
return (statfs_to_mntent(&mntbuf[pos]));
}
#endif
#ifdef UNKNOWN
/* dummy, do-nothing version */
FILE *mounts_start (void) {
return ((FILE *)0x1);
}
int mounts_end (FILE *fp) {
return 1;
}
struct mntent *mounts_next (FILE *fp) {
return NULL;
}
#endif

View file

@ -1,38 +0,0 @@
/* Include appropriate headers for the OS, and define what will be used. */
#if defined (__FreeBSD__) || defined (__APPLE__)
# include <sys/param.h>
# include <sys/ucred.h>
# include <sys/mount.h>
# define GETMNTINFO
#else
#if defined __ANDROID__
/* Android is handled by the Haskell code, not here. */
# define UNKNOWN
#else
#if defined (__linux__) || defined (__FreeBSD_kernel__)
/* Linux or Debian kFreeBSD */
#include <mntent.h>
# define GETMNTENT
#else
# warning mounts listing code not available for this OS
# define UNKNOWN
#endif
#endif
#endif
#include <stdio.h>
#ifndef GETMNTENT
struct mntent {
char *mnt_fsname;
char *mnt_dir;
char *mnt_type;
char *mnt_opts; /* not filled in */
int mnt_freq; /* not filled in */
int mnt_passno; /* not filled in */
};
#endif
FILE *mounts_start (void);
int mounts_end (FILE *fp);
struct mntent *mounts_next (FILE *fp);

45
debian/copyright vendored
View file

@ -35,10 +35,6 @@ Copyright: 2007 Henrik Nyh <http://henrik.nyh.se/>
License: other License: other
Free to modify and redistribute with due credit, and obviously free to use. Free to modify and redistribute with due credit, and obviously free to use.
Files: Utility/Mounts.hsc
Copyright: Volker Wysk <hsss@volker-wysk.de>
License: LGPL-2.1+
Files: Annex/DirHashes.hs Files: Annex/DirHashes.hs
Copyright: 2001 Ian Lynagh Copyright: 2001 Ian Lynagh
2010-2015 Joey Hess <id@joeyh.name> 2010-2015 Joey Hess <id@joeyh.name>
@ -49,42 +45,6 @@ Copyright: 2014 Joey Hess <id@joeyh.name>
2016 Klaus Ethgen <Klaus@Ethgen.ch> 2016 Klaus Ethgen <Klaus@Ethgen.ch>
License: GPL-3+ License: GPL-3+
Files: Utility/libmounts.c
Copyright: 1980, 1989, 1993, 1994 The Regents of the University of California
2001 David Rufino <daverufino@btinternet.com>
2012 Joey Hess <id@joeyh.name>
License: BSD-3-clause
* Copyright (c) 1980, 1989, 1993, 1994
* The Regents of the University of California. All rights reserved.
* Copyright (c) 2001
* David Rufino <daverufino@btinternet.com>
* Copyright 2012
* Joey Hess <id@joeyh.name>
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
* 3. Neither the name of the University nor the names of its contributors
* may be used to endorse or promote products derived from this software
* without specific prior written permission.
*
* THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
* ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
* IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
* ARE DISCLAIMED. IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
* FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
* DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
* OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
* HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
* LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
* OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
* SUCH DAMAGE.
Files: static/jquery* Files: static/jquery*
Copyright: © 2005-2011 by John Resig, Branden Aaron & Jörn Zaefferer Copyright: © 2005-2011 by John Resig, Branden Aaron & Jörn Zaefferer
© 2011 The Dojo Foundation © 2011 The Dojo Foundation
@ -140,11 +100,6 @@ License: GPL-3+
this package's source, or in /usr/share/common-licenses/GPL-3 on this package's source, or in /usr/share/common-licenses/GPL-3 on
Debian systems. Debian systems.
License: LGPL-2.1+
The full text of version 2.1 of the LGPL is distributed as doc/license/LGPL
in this package's source, or in /usr/share/common-licenses/LGPL-2.1
on Debian systems.
License: BSD-2-clause License: BSD-2-clause
Redistribution and use in source and binary forms, with or without Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions modification, are permitted provided that the following conditions

View file

@ -111,7 +111,8 @@ Executable git-annex
esqueleto, persistent-sqlite, persistent, persistent-template, esqueleto, persistent-sqlite, persistent, persistent-template,
aeson, aeson,
feed, feed,
regex-tdfa regex-tdfa,
disk-free-space
CC-Options: -Wall CC-Options: -Wall
GHC-Options: -Wall -fno-warn-tabs GHC-Options: -Wall -fno-warn-tabs
Extensions: PackageImports Extensions: PackageImports
@ -143,11 +144,8 @@ Executable git-annex
process (>= 1.3.0.0) process (>= 1.3.0.0)
else else
Build-Depends: unix Build-Depends: unix
-- Need to list these because they're generated from .hsc files. if impl(ghc <= 7.6.3)
Other-Modules: Utility.Touch Utility.Mounts Other-Modules: Utility.Touch.Old
Include-Dirs: Utility
C-Sources: Utility/libdiskfree.c Utility/libmounts.c
CPP-Options: -DWITH_CLIBS
if flag(TestSuite) if flag(TestSuite)
Build-Depends: tasty (>= 0.7), tasty-hunit, tasty-quickcheck, tasty-rerun, Build-Depends: tasty (>= 0.7), tasty-hunit, tasty-quickcheck, tasty-rerun,
@ -163,7 +161,7 @@ Executable git-annex
CPP-Options: -DWITH_WEBDAV CPP-Options: -DWITH_WEBDAV
if flag(Assistant) && ! os(solaris) if flag(Assistant) && ! os(solaris)
Build-Depends: dns Build-Depends: dns, mountpoints
CPP-Options: -DWITH_ASSISTANT CPP-Options: -DWITH_ASSISTANT
if flag(Assistant) if flag(Assistant)