module Filesystem.CanonicalPath.Internal (CanonicalPath(..)
,canonicalPath
,canonicalPath'
,canonicalPathM
,canonicalPathM'
,canonicalPathE
,canonicalPathE'
,unsafePath
,Filesystem.CanonicalPath.Internal.readFile
,Filesystem.CanonicalPath.Internal.writeFile
,writeFile'
,Filesystem.CanonicalPath.Internal.appendFile
,preludeMap
,fromText
,toText
,toText'
,toPrelude
,fromPrelude
,voidM) where
import BasicPrelude
import Control.Applicative as Applicative
import Control.Arrow (left, right)
import Data.Text ()
import qualified Data.Text as Text
import Filesystem.Path.CurrentOS
import qualified Prelude
import System.Directory (getHomeDirectory
,canonicalizePath)
import qualified System.Environment as SE (getEnv)
newtype CanonicalPath = CanonicalPath FilePath deriving Eq
instance Show CanonicalPath where
showsPrec d path =
showParen (d > 15)
(showString "CanonicalPath " .
shows (toText' path))
canonicalPath :: MonadIO m => FilePath -> m CanonicalPath
canonicalPath path = canonicalize path >>= either (error . textToString) (return . CanonicalPath)
canonicalPath' :: MonadIO m => Text -> m CanonicalPath
canonicalPath' = canonicalPath . fromText
canonicalPathM :: MonadIO m => FilePath -> m (Maybe CanonicalPath)
canonicalPathM path = canonicalize path >>= either (\_ -> return Nothing) (return . Just . CanonicalPath)
canonicalPathM' :: MonadIO m => Text -> m (Maybe CanonicalPath)
canonicalPathM' = canonicalPathM . fromText
canonicalPathE :: MonadIO m => FilePath -> m (Either Text CanonicalPath)
canonicalPathE path = canonicalize path >>= either (return . Left) (return . Right . CanonicalPath)
canonicalPathE' :: MonadIO m => Text -> m (Either Text CanonicalPath)
canonicalPathE' = canonicalPathE . fromText
unsafePath :: CanonicalPath -> FilePath
unsafePath (CanonicalPath up) = up
canonicalize :: MonadIO m => FilePath -> m (Either Text FilePath)
canonicalize fp = extractPath fp >>= either (return . Left) canonicalize'
canonicalize' :: MonadIO m => Text -> m (Either Text FilePath)
canonicalize' path =
liftIO $ liftM (right fromPrelude) (tryIO . canonicalizePath . textToString $ path)
extractPath :: MonadIO m => FilePath -> m (Either Text Text)
extractPath = liftM (right concatPath . sequence) . mapM extractAtom . splitPath . toTextUnsafe . collapse
extractAtom :: MonadIO m => Text -> m (Either Text Text)
extractAtom atom = tryEnvPosix <||> tryHome <||> tryEnvWindows <%> atom
type Parser m = Text -> Maybe (m (Either Text Text))
tryEnvPosix :: MonadIO m => Parser m
tryEnvPosix x = when' (Text.isPrefixOf "$" x) (Just . getEnv . Text.tail $ x)
tryEnvWindows :: MonadIO m => Parser m
tryEnvWindows x =
when' (Text.isPrefixOf "%" x &&
Text.isSuffixOf "%" x)
(Just . getEnv . Text.tail . Text.init $ x)
tryHome :: MonadIO m => Parser m
tryHome x = when' ("~" == x) (Just $ liftM Right homeDirectory)
(<||>) :: MonadIO m => Parser m -> Parser m -> Parser m
p1 <||> p2 = \v -> p1 v <|> p2 v
(<%>) :: MonadIO m => Parser m -> Text -> m (Either Text Text)
p <%> v = fromMaybe (return . Right $ v) (p v)
readFile :: MonadIO m => CanonicalPath -> m Text
readFile = liftIO . BasicPrelude.readFile . unsafePath
writeFile :: MonadIO m => CanonicalPath -> Text -> m ()
writeFile p = liftIO . BasicPrelude.writeFile (unsafePath p)
writeFile' :: MonadIO m => CanonicalPath -> FilePath -> Text -> m ()
writeFile' cp file = liftIO . BasicPrelude.writeFile (unsafePath cp </> file)
appendFile :: MonadIO m => CanonicalPath -> Text -> m ()
appendFile p = liftIO . BasicPrelude.appendFile (unsafePath p)
tryIO :: MonadIO m => IO a -> m (Either Text a)
tryIO a = liftM (left show) (try' a)
where try' :: MonadIO m => IO a -> m (Either IOException a)
try' = liftIO . try
getEnv :: MonadIO m => Text -> m (Either Text Text)
getEnv = liftM (right fromString) . tryIO . SE.getEnv . textToString
homeDirectory :: MonadIO m => m Text
homeDirectory = liftIO $ fromString <$> getHomeDirectory
when' :: Alternative f => Bool -> f a -> f a
when' b v = if b then v else Applicative.empty
splitPath :: Text -> [Text]
splitPath = Text.splitOn "/"
concatPath :: [Text] -> Text
concatPath = Text.intercalate "/"
preludeMap :: (Prelude.FilePath -> a) -> CanonicalPath -> a
preludeMap f = f . toPrelude . unsafePath
toTextUnsafe :: FilePath -> Text
toTextUnsafe = either (error . textToString) id . toText
toText' :: CanonicalPath -> Text
toText' = toTextUnsafe . unsafePath
fromPrelude :: Prelude.FilePath -> FilePath
fromPrelude = fromText . Text.pack
toPrelude :: FilePath -> Prelude.FilePath
toPrelude = Text.unpack . toTextUnsafe
voidM :: Monad m => m a -> m ()
voidM a = a >> return ()