{-# LANGUAGE OverloadedStrings #-}

-- |
-- Module      : Clod.FileSystem.Operations
-- Description : File system operations for Clod
-- Copyright   : (c) Fuzz Leonard, 2025
-- License     : MIT
-- Maintainer  : cyborg@bionicfuzz.com
-- Stability   : experimental
--
-- This module provides basic file system operations like finding files,
-- copying files, and safely removing files.

module Clod.FileSystem.Operations
  ( -- * File operations
    findAllFiles
  , copyFile
  , safeRemoveFile
  , safeReadFile
  , safeWriteFile
  , safeCopyFile
  ) where

import Control.Monad (when)
import Control.Monad.Except (throwError)
import Control.Monad.IO.Class (liftIO)
import System.Directory (doesDirectoryExist, doesFileExist, getDirectoryContents, removeFile, 
                        copyFile, canonicalizePath)
import System.FilePath ((</>))
import qualified Data.ByteString as BS

import Clod.Types (ClodM, FileReadCap(..), FileWriteCap(..), ClodError(..), isPathAllowed)

-- | Recursively find all files in a directory
--
-- This function takes a base path and a list of files/directories,
-- and recursively finds all files within those directories.
-- It returns paths relative to the base path.
--
-- @
-- -- Find all files in the "src" directory
-- files <- findAllFiles "/path/to/repo" ["src"]
--
-- -- Find all files in multiple directories
-- files <- findAllFiles "/path/to/repo" ["src", "docs", "tests"]
--
-- -- Find all files in the root directory (without "./" prefix)
-- files <- findAllFiles "/path/to/repo" [""]
-- @
findAllFiles :: FilePath -> [FilePath] -> ClodM [FilePath]
findAllFiles :: [Char] -> [[Char]] -> ClodM [[Char]]
findAllFiles [Char]
basePath = ([[[Char]]] -> [[Char]])
-> ReaderT ClodConfig (ExceptT ClodError IO) [[[Char]]]
-> ClodM [[Char]]
forall a b.
(a -> b)
-> ReaderT ClodConfig (ExceptT ClodError IO) a
-> ReaderT ClodConfig (ExceptT ClodError IO) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[[Char]]] -> [[Char]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (ReaderT ClodConfig (ExceptT ClodError IO) [[[Char]]]
 -> ClodM [[Char]])
-> ([[Char]]
    -> ReaderT ClodConfig (ExceptT ClodError IO) [[[Char]]])
-> [[Char]]
-> ClodM [[Char]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char] -> ClodM [[Char]])
-> [[Char]] -> ReaderT ClodConfig (ExceptT ClodError IO) [[[Char]]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM [Char] -> ClodM [[Char]]
findFilesRecursive
  where
    findFilesRecursive :: FilePath -> ClodM [FilePath]
    findFilesRecursive :: [Char] -> ClodM [[Char]]
findFilesRecursive [Char]
file = do
      -- Special case for empty string or "." to handle root directory
      -- without adding a "./" prefix to paths
      let useBasePath :: Bool
useBasePath = [Char] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
file Bool -> Bool -> Bool
|| [Char]
file [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
== [Char]
"."
          fullPath :: [Char]
fullPath = if Bool
useBasePath then [Char]
basePath else [Char]
basePath [Char] -> [Char] -> [Char]
</> [Char]
file
      
      isDir <- IO Bool -> ReaderT ClodConfig (ExceptT ClodError IO) Bool
forall a. IO a -> ReaderT ClodConfig (ExceptT ClodError IO) a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> ReaderT ClodConfig (ExceptT ClodError IO) Bool)
-> IO Bool -> ReaderT ClodConfig (ExceptT ClodError IO) Bool
forall a b. (a -> b) -> a -> b
$ [Char] -> IO Bool
doesDirectoryExist [Char]
fullPath
      
      case isDir of
        Bool
False -> [[Char]] -> ClodM [[Char]]
forall a. a -> ReaderT ClodConfig (ExceptT ClodError IO) a
forall (m :: * -> *) a. Monad m => a -> m a
return [[Char]
file]  -- Just return the file path
        Bool
True  -> do
          -- Get directory contents, excluding "." and ".."
          contents <- IO [[Char]] -> ClodM [[Char]]
forall a. IO a -> ReaderT ClodConfig (ExceptT ClodError IO) a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [[Char]] -> ClodM [[Char]]) -> IO [[Char]] -> ClodM [[Char]]
forall a b. (a -> b) -> a -> b
$ [Char] -> IO [[Char]]
getDirectoryContents [Char]
fullPath
          let validContents = ([Char] -> Bool) -> [[Char]] -> [[Char]]
forall a. (a -> Bool) -> [a] -> [a]
filter ([Char] -> [[Char]] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [[Char]
".", [Char]
".."]) [[Char]]
contents
          
          -- Recursively process subdirectories
          subFiles <- findAllFiles fullPath validContents
          
          -- Prepend current path to subdirectory files, but only if not the root dir
          return $ if useBasePath
                  then subFiles  -- For root dir, don't add any prefix
                  else map (file </>) subFiles  -- Otherwise add directory prefix

