module Foundation.VFS.FilePath
( FilePath
, Relativity(..)
, FileName
, filePathToString
, filePathToLString
, unsafeFilePath
, unsafeFileName
, extension
) where
import Foundation.Internal.Base
import Foundation.Collection
import Foundation.Array
import Foundation.String (Encoding(..), ValidationFailure, toBytes, fromBytes, String)
import Foundation.VFS.Path(Path(..))
import qualified Data.List
#ifdef mingw32_HOST_OS
pathSeparatorWINC :: Char
pathSeparatorWINC = '\\'
pathSeparatorWIN :: String
pathSeparatorWIN = fromString [pathSeparatorWINC]
#else
pathSeparatorPOSIXC :: Char
pathSeparatorPOSIXC = '/'
pathSeparatorPOSIX :: String
pathSeparatorPOSIX = fromString [pathSeparatorPOSIXC]
#endif
pathSeparatorC :: Char
pathSeparator :: String
#ifdef mingw32_HOST_OS
pathSeparatorC = pathSeparatorWINC
pathSeparator = pathSeparatorWIN
#else
pathSeparatorC = pathSeparatorPOSIXC
pathSeparator = pathSeparatorPOSIX
#endif
data Relativity = Absolute | Relative
deriving (Eq, Show)
data FilePath = FilePath Relativity [FileName]
instance Show FilePath where
show = filePathToLString
instance Eq FilePath where
(==) a b = (==) (show a) (show b)
instance Ord FilePath where
compare a b = compare (show a) (show b)
data FilePath_Invalid
= ContiguousPathSeparator
deriving (Typeable, Show)
instance Exception FilePath_Invalid
instance IsString FilePath where
fromString [] = FilePath Absolute mempty
fromString s@(x:xs)
| hasContigueSeparators s = throw ContiguousPathSeparator
| otherwise = FilePath relativity $ case relativity of
Absolute -> fromString <$> splitOn isSeparator xs
Relative -> fromString <$> splitOn isSeparator s
where
relativity :: Relativity
relativity = if isSeparator x then Absolute else Relative
data FileName = FileName (UArray Word8)
deriving (Eq)
data FileName_Invalid
= ContainsNullByte
| ContainsSeparator
| EncodingError ValidationFailure
| UnknownTrailingBytes (UArray Word8)
deriving (Typeable, Show)
instance Exception FileName_Invalid
instance Show FileName where
show = fileNameToLString
instance IsString FileName where
fromString [] = FileName mempty
fromString xs | hasNullByte xs = throw ContainsNullByte
| hasSeparator xs = throw ContainsSeparator
| otherwise = FileName $ toBytes UTF8 $ fromString xs
hasNullByte :: [Char] -> Bool
hasNullByte = Data.List.elem '\0'
hasSeparator :: [Char] -> Bool
hasSeparator = Data.List.elem pathSeparatorC
isSeparator :: Char -> Bool
isSeparator = (==) pathSeparatorC
hasContigueSeparators :: [Char] -> Bool
hasContigueSeparators [] = False
hasContigueSeparators [_] = False
hasContigueSeparators (x1:x2:xs) =
(isSeparator x1 && x1 == x2) || hasContigueSeparators xs
instance Monoid FileName where
mempty = FileName mempty
mappend (FileName a) (FileName b) = FileName $ a `mappend` b
instance Path FilePath where
type PathEnt FilePath = FileName
type PathPrefix FilePath = Relativity
type PathSuffix FilePath = ()
(</>) = join
splitPath (FilePath r xs) = (r, xs, ())
buildPath (r, xs , _) = FilePath r xs
join :: FilePath -> FileName -> FilePath
join p (FileName x) | null x = p
join (FilePath r xs) x = FilePath r $ snoc xs x
filePathToString :: FilePath -> String
filePathToString (FilePath Absolute []) = fromString [pathSeparatorC]
filePathToString (FilePath Relative []) = fromString "."
filePathToString (FilePath Absolute fns) = cons pathSeparatorC $ filenameIntercalate fns
filePathToString (FilePath Relative fns) = filenameIntercalate fns
filenameIntercalate :: [FileName] -> String
filenameIntercalate = mconcat . Data.List.intersperse pathSeparator . fmap fileNameToString
fileNameToString :: FileName -> String
fileNameToString (FileName fp) =
case fromBytes UTF8 fp of
(s, Nothing, bs)
| null bs -> s
| otherwise -> throw $ UnknownTrailingBytes bs
(_, Just err, _) -> throw $ EncodingError err
fileNameToLString :: FileName -> [Char]
fileNameToLString = toList . fileNameToString
filePathToLString :: FilePath -> [Char]
filePathToLString = toList . filePathToString
unsafeFilePath :: Relativity -> [FileName] -> FilePath
unsafeFilePath = FilePath
unsafeFileName :: UArray Word8 -> FileName
unsafeFileName = FileName
extension :: FileName -> Maybe FileName
extension (FileName fn) = case splitOn (\c -> c == 0x2E) fn of
[] -> Nothing
[_] -> Nothing
xs -> Just $ FileName $ last $ nonEmpty_ xs