-- Copyright (C) 2004 David Roundy
--
-- This program is free software; you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation; either version 2, or (at your option)
-- any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-- GNU General Public License for more details.
--
-- You should have received a copy of the GNU General Public License
-- along with this program; see the file COPYING.  If not, write to
-- the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor,
-- Boston, MA 02110-1301, USA.

module Darcs.CheckFileSystem ( can_I_use_mmap ) where

import System.Directory ( removeFile, removeDirectory, setCurrentDirectory,
                          createDirectory,
                        )
import Control.Exception ( block )

import Darcs.Utils ( withCurrentDirectory )
import Darcs.Lock ( withOpenTemp )

-- Beware that the below test will return true in any directory where we
-- don't have write permission.  This is risky, but means we'll do the
-- right thing in the common case where we're dealing with posix
-- filesystems and directories in which we don't have permission to write.

can_I_remove_open_files :: IO Bool
can_I_remove_open_files = block $ 
   (withOpenTemp $ \ (_,f) ->
       (do { removeFile f; return True}) `catch` \_ -> return False)
   `catch` \_ -> return True

can_I_remove_directories_holding_open_files :: IO Bool
can_I_remove_directories_holding_open_files = block $
   (do createDirectory "darcs_testing_for_nfs"
       okay <- (withCurrentDirectory "darcs_testing_for_nfs" $
                do withOpenTemp $ \ (_,f) -> 
                       (do removeFile f
                           setCurrentDirectory ".."
                           removeDirectory "darcs_testing_for_nfs"
                           return True
                       ) `catch` \_ -> return False
               ) `catch` \_ -> return True
       removeDirectory "darcs_testing_for_nfs" `catch` \_ -> return ()
       return okay
   ) `catch` \_ -> return True

can_I_use_mmap :: IO Bool
can_I_use_mmap = do a <- can_I_remove_open_files
                    if a then can_I_remove_directories_holding_open_files
                         else return False