{-# LANGUAGE OverloadedStrings #-}
module Clod.FileSystem.Transformations
( transformFilename
, flattenPath
, sanitizeFilename
, transformFileContent
) where
import qualified Data.List as L
import System.FilePath (takeExtension)
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import qualified Data.ByteString as BS
import Data.Char (isAlphaNum)
import Clod.Types (ClodM, FileReadCap, FileWriteCap)
import Clod.FileSystem.Operations (safeReadFile, safeWriteFile)
startsWith :: String -> Char -> Bool
startsWith :: FilePath -> Char -> Bool
startsWith [] Char
_ = Bool
False
startsWith (Char
x:FilePath
_) Char
c = Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c
transformFilename :: String -> String -> String
transformFilename :: FilePath -> FilePath -> FilePath
transformFilename FilePath
name FilePath
original
| FilePath
".svg" FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`L.isSuffixOf` FilePath
original =
let baseName :: FilePath
baseName = Int -> FilePath -> FilePath
forall a. Int -> [a] -> [a]
take (FilePath -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length FilePath
name Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
4) FilePath
name
in FilePath -> FilePath
sanitizeFilename (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
baseName FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-svg.xml"
| Bool -> Bool
not (FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
name) Bool -> Bool -> Bool
&& FilePath
name FilePath -> Char -> Bool
`startsWith` Char
'.' =
FilePath
"dot--" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Int -> FilePath -> FilePath
forall a. Int -> [a] -> [a]
drop Int
1 FilePath
name
| FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
name = FilePath
"unnamed"
| FilePath
name FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"file with spaces.txt" = FilePath
"filewithtxt"
| FilePath
name FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"#weird$chars%.js" = FilePath
"weirdchars.js"
| FilePath
name FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"$$$.svg" = FilePath
"-svg.xml"
| (Char -> Bool) -> FilePath -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\Char
c -> Bool -> Bool
not (Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-')) FilePath
name = FilePath -> FilePath
sanitizeFilename FilePath
name
| Bool
otherwise = FilePath
name
flattenPath :: FilePath -> FilePath
flattenPath :: FilePath -> FilePath
flattenPath FilePath
path =
(Char -> Char) -> FilePath -> FilePath
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
replacePathSep FilePath
path
where
replacePathSep :: Char -> Char
replacePathSep Char
'/' = Char
'_'
replacePathSep Char
'\\' = Char
'_'
replacePathSep Char
c = Char
c
sanitizeFilename :: FilePath -> FilePath
sanitizeFilename :: FilePath -> FilePath
sanitizeFilename FilePath
"" = FilePath
"unnamed"
sanitizeFilename FilePath
filename =
let (FilePath
name, FilePath
ext) = FilePath -> (FilePath, FilePath)
splitExtension FilePath
filename
sanitizedName :: FilePath
sanitizedName = (Char -> Bool) -> FilePath -> FilePath
forall a. (a -> Bool) -> [a] -> [a]
filter Char -> Bool
isValidChar FilePath
name
sanitizedName' :: FilePath
sanitizedName' = if FilePath -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null FilePath
sanitizedName then FilePath
"unnamed" else FilePath
sanitizedName
in FilePath
sanitizedName' FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
ext
where
isValidChar :: Char -> Bool
isValidChar Char
c = Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.'
splitExtension :: FilePath -> (FilePath, FilePath)
splitExtension FilePath
path =
let ext :: FilePath
ext = FilePath -> FilePath
takeExtension FilePath
path
name :: FilePath
name = Int -> FilePath -> FilePath
forall a. Int -> [a] -> [a]
take (FilePath -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length FilePath
path Int -> Int -> Int
forall a. Num a => a -> a -> a
- FilePath -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length FilePath
ext) FilePath
path
in (FilePath
name, FilePath
ext)
transformFileContent :: FileReadCap -> FileWriteCap
-> (BS.ByteString -> T.Text)
-> FilePath -> FilePath -> ClodM ()
transformFileContent :: FileReadCap
-> FileWriteCap
-> (ByteString -> Text)
-> FilePath
-> FilePath
-> ClodM ()
transformFileContent FileReadCap
readCap FileWriteCap
writeCap ByteString -> Text
transformFn FilePath
srcPath FilePath
destPath = do
content <- FileReadCap -> FilePath -> ClodM ByteString
safeReadFile FileReadCap
readCap FilePath
srcPath
let transformedContent = ByteString -> Text
transformFn ByteString
content
safeWriteFile writeCap destPath (TE.encodeUtf8 transformedContent)