Safe Haskell | None |
---|---|
Language | Haskell2010 |
Directory layout DSL
- data Layout a
- file :: String -> Layout ()
- symlink :: String -> FilePath -> Layout ()
- dir :: String -> Layout a -> Layout ()
- dirs :: [String] -> Layout () -> Layout ()
- emptydir :: String -> Layout ()
- contents :: Traversal' (Layout a) (Maybe Contents)
- data Contents
- binary :: ByteString -> Contents
- text :: Text -> Contents
- dedent :: QuasiQuoter
- copyOf :: FilePath -> Contents
- source :: Traversal' (Layout a) String
- exists :: Traversal' (Layout a) Bool
- data User
- user :: Traversal' (Layout a) (Maybe User)
- uid :: UserID -> User
- username :: String -> User
- data Group
- group :: Traversal' (Layout a) (Maybe Group)
- gid :: GroupID -> Group
- groupname :: String -> Group
- mode :: Traversal' (Layout a) (Maybe FileMode)
- anything :: Maybe a
- into :: String -> Traversal' (Layout ()) (Layout ())
- focus :: String -> Traversal' (Layout ()) (Layout ())
- module System.Directory.Layout.Interpreter
Describe layouts
Directory layout description
Monad Layout | |
Functor Layout | |
Applicative Layout | |
Foldable Layout | |
Traversable Layout | |
Eq (Layout a) | Equality check does not care about the order the files are listed insofar they are consistent, i.e. different things aren't named the same |
Generic (Layout a) | |
Semigroup (Layout a) | |
Typeable (* -> *) Layout | |
type Rep (Layout a) |
Nodes
file :: String -> Layout () Source
Regular file with some contents or empty
>>>
let layout = file "foo"
dir :: String -> Layout a -> Layout () Source
Directory
>>>
:{
let layout = dir "foo" $ do file "bar" file "baz" :}
dirs :: [String] -> Layout () -> Layout () Source
A nested list of directories
>>>
:{
let layout = dirs ["foo", "bar"] $ do file "qux" file "quux" :}
Nodes augmentation
Regular file contents
binary :: ByteString -> Contents Source
Binary contents
>>>
let layout = file "foo" & contents ?~ binary (ByteString.pack [1..10])
text :: Text -> Contents Source
Plain text contents
>>>
let layout = file "foo" & contents ?~ text (Data.Text.pack "hello")
A handy quasiquoter to work with the multiline file contents
Strips the longest common leading spaces segment. All spacey characters are treated equally. The first line is ignored if it's spaces only.
>>>
:set -XQuasiQuotes
>>>
:{
putStr [dedent| hello world ! |] :} hello world !
copyOf :: FilePath -> Contents Source
Contents are the copy of whose of the real file
>>>
let layout = file "foo" & contents ?~ copyOf "/home/user/.vimrc"
source :: Traversal' (Layout a) String Source
An optic into symbolic link source
>>>
symlink "foo" "bar" ^? source
Just "bar"
exists :: Traversal' (Layout a) Bool Source
An optic into symbolic link source expected existence
>>>
let layout = symlink "foo" "bar" & exists .~ True
File owner
user :: Traversal' (Layout a) (Maybe User) Source
An optic into file owner
>>>
let layout = file "foo" & user ?~ uid 0
username :: String -> User Source
Set the file owner by username
>>>
let layout = file "foo" & user ?~ username "root"
File group
group :: Traversal' (Layout a) (Maybe Group) Source
An optic into file group
>>>
let layout = file "foo" & group ?~ gid 0
groupname :: String -> Group Source
Set the file group by groupname
>>>
let layout = file "foo" & group ?~ groupname "wheel"
mode :: Traversal' (Layout a) (Maybe FileMode) Source
An optic into file mode
>>>
let layout = file "foo" & mode ?~ 0o100777
Anything
>>>
let layout = file "foo" & contents .~ anything
>>>
let layout = file "foo" & user .~ anything
into :: String -> Traversal' (Layout ()) (Layout ()) Source
An optic into the directory contents of the particular directory
>>>
:{
dirs ["foo", "bar", "baz"] (symlink "qux" "quux") ^? into "foo".into "bar".into "baz".focus "qux".source :} Just "quux"