{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE ScopedTypeVariables #-}
module System.Path.Lens
(
(</>~)
, (<.>~)
, basename
, directory
, extension
, filename
) where
import Data.Functor as Fun
import Data.Functor.Identity
import System.Path
infixr 4 </>~
(</>~) :: ASetter s t (Path a) (Path a) -> (Path Unrooted) -> s -> t
l </>~ n = overSafe l (</> n)
infixr 4 <.>~
(<.>~) :: ASetter s t (Path a) (Path a) -> FileExt -> s -> t
l <.>~ n = overSafe l (<.> n)
basename :: Lens' (Path a) (Path Unrooted)
basename f p = (<.?> takeExtension p) . (takeDirectory p </>) Fun.<$> f (takeBaseName p)
(<.?>) :: Path a -> Maybe FileExt -> Path a
fp <.?> Nothing = fp
fp <.?> Just fe = fp <.> fe
directory :: Lens' (Path a) (Path a)
directory f p = (</> takeFileName p) <$> f (takeDirectory p)
extension :: Lens' (Path a) (Maybe FileExt)
extension f p = (n <.?>) <$> f e
where
(n, e) = splitExtension p
filename :: Lens' (Path a) (Path Unrooted)
filename f p = (takeDirectory p </>) <$> f (takeFileName p)
type ASetter s t a b = (a -> Identity b) -> s -> Identity t
type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t
type Lens' s a = Lens s s a a
{-# INLINE overSafe #-}
overSafe :: ASetter s t a b -> (a -> b) -> s -> t
overSafe l f = runIdentity `g` (l (Identity `h` f))
where
h _ = (Identity .)
g _ = (runIdentity .)