module System.Path.Internal.Part where import qualified Control.Monad.Trans.State as MS import Control.Applicative ((<$>)) import Control.DeepSeq (NFData(rnf)) import Data.Tagged (Tagged(Tagged)) import Data.Ord.HT (comparing) import Data.Eq.HT (equating) import Test.QuickCheck (Gen) newtype Abs = Abs GenComponent data Rel = Rel data AbsRel = AbsO GenComponent | RelO absPC :: String -> Abs absPC = Abs . PathComponent emptyPC :: PathComponent os emptyPC = PathComponent "" newtype File = File GenComponent data Dir = Dir data FileDir = FileDir instance NFData Abs where rnf (Abs drive) = rnf drive instance NFData Rel where rnf Rel = () instance NFData File where rnf (File pc) = rnf pc instance NFData Dir where rnf Dir = () instance NFData FileDir where rnf FileDir = () data Generic = Generic {- | We cannot have a PathComponent without phantom types plus a Tagged wrapper, because we need specialised Eq and Ord instances. -} type GenComponent = PathComponent Generic newtype PathComponent os = PathComponent String instance NFData (PathComponent os) where rnf (PathComponent pc) = rnf pc instance (System os) => Eq (PathComponent os) where (==) = equating (applyComp canonicalize) instance (System os) => Ord (PathComponent os) where compare = comparing (applyComp canonicalize) applyComp :: Tagged os (String -> String) -> PathComponent os -> String applyComp (Tagged canon) (PathComponent pc) = canon pc retagPC :: GenComponent -> PathComponent os retagPC (PathComponent pc) = PathComponent pc untagPC :: PathComponent os -> GenComponent untagPC (PathComponent pc) = PathComponent pc fileMap :: (String -> String) -> File -> File fileMap f (File pc) = File $ pcMap f pc pcMap :: (String -> String) -> PathComponent os -> PathComponent os pcMap f (PathComponent s) = PathComponent $ f s pcMapF :: (Functor f) => (String -> f String) -> PathComponent os -> f (PathComponent os) pcMapF f (PathComponent s) = PathComponent <$> f s class System os where -- | The character that separates directories. In the case where more than -- one character is possible, 'pathSeparator' is the \'ideal\' one. -- -- >> Posix.isPathSeparator Posix.pathSeparator pathSeparator :: Tagged os Char -- | The list of all possible separators. -- -- >> Posix.pathSeparator `elem` Posix.pathSeparators pathSeparators :: Tagged os [Char] pathSeparators = (:[]) <$> pathSeparator -- | Rather than using @(== 'pathSeparator')@, use this. Test if something -- is a path separator. -- -- >> Posix.isPathSeparator a == (a `elem` Posix.pathSeparators) isPathSeparator :: Tagged os (Char -> Bool) isPathSeparator = flip elem <$> pathSeparators splitAbsolute :: Tagged os (MS.State String String) canonicalize :: Tagged os (String -> String) splitDrive :: Tagged os (MS.State String String) genDrive :: Tagged os (Gen String)