-- | Safely remove a file, ignoring errors if it doesn't exist
safeRemoveFile :: FilePath -> ClodM ()
safeRemoveFile :: [Char] -> ClodM ()
safeRemoveFile [Char]
path = do
  exists <- IO Bool -> ReaderT ClodConfig (ExceptT ClodError IO) Bool
forall a. IO a -> ReaderT ClodConfig (ExceptT ClodError IO) a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> ReaderT ClodConfig (ExceptT ClodError IO) Bool)
-> IO Bool -> ReaderT ClodConfig (ExceptT ClodError IO) Bool
forall a b. (a -> b) -> a -> b
$ [Char] -> IO Bool
doesFileExist [Char]
path
  when exists $ liftIO $ removeFile path

-- | Safe file reading that checks capabilities
safeReadFile :: FileReadCap -> FilePath -> ClodM BS.ByteString
safeReadFile :: FileReadCap -> [Char] -> ClodM ByteString
safeReadFile FileReadCap
cap [Char]
path = do
  allowed <- IO Bool -> ReaderT ClodConfig (ExceptT ClodError IO) Bool
forall a. IO a -> ReaderT ClodConfig (ExceptT ClodError IO) a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> ReaderT ClodConfig (ExceptT ClodError IO) Bool)
-> IO Bool -> ReaderT ClodConfig (ExceptT ClodError IO) Bool
forall a b. (a -> b) -> a -> b
$ [[Char]] -> [Char] -> IO Bool
isPathAllowed (FileReadCap -> [[Char]]
allowedReadDirs FileReadCap
cap) [Char]
path
  if allowed
    then liftIO $ BS.readFile path
    else do
      canonicalPath <- liftIO $ canonicalizePath path
      throwError $ CapabilityError $ "Access denied: Cannot read file outside allowed directories: " ++ canonicalPath

-- | Safe file writing that checks capabilities
safeWriteFile :: FileWriteCap -> FilePath -> BS.ByteString -> ClodM ()
safeWriteFile :: FileWriteCap -> [Char] -> ByteString -> ClodM ()
safeWriteFile FileWriteCap
cap [Char]
path ByteString
content = do
  allowed <- IO Bool -> ReaderT ClodConfig (ExceptT ClodError IO) Bool
forall a. IO a -> ReaderT ClodConfig (ExceptT ClodError IO) a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> ReaderT ClodConfig (ExceptT ClodError IO) Bool)
-> IO Bool -> ReaderT ClodConfig (ExceptT ClodError IO) Bool
forall a b. (a -> b) -> a -> b
$ [[Char]] -> [Char] -> IO Bool
isPathAllowed (FileWriteCap -> [[Char]]
allowedWriteDirs FileWriteCap
cap) [Char]
path
  if allowed
    then liftIO $ BS.writeFile path content
    else do
      canonicalPath <- liftIO $ canonicalizePath path
      throwError $ CapabilityError $ "Access denied: Cannot write file outside allowed directories: " ++ canonicalPath

-- | Safe file copying that checks capabilities for both read and write
safeCopyFile :: FileReadCap -> FileWriteCap -> FilePath -> FilePath -> ClodM ()
safeCopyFile :: FileReadCap -> FileWriteCap -> [Char] -> [Char] -> ClodM ()
safeCopyFile FileReadCap
readCap FileWriteCap
writeCap [Char]
src [Char]
dest = do
  srcAllowed <- IO Bool -> ReaderT ClodConfig (ExceptT ClodError IO) Bool
forall a. IO a -> ReaderT ClodConfig (ExceptT ClodError IO) a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> ReaderT ClodConfig (ExceptT ClodError IO) Bool)
-> IO Bool -> ReaderT ClodConfig (ExceptT ClodError IO) Bool
forall a b. (a -> b) -> a -> b
$ [[Char]] -> [Char] -> IO Bool
isPathAllowed (FileReadCap -> [[Char]]
allowedReadDirs FileReadCap
readCap) [Char]
src
  destAllowed <- liftIO $ isPathAllowed (allowedWriteDirs writeCap) dest
  if srcAllowed && destAllowed
    then liftIO $ copyFile src dest
    else do
      canonicalSrc <- liftIO $ canonicalizePath src
      canonicalDest <- liftIO $ canonicalizePath dest
      let errorMsg = if Bool -> Bool
not Bool
srcAllowed Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
destAllowed
                     then [Char]
"Access denied: Both source and destination paths violate restrictions"
                     else if Bool -> Bool
not Bool
srcAllowed
                          then [Char]
"Access denied: Source path violates restrictions: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
canonicalSrc
                          else [Char]
"Access denied: Destination path violates restrictions: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
canonicalDest
      throwError $ CapabilityError errorMsg