module Filesystem.Path.Internal where
import           Prelude hiding (FilePath)
import           Control.DeepSeq (NFData, rnf)
import qualified Control.Exception as Exc
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as B8
import           Data.Char (chr, ord)
import           Data.Data (Data)
import           Data.List (intersperse)
import           Data.Ord (comparing)
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import           Data.Text.Encoding.Error (UnicodeException)
import           Data.Typeable (Typeable)
import           System.IO.Unsafe (unsafePerformIO)
type Chunk = String
type Directory = Chunk
type Basename = Chunk
type Extension = Chunk
data Root
	= RootPosix
	| RootWindowsVolume Char
	| RootWindowsCurrentVolume
	deriving (Eq, Ord, Data, Typeable)
data FilePath = FilePath
	{ pathRoot :: Maybe Root
	, pathDirectories :: [Directory]
	, pathBasename :: Maybe Basename
	, pathExtensions :: [Extension]
	}
	deriving (Data, Typeable)
instance Eq FilePath where
	x == y = compare x y == EQ
instance Ord FilePath where
	compare = comparing (\p ->
		(pathRoot p
		, fmap unescape' (pathDirectories p)
		, fmap unescape' (pathBasename p)
		, fmap unescape' (pathExtensions p)
		))
instance NFData Root where
	rnf (RootWindowsVolume c) = rnf c
	rnf _ = ()
instance NFData FilePath where
	rnf p = rnf (pathRoot p) `seq` rnf (pathDirectories p) `seq` rnf (pathBasename p) `seq` rnf (pathExtensions p)
empty :: FilePath
empty = FilePath Nothing [] Nothing []
dot :: Chunk
dot = "."
dots :: Chunk
dots = ".."
filenameChunk :: FilePath -> Chunk
filenameChunk p = concat (name:exts) where
	name = maybe "" id (pathBasename p)
	exts = case pathExtensions p of
		[] -> []
		exts' -> intersperse dot ("":exts')
rootChunk :: Maybe Root -> Chunk
rootChunk r = flip (maybe "") r $ \r' -> case r' of
	RootPosix -> "/"
	RootWindowsVolume c -> c : ":\\"
	RootWindowsCurrentVolume -> "\\"
rootText :: Maybe Root -> T.Text
rootText = T.pack . rootChunk
directoryChunks :: FilePath -> [Chunk]
directoryChunks path = pathDirectories path ++ [filenameChunk path]
data Rules platformFormat = Rules
	{ rulesName :: T.Text
	
	
	
	
	, valid :: FilePath -> Bool
	
	
	
	, splitSearchPath :: platformFormat -> [FilePath]
	
	
	
	
	
	
	
	
	
	
	
	
	
	
	
	
	
	
	
	, toText :: FilePath -> Either T.Text T.Text
	
	
	
	
	
	
	
	
	
	, fromText :: T.Text -> FilePath
	
	
	
	
	
	, encode :: FilePath -> platformFormat
	
	
	
	
	
	, decode :: platformFormat -> FilePath
	
	
	
	
	
	
	
	
	, encodeString :: FilePath -> String
	
	
	
	
	
	
	
	
	, decodeString :: String -> FilePath
	}
instance Show (Rules a) where
	showsPrec d r = showParen (d > 10)
		(showString "Rules " . shows (rulesName r))
escape :: T.Text -> Chunk
escape t = T.unpack t
unescape :: Chunk -> (T.Text, Bool)
unescape cs = if any (\c -> ord c >= 0xDC80 && ord c <= 0xDCFF) cs
	then (T.pack (map (\c -> if ord c >= 0xDC80 && ord c <= 0xDCFF
		then chr (ord c  0xDC00)
		else c) cs), False)
	else (T.pack cs, True)
unescape' :: Chunk -> T.Text
unescape' = fst . unescape
unescapeBytes' :: Chunk -> B.ByteString
unescapeBytes' cs = if any (\c -> ord c >= 0xDC80 && ord c <= 0xDCFF) cs
	then B8.concat (map (\c -> if ord c >= 0xDC80 && ord c <= 0xDCFF
		then B8.singleton (chr (ord c  0xDC00))
		else TE.encodeUtf8 (T.singleton c)) cs)
	else TE.encodeUtf8 (T.pack cs)
splitBy :: (a -> Bool) -> [a] -> [[a]]
splitBy p = loop where
	loop xs = let
		(chunk, rest) = break p xs
		cont = chunk : loop (tail rest)
		in if null rest then [chunk] else cont
textSplitBy :: (Char -> Bool) -> T.Text -> [T.Text]
#if MIN_VERSION_text(0,11,0)
textSplitBy = T.split
#else
textSplitBy = T.splitBy
#endif
parseFilename :: Chunk -> (Maybe Basename, [Extension])
parseFilename filename = parsed where
	parsed = if null filename
		then (Nothing, [])
		else case splitBy (== '.') filename of
			[] -> (Nothing, [])
			(name':exts') -> (Just name', exts')
maybeDecodeUtf8 :: B.ByteString -> Maybe T.Text
maybeDecodeUtf8 = excToMaybe . TE.decodeUtf8 where
	excToMaybe :: a -> Maybe a
	excToMaybe x = unsafePerformIO $ Exc.catch
		(fmap Just (Exc.evaluate x))
		unicodeError
	
	unicodeError :: UnicodeException -> IO (Maybe a)
	unicodeError _ = return Nothing