{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
{-# OPTIONS_GHC -Wno-orphans #-}
#if defined(IS_WINDOWS)
#define OS_NAME Windows
#define OS_PATH WindowsPath
#else
#define OS_NAME Posix
#define OS_PATH PosixPath
#endif
module Streamly.Internal.FileSystem.OS_PATH.SegNode
(
rtdir
, urdir
, rtfile
, urfile
, rtdirE
, urdirE
, rtfileE
, urfileE
, join
)
where
import Control.Monad ((>=>))
import Language.Haskell.TH.Syntax (lift)
import Streamly.Internal.FileSystem.Path.Common (mkQ)
import Streamly.Internal.FileSystem.OS_PATH (OS_PATH(..))
import Streamly.Internal.FileSystem.OS_PATH.Seg (Rooted(..), Unrooted(..))
import Streamly.Internal.FileSystem.OS_PATH.Node (File(..), Dir(..))
import qualified Streamly.Internal.FileSystem.OS_PATH as OsPath
import Language.Haskell.TH
import Language.Haskell.TH.Quote
import Streamly.Internal.Data.Path
instance IsPath OS_PATH (Rooted (File OS_PATH)) where
unsafeFromPath :: PosixPath -> Rooted (File PosixPath)
unsafeFromPath PosixPath
p = File PosixPath -> Rooted (File PosixPath)
forall a. a -> Rooted a
Rooted (PosixPath -> File PosixPath
forall a. a -> File a
File PosixPath
p)
fromPath :: forall (m :: * -> *).
MonadThrow m =>
PosixPath -> m (Rooted (File PosixPath))
fromPath PosixPath
p = do
File PosixPath
_ :: File OS_PATH <- fromPath p
Rooted PosixPath
_ :: Rooted OS_PATH <- fromPath p
Rooted (File PosixPath) -> m (Rooted (File PosixPath))
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Rooted (File PosixPath) -> m (Rooted (File PosixPath)))
-> Rooted (File PosixPath) -> m (Rooted (File PosixPath))
forall a b. (a -> b) -> a -> b
$ File PosixPath -> Rooted (File PosixPath)
forall a. a -> Rooted a
Rooted (PosixPath -> File PosixPath
forall a. a -> File a
File PosixPath
p)
toPath :: Rooted (File PosixPath) -> PosixPath
toPath (Rooted (File PosixPath
p)) = PosixPath
p
instance IsPath OS_PATH (Rooted (Dir OS_PATH)) where
unsafeFromPath :: PosixPath -> Rooted (Dir PosixPath)
unsafeFromPath PosixPath
p = Dir PosixPath -> Rooted (Dir PosixPath)
forall a. a -> Rooted a
Rooted (PosixPath -> Dir PosixPath
forall a. a -> Dir a
Dir PosixPath
p)
fromPath :: forall (m :: * -> *).
MonadThrow m =>
PosixPath -> m (Rooted (Dir PosixPath))
fromPath PosixPath
p = do
Dir PosixPath
_ :: Dir OS_PATH <- fromPath p
Rooted PosixPath
_ :: Rooted OS_PATH <- fromPath p
Rooted (Dir PosixPath) -> m (Rooted (Dir PosixPath))
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Rooted (Dir PosixPath) -> m (Rooted (Dir PosixPath)))
-> Rooted (Dir PosixPath) -> m (Rooted (Dir PosixPath))
forall a b. (a -> b) -> a -> b
$ Dir PosixPath -> Rooted (Dir PosixPath)
forall a. a -> Rooted a
Rooted (PosixPath -> Dir PosixPath
forall a. a -> Dir a
Dir PosixPath
p)
toPath :: Rooted (Dir PosixPath) -> PosixPath
toPath (Rooted (Dir PosixPath
p)) = PosixPath
p
instance IsPath OS_PATH (Unrooted (File OS_PATH)) where
unsafeFromPath :: PosixPath -> Unrooted (File PosixPath)
unsafeFromPath PosixPath
p = File PosixPath -> Unrooted (File PosixPath)
forall a. a -> Unrooted a
Unrooted (PosixPath -> File PosixPath
forall a. a -> File a
File PosixPath
p)
fromPath :: forall (m :: * -> *).
MonadThrow m =>
PosixPath -> m (Unrooted (File PosixPath))
fromPath PosixPath
p = do
File PosixPath
_ :: File OS_PATH <- fromPath p
Unrooted PosixPath
_ :: Unrooted OS_PATH <- fromPath p
Unrooted (File PosixPath) -> m (Unrooted (File PosixPath))
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Unrooted (File PosixPath) -> m (Unrooted (File PosixPath)))
-> Unrooted (File PosixPath) -> m (Unrooted (File PosixPath))
forall a b. (a -> b) -> a -> b
$ File PosixPath -> Unrooted (File PosixPath)
forall a. a -> Unrooted a
Unrooted (PosixPath -> File PosixPath
forall a. a -> File a
File PosixPath
p)
toPath :: Unrooted (File PosixPath) -> PosixPath
toPath (Unrooted (File PosixPath
p)) = PosixPath
p
instance IsPath OS_PATH (Unrooted (Dir OS_PATH)) where
unsafeFromPath :: PosixPath -> Unrooted (Dir PosixPath)
unsafeFromPath PosixPath
p = Dir PosixPath -> Unrooted (Dir PosixPath)
forall a. a -> Unrooted a
Unrooted (PosixPath -> Dir PosixPath
forall a. a -> Dir a
Dir PosixPath
p)
fromPath :: forall (m :: * -> *).
MonadThrow m =>
PosixPath -> m (Unrooted (Dir PosixPath))
fromPath PosixPath
p = do
Dir PosixPath
_ :: Dir OS_PATH <- fromPath p
Unrooted PosixPath
_ :: Unrooted OS_PATH <- fromPath p
Unrooted (Dir PosixPath) -> m (Unrooted (Dir PosixPath))
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Unrooted (Dir PosixPath) -> m (Unrooted (Dir PosixPath)))
-> Unrooted (Dir PosixPath) -> m (Unrooted (Dir PosixPath))
forall a b. (a -> b) -> a -> b
$ Dir PosixPath -> Unrooted (Dir PosixPath)
forall a. a -> Unrooted a
Unrooted (PosixPath -> Dir PosixPath
forall a. a -> Dir a
Dir PosixPath
p)
toPath :: Unrooted (Dir PosixPath) -> PosixPath
toPath (Unrooted (Dir PosixPath
p)) = PosixPath
p
liftRootedDir :: Rooted (Dir OS_PATH) -> Q Exp
liftRootedDir :: Rooted (Dir PosixPath) -> Q Exp
liftRootedDir (Rooted (Dir PosixPath
p)) =
[| unsafeFromPath (OsPath.unsafeFromString $([Char] -> Q Exp
forall t (m :: * -> *). (Lift t, Quote m) => t -> m Exp
forall (m :: * -> *). Quote m => [Char] -> m Exp
lift ([Char] -> Q Exp) -> [Char] -> Q Exp
forall a b. (a -> b) -> a -> b
$ PosixPath -> [Char]
OsPath.toString (PosixPath -> [Char]) -> PosixPath -> [Char]
forall a b. (a -> b) -> a -> b
$ PosixPath -> PosixPath
forall a b. IsPath a b => b -> a
toPath PosixPath
p)) :: Rooted (Dir OS_PATH)|]
liftUnrootedDir :: Unrooted (Dir OS_PATH) -> Q Exp
liftUnrootedDir :: Unrooted (Dir PosixPath) -> Q Exp
liftUnrootedDir (Unrooted (Dir PosixPath
p)) =
[| unsafeFromPath (OsPath.unsafeFromString $([Char] -> Q Exp
forall t (m :: * -> *). (Lift t, Quote m) => t -> m Exp
forall (m :: * -> *). Quote m => [Char] -> m Exp
lift ([Char] -> Q Exp) -> [Char] -> Q Exp
forall a b. (a -> b) -> a -> b
$ PosixPath -> [Char]
OsPath.toString (PosixPath -> [Char]) -> PosixPath -> [Char]
forall a b. (a -> b) -> a -> b
$ PosixPath -> PosixPath
forall a b. IsPath a b => b -> a
toPath PosixPath
p)) :: Unrooted (Dir OS_PATH) |]
liftRootedFile :: Rooted (File OS_PATH) -> Q Exp
liftRootedFile :: Rooted (File PosixPath) -> Q Exp
liftRootedFile (Rooted (File PosixPath
p)) =
[| unsafeFromPath (OsPath.unsafeFromString $([Char] -> Q Exp
forall t (m :: * -> *). (Lift t, Quote m) => t -> m Exp
forall (m :: * -> *). Quote m => [Char] -> m Exp
lift ([Char] -> Q Exp) -> [Char] -> Q Exp
forall a b. (a -> b) -> a -> b
$ PosixPath -> [Char]
OsPath.toString (PosixPath -> [Char]) -> PosixPath -> [Char]
forall a b. (a -> b) -> a -> b
$ PosixPath -> PosixPath
forall a b. IsPath a b => b -> a
toPath PosixPath
p)) :: Rooted (File OS_PATH)|]
liftUnrootedFile :: Unrooted (File OS_PATH) -> Q Exp
liftUnrootedFile :: Unrooted (File PosixPath) -> Q Exp
liftUnrootedFile (Unrooted (File PosixPath
p)) =
[| unsafeFromPath (OsPath.unsafeFromString $([Char] -> Q Exp
forall t (m :: * -> *). (Lift t, Quote m) => t -> m Exp
forall (m :: * -> *). Quote m => [Char] -> m Exp
lift ([Char] -> Q Exp) -> [Char] -> Q Exp
forall a b. (a -> b) -> a -> b
$ PosixPath -> [Char]
OsPath.toString (PosixPath -> [Char]) -> PosixPath -> [Char]
forall a b. (a -> b) -> a -> b
$ PosixPath -> PosixPath
forall a b. IsPath a b => b -> a
toPath PosixPath
p)) :: Unrooted (File OS_PATH)|]
rtdirE :: String -> Q Exp
rtdirE :: [Char] -> Q Exp
rtdirE = (SomeException -> Q Exp)
-> (Rooted (Dir PosixPath) -> Q Exp)
-> Either SomeException (Rooted (Dir PosixPath))
-> Q Exp
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ([Char] -> Q Exp
forall a. HasCallStack => [Char] -> a
error ([Char] -> Q Exp)
-> (SomeException -> [Char]) -> SomeException -> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> [Char]
forall a. Show a => a -> [Char]
show) Rooted (Dir PosixPath) -> Q Exp
liftRootedDir (Either SomeException (Rooted (Dir PosixPath)) -> Q Exp)
-> ([Char] -> Either SomeException (Rooted (Dir PosixPath)))
-> [Char]
-> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char] -> Either SomeException PosixPath
forall (m :: * -> *). MonadThrow m => [Char] -> m PosixPath
OsPath.fromString ([Char] -> Either SomeException PosixPath)
-> (PosixPath -> Either SomeException (Rooted (Dir PosixPath)))
-> [Char]
-> Either SomeException (Rooted (Dir PosixPath))
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> PosixPath -> Either SomeException (Rooted (Dir PosixPath))
forall a b (m :: * -> *). (IsPath a b, MonadThrow m) => a -> m b
forall (m :: * -> *).
MonadThrow m =>
PosixPath -> m (Rooted (Dir PosixPath))
fromPath)
urdirE :: String -> Q Exp
urdirE :: [Char] -> Q Exp
urdirE = (SomeException -> Q Exp)
-> (Unrooted (Dir PosixPath) -> Q Exp)
-> Either SomeException (Unrooted (Dir PosixPath))
-> Q Exp
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ([Char] -> Q Exp
forall a. HasCallStack => [Char] -> a
error ([Char] -> Q Exp)
-> (SomeException -> [Char]) -> SomeException -> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> [Char]
forall a. Show a => a -> [Char]
show) Unrooted (Dir PosixPath) -> Q Exp
liftUnrootedDir (Either SomeException (Unrooted (Dir PosixPath)) -> Q Exp)
-> ([Char] -> Either SomeException (Unrooted (Dir PosixPath)))
-> [Char]
-> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char] -> Either SomeException PosixPath
forall (m :: * -> *). MonadThrow m => [Char] -> m PosixPath
OsPath.fromString ([Char] -> Either SomeException PosixPath)
-> (PosixPath -> Either SomeException (Unrooted (Dir PosixPath)))
-> [Char]
-> Either SomeException (Unrooted (Dir PosixPath))
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> PosixPath -> Either SomeException (Unrooted (Dir PosixPath))
forall a b (m :: * -> *). (IsPath a b, MonadThrow m) => a -> m b
forall (m :: * -> *).
MonadThrow m =>
PosixPath -> m (Unrooted (Dir PosixPath))
fromPath)
rtfileE :: String -> Q Exp
rtfileE :: [Char] -> Q Exp
rtfileE = (SomeException -> Q Exp)
-> (Rooted (File PosixPath) -> Q Exp)
-> Either SomeException (Rooted (File PosixPath))
-> Q Exp
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ([Char] -> Q Exp
forall a. HasCallStack => [Char] -> a
error ([Char] -> Q Exp)
-> (SomeException -> [Char]) -> SomeException -> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> [Char]
forall a. Show a => a -> [Char]
show) Rooted (File PosixPath) -> Q Exp
liftRootedFile (Either SomeException (Rooted (File PosixPath)) -> Q Exp)
-> ([Char] -> Either SomeException (Rooted (File PosixPath)))
-> [Char]
-> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char] -> Either SomeException PosixPath
forall (m :: * -> *). MonadThrow m => [Char] -> m PosixPath
OsPath.fromString ([Char] -> Either SomeException PosixPath)
-> (PosixPath -> Either SomeException (Rooted (File PosixPath)))
-> [Char]
-> Either SomeException (Rooted (File PosixPath))
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> PosixPath -> Either SomeException (Rooted (File PosixPath))
forall a b (m :: * -> *). (IsPath a b, MonadThrow m) => a -> m b
forall (m :: * -> *).
MonadThrow m =>
PosixPath -> m (Rooted (File PosixPath))
fromPath)
urfileE :: String -> Q Exp
urfileE :: [Char] -> Q Exp
urfileE = (SomeException -> Q Exp)
-> (Unrooted (File PosixPath) -> Q Exp)
-> Either SomeException (Unrooted (File PosixPath))
-> Q Exp
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ([Char] -> Q Exp
forall a. HasCallStack => [Char] -> a
error ([Char] -> Q Exp)
-> (SomeException -> [Char]) -> SomeException -> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> [Char]
forall a. Show a => a -> [Char]
show) Unrooted (File PosixPath) -> Q Exp
liftUnrootedFile (Either SomeException (Unrooted (File PosixPath)) -> Q Exp)
-> ([Char] -> Either SomeException (Unrooted (File PosixPath)))
-> [Char]
-> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char] -> Either SomeException PosixPath
forall (m :: * -> *). MonadThrow m => [Char] -> m PosixPath
OsPath.fromString ([Char] -> Either SomeException PosixPath)
-> (PosixPath -> Either SomeException (Unrooted (File PosixPath)))
-> [Char]
-> Either SomeException (Unrooted (File PosixPath))
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> PosixPath -> Either SomeException (Unrooted (File PosixPath))
forall a b (m :: * -> *). (IsPath a b, MonadThrow m) => a -> m b
forall (m :: * -> *).
MonadThrow m =>
PosixPath -> m (Unrooted (File PosixPath))
fromPath)
rtdir :: QuasiQuoter
rtdir :: QuasiQuoter
rtdir = ([Char] -> Q Exp) -> QuasiQuoter
mkQ [Char] -> Q Exp
rtdirE
urdir :: QuasiQuoter
urdir :: QuasiQuoter
urdir = ([Char] -> Q Exp) -> QuasiQuoter
mkQ [Char] -> Q Exp
urdirE
rtfile :: QuasiQuoter
rtfile :: QuasiQuoter
rtfile = ([Char] -> Q Exp) -> QuasiQuoter
mkQ [Char] -> Q Exp
rtfileE
urfile :: QuasiQuoter
urfile :: QuasiQuoter
urfile = ([Char] -> Q Exp) -> QuasiQuoter
mkQ [Char] -> Q Exp
urfileE
{-# INLINE join #-}
join ::
(
IsPath OS_PATH (a (Dir OS_PATH))
, IsPath OS_PATH (b OS_PATH)
, IsPath OS_PATH (a (b OS_PATH))
) => a (Dir OS_PATH) -> Unrooted (b OS_PATH) -> a (b OS_PATH)
join :: forall (a :: * -> *) (b :: * -> *).
(IsPath PosixPath (a (Dir PosixPath)),
IsPath PosixPath (b PosixPath),
IsPath PosixPath (a (b PosixPath))) =>
a (Dir PosixPath) -> Unrooted (b PosixPath) -> a (b PosixPath)
join a (Dir PosixPath)
p1 (Unrooted b PosixPath
p2) =
PosixPath -> a (b PosixPath)
forall a b. IsPath a b => a -> b
unsafeFromPath (PosixPath -> a (b PosixPath)) -> PosixPath -> a (b PosixPath)
forall a b. (a -> b) -> a -> b
$ PosixPath -> PosixPath -> PosixPath
OsPath.unsafeJoin (a (Dir PosixPath) -> PosixPath
forall a b. IsPath a b => b -> a
toPath a (Dir PosixPath)
p1) (b PosixPath -> PosixPath
forall a b. IsPath a b => b -> a
toPath b PosixPath
p2)