module System.IO.HVFS.Combinators ( 
                                    HVFSReadOnly(..),
                                    HVFSChroot, newHVFSChroot)
    where
import System.IO
import System.IO.Error
import System.IO.HVFS
import System.IO.HVFS.InstanceHelpers (getFullPath)
#ifndef mingw32_HOST_OS
import System.Posix.Files 
                          
#endif
import System.Path (secureAbsNormPath)
import System.Path.NameManip (normalise_path)
data HVFS a => HVFSReadOnly a = HVFSReadOnly a
                              deriving (Eq, Show)
withro :: HVFS a => (a -> b) -> HVFSReadOnly a -> b
withro f (HVFSReadOnly x) = f x
roerror :: (HVFS a) => HVFSReadOnly a -> IO c
roerror h =
    let err x = vRaiseError x permissionErrorType "Read-only virtual filesystem"
                  Nothing
        in withro err h
instance HVFS a => HVFS (HVFSReadOnly a) where
    vGetCurrentDirectory = withro vGetCurrentDirectory
    vSetCurrentDirectory = withro vSetCurrentDirectory
    vGetDirectoryContents = withro vGetDirectoryContents
    vDoesFileExist = withro vDoesFileExist
    vDoesDirectoryExist = withro vDoesDirectoryExist
    vCreateDirectory h _ = roerror h
    vRemoveDirectory h _ = roerror h
    vRenameDirectory h _ _ = roerror h
    vRenameFile h _ _ = roerror h
    vGetFileStatus = withro vGetFileStatus
    vGetSymbolicLinkStatus = withro vGetSymbolicLinkStatus
    vGetModificationTime = withro vGetModificationTime
    vRaiseError = withro vRaiseError
    vCreateSymbolicLink h _ _ = roerror h
    vReadSymbolicLink = withro vReadSymbolicLink
    vCreateLink h _ _ = roerror h
instance HVFSOpenable a => HVFSOpenable (HVFSReadOnly a) where
    vOpen fh fp mode =
        case mode of ReadMode -> withro (\h -> vOpen h fp mode) fh
                     _ -> roerror fh
data HVFS a => HVFSChroot a = HVFSChroot String a
                            deriving (Eq, Show)
newHVFSChroot :: HVFS a => a            
              -> FilePath               
              -> IO (HVFSChroot a)      
newHVFSChroot fh fp =
    do full <- getFullPath fh fp
       isdir <- vDoesDirectoryExist fh full
       if isdir
          then do let newobj = (HVFSChroot full fh)
                  vSetCurrentDirectory newobj "/"
                  return newobj
          else vRaiseError fh doesNotExistErrorType
                 ("Attempt to instantiate HVFSChroot over non-directory " ++ full)
                 (Just full)
dch :: (HVFS t) => HVFSChroot t -> t
dch (HVFSChroot _ a) = a
dch2fp, fp2dch :: (HVFS t) => HVFSChroot t -> String -> IO String
dch2fp mainh@(HVFSChroot fp h) locfp =
    do full <- case (head locfp) of
                  '/' -> return (fp ++ locfp)
                  _ -> do y <- getFullPath mainh locfp
                          return $ fp ++ y
       case secureAbsNormPath fp full of
           Nothing -> vRaiseError h doesNotExistErrorType
                        ("Trouble normalizing path in chroot")
                        (Just (fp ++ "," ++ full))
           Just x -> return x
fp2dch (HVFSChroot fp h) locfp =
    do newpath <- case secureAbsNormPath fp locfp of
                     Nothing -> vRaiseError h doesNotExistErrorType
                                  ("Unable to securely normalize path")
                                  (Just (fp ++ "/" ++ locfp))
                     Just x -> return x
       if (take (length fp) newpath /= fp)
               then vRaiseError h doesNotExistErrorType
                        ("Local path is not subdirectory of parent path")
                        (Just newpath)
               else let newpath2 = drop (length fp) newpath
                        in return $ normalise_path ("/" ++ newpath2)
dch2fph :: (HVFS t) => (t -> String -> IO t1) -> HVFSChroot t -> [Char] -> IO t1
dch2fph func fh@(HVFSChroot _ h) locfp =
    do newfp <- dch2fp fh locfp
       func h newfp
instance HVFS a => HVFS (HVFSChroot a) where
    vGetCurrentDirectory x = do fp <- vGetCurrentDirectory (dch x)
                                fp2dch x fp
    vSetCurrentDirectory = dch2fph vSetCurrentDirectory
    vGetDirectoryContents = dch2fph vGetDirectoryContents
    vDoesFileExist = dch2fph vDoesFileExist
    vDoesDirectoryExist = dch2fph vDoesDirectoryExist
    vCreateDirectory = dch2fph vCreateDirectory
    vRemoveDirectory = dch2fph vRemoveDirectory
    vRenameDirectory fh old new = do old' <- dch2fp fh old
                                     new' <- dch2fp fh new
                                     vRenameDirectory (dch fh) old' new'
    vRemoveFile = dch2fph vRemoveFile
    vRenameFile fh old new = do old' <- dch2fp fh old
                                new' <- dch2fp fh new
                                vRenameFile (dch fh) old' new'
    vGetFileStatus = dch2fph vGetFileStatus
    vGetSymbolicLinkStatus = dch2fph vGetSymbolicLinkStatus
    vGetModificationTime = dch2fph vGetModificationTime
    
    vCreateSymbolicLink fh old new = do old' <- dch2fp fh old
                                        new' <- dch2fp fh new
                                        vCreateSymbolicLink (dch fh) old' new'
    vReadSymbolicLink fh fp = do result <- dch2fph vReadSymbolicLink fh fp
                                 fp2dch fh result
    vCreateLink fh old new = do old' <- dch2fp fh old
                                new' <- dch2fp fh new
                                vCreateLink (dch fh) old' new'
instance HVFSOpenable a => HVFSOpenable (HVFSChroot a) where
    vOpen fh fp mode = do newfile <- dch2fp fh fp
                          vOpen (dch fh) newfile mode