module System.Directory.Layout.Internal where
import Control.Applicative
import Control.Lens
import Control.Monad.Free
import Data.ByteString (ByteString)
import qualified Data.ByteString as ByteString
import Data.Data (Data, Typeable)
import Data.Foldable (Foldable)
import qualified Data.HashMap.Strict as HashMap
import Data.Semigroup (Semigroup(..))
import Data.String (IsString(..))
import Data.Word (Word8)
import Data.Text (Text)
#if __GLASGOW_HASKELL__ >= 708
import GHC.Exts (IsList(..))
#endif
import GHC.Generics (Generic)
import System.FilePath ((</>))
import qualified System.Posix as Posix
newtype Layout a = L { unL :: Free F a }
deriving (Functor, Applicative, Monad, Foldable, Traversable, Typeable, Generic)
data F a =
F String (Maybe Contents) Aux a
| SL String FilePath Bool Aux a
| D String a Aux a
| E
deriving (Eq, Functor, Foldable, Traversable, Typeable, Generic)
data Contents =
Binary ByteString
| Text Text
| CopyOf FilePath
deriving (Eq, Typeable, Data, Generic)
instance IsString Contents where
fromString = Text . fromString
#if __GLASGOW_HASKELL__ >= 708
instance IsList Contents where
type Item Contents = Word8
fromList = Binary . ByteString.pack
toList = error "Contents.toList: not implemented"
#endif
data Aux = Aux (Maybe User) (Maybe Group) (Maybe Posix.FileMode)
deriving (Show, Eq, Typeable, Generic)
data User =
UserID Posix.UserID
| Username String
deriving (Show, Eq, Typeable, Generic)
instance IsString User where
fromString = Username
data Group =
GroupID Posix.GroupID
| Groupname String
deriving (Show, Eq, Typeable, Generic)
instance IsString Group where
fromString = Groupname
instance Eq (Layout a) where
L xs == L ys = go "." xs == go "." ys
where
go root (Free t@(F n _ _ m)) =
HashMap.singleton (root </> n) (() <$ t) <> go root m
go root (Free t@(SL n _ _ _ m)) =
HashMap.singleton (root </> n) (() <$ t) <> go root m
go root (Free t@(D n is _ m)) =
HashMap.singleton (root </> n) (() <$ t) <> go (root </> n) is <> go root m
go _ (Free E) = HashMap.empty
go _ (Pure _) = HashMap.empty
instance Semigroup (Layout a) where
(<>) = (>>)
file :: String -> Layout ()
file name = L (liftF (F name anything defaux ()))
symlink
:: String
-> FilePath
-> Layout ()
symlink name s = L (liftF (SL name s False defaux ()))
dir :: String -> Layout a -> Layout ()
dir name is = L (Free (D name (unL is >> liftF E) defaux (Pure ())))
emptydir :: String -> Layout ()
emptydir name = dir name (return ())
dirs :: [String] -> Layout () -> Layout ()
dirs names l = foldr dir l names
defaux :: Aux
defaux = Aux Nothing Nothing Nothing
contents :: Traversal' (Layout a) (Maybe Contents)
contents f (L (Free (F n cs a x@(Pure _)))) = f cs <&> \cs' -> L (Free (F n cs' a x))
contents _ l = pure l
binary :: ByteString -> Contents
binary = Binary
text :: Text -> Contents
text = Text
copyOf :: FilePath -> Contents
copyOf = CopyOf
anything :: Maybe a
anything = Nothing
source :: Traversal' (Layout a) String
source f (L (Free (SL n s e a x@(Pure _)))) = f s <&> \s' -> L (Free (SL n s' e a x))
source _ l = pure l
exists :: Traversal' (Layout a) Bool
exists f (L (Free (SL n s e a x@(Pure _)))) = f e <&> \e' -> L (Free (SL n s e' a x))
exists _ l = pure l
aux :: Traversal' (Layout a) Aux
aux f (L (Free (F n cs a x@(Pure _)))) = f a <&> \a' -> L (Free (F n cs a' x))
aux f (L (Free (SL n s e a x@(Pure _)))) = f a <&> \a' -> L (Free (SL n s e a' x))
aux f (L (Free (D n is a x@(Pure _)))) = f a <&> \a' -> L (Free (D n is a' x))
aux _ l = pure l
user :: Traversal' (Layout a) (Maybe User)
user = aux . \f (Aux x y z) -> f x <&> \x' -> Aux x' y z
uid :: Posix.UserID -> User
uid = UserID
username :: String -> User
username = Username
group :: Traversal' (Layout a) (Maybe Group)
group = aux . \f (Aux x y z) -> f y <&> \y' -> Aux x y' z
gid :: Posix.GroupID -> Group
gid = GroupID
groupname :: String -> Group
groupname = Groupname
mode :: Traversal' (Layout a) (Maybe Posix.FileMode)
mode = aux . \f (Aux x y z) -> f z <&> \z' -> Aux x y z'
innards :: Traversal' (Layout a) (Layout a)
innards f (L (Free (D n is a x@(Pure _)))) = fmap unL (f (L is)) <&> \is' -> L (Free (D n is' a x))
innards _ l = pure l
into :: String -> Traversal' (Layout ()) (Layout ())
into s = focus s.innards
focus :: String -> Traversal' (Layout ()) (Layout ())
focus k f = fmap L . go . unL where
go (Free (F n cs a x))
| n == k =
g (liftF (F n cs a ())) <&> \(Free (F _ cs' a' _)) -> Free (F n cs' a' x)
| otherwise =
go x <&> Free . F n cs a
go (Free (D n is a x))
| n == k =
g (Free (D n is a (Pure ()))) <&> \(Free (D _ is' a' _)) -> Free (D n is' a' x)
| otherwise =
go x <&> Free . D n is a
go (Free (SL n s e a x))
| n == k =
g (liftF (SL n s e a ())) <&> \(Free (SL _ s' e' a' _)) -> Free (SL n s' e' a' x)
| otherwise =
go x <&> Free . SL n s e a
go (Free E) = pure (Free E)
go (Pure x) = pure (Pure x)
g = fmap unL . f . L