Copyright | (c) 2024 Illia Shkroba |
---|---|
License | BSD3 |
Maintainer | Illia Shkroba <[email protected]> |
Stability | unstable |
Portability | non-portable (Non-Unix systems are not supported) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
PFile.Profile
Description
Types and functions for managing profiles defined for a set of entries.
(A note on naming: pfile
is an abbreviation for "profile".)
Synopsis
- data LoadCurrentError
- data SetCurrentError
- newtype UnsetCurrentError = CurrentLinkRemoveError RemoveError
- loadCurrent :: (MonadReader Env m, MonadError LoadCurrentError m, MonadIO m) => m Profile
- setCurrent :: (MonadReader Env m, MonadError SetCurrentError m, MonadIO m) => Profile -> m ()
- showLoadCurrentError :: LoadCurrentError -> Text
- showSetCurrentError :: SetCurrentError -> Text
- showUnsetCurrentError :: UnsetCurrentError -> Text
- unsetCurrent :: (MonadReader Env m, MonadError UnsetCurrentError m, MonadIO m) => m ()
- data CreateError
- newtype CreateOptions = CreateOptions {}
- create :: forall m. (MonadReader Env m, MonadError CreateError m, MonadIO m) => CreateOptions -> Name -> [Absolute] -> m Profile
- showCreateError :: CreateError -> Text
- data ListError
- newtype ListOptions = ListOptions {}
- list :: forall m. (MonadReader Env m, MonadError ListError m, MonadIO m) => ListOptions -> m [Profile]
- showListError :: ListError -> Text
- data State
- newtype Name = Name {}
- data Profile = Profile {}
- data Entry = Entry {
- mountPath :: !Mount
- originPath :: !Absolute
- absoluteRoot :: MonadReader Env m => Name -> m Root
- profileRoot :: MonadReader Env m => Name -> m Absolute
- profileState :: MonadReader Env m => Name -> m Absolute
- data DumpError
- data LoadError
- = LoadError !Absolute !IOException
- | DecodeError !Absolute ![Char]
- dump :: (MonadReader Env m, MonadError DumpError m, MonadIO m) => Profile -> m ()
- load :: (MonadReader Env m, MonadError LoadError m, MonadIO m) => Name -> m Profile
- showDumpError :: DumpError -> Text
- showLoadError :: LoadError -> Text
- data LinkError
- data SwitchError
- newtype SwitchOptions = SwitchOptions {}
- data UnpackError
- link :: forall m. (MonadError LinkError m, MonadIO m) => SwitchOptions -> Profile -> m ()
- unpack :: forall m. (MonadError UnpackError m, MonadIO m) => SwitchOptions -> Profile -> m ()
- switch :: (MonadError SwitchError m, MonadIO m) => SwitchOptions -> Profile -> Profile -> m ()
- showLinkError :: LinkError -> Text
- showSwitchError :: SwitchError -> Text
- showUnpackError :: UnpackError -> Text
Documentation
data LoadCurrentError Source #
Error thrown by loadCurrent
.
Since: 0.1.0.0
Constructors
CanonicalizeCurrentError !Absolute !IOException | Unable to canonicalize |
LoadCurrentError !LoadError | Error was encountered during
|
data SetCurrentError Source #
Error thrown by setCurrent
.
Since: 0.1.0.0
Constructors
UnsetCurrentError !UnsetCurrentError | Error was encountered during |
CurrentLinkError !CreateDirectoryLinkError | Unable to create a directory link |
newtype UnsetCurrentError Source #
Error thrown by unsetCurrent
.
Since: 0.1.0.0
Constructors
CurrentLinkRemoveError RemoveError | Unable to remove a directory link |
loadCurrent :: (MonadReader Env m, MonadError LoadCurrentError m, MonadIO m) => m Profile Source #
load
current Profile
. Current
Profile
is resolved via currentLinkPath
.
Since: 0.1.0.0
setCurrent :: (MonadReader Env m, MonadError SetCurrentError m, MonadIO m) => Profile -> m () Source #
Set current Profile
. Previously set Profile
is unset via
unsetCurrent
and then currentLinkPath
is set to point at a new
current Profile
.
Since: 0.1.0.0
unsetCurrent :: (MonadReader Env m, MonadError UnsetCurrentError m, MonadIO m) => m () Source #
Unset current Profile
. currentLinkPath
is removed.
Since: 0.1.0.0
data CreateError Source #
Error thrown by create
.
Since: 0.1.0.0
Constructors
ProfileAlreadyExistsError !Name | 'PFile.Profile.Internal.Profile.Profile with
|
PushRollbackError |
|
PushCreateError !CreateRollbackCause |
|
Arguments
:: forall m. (MonadReader Env m, MonadError CreateError m, MonadIO m) | |
=> CreateOptions | Options that control |
-> Name |
|
-> [Absolute] | List of |
-> m Profile |
Create a new profile called Name
with
a list of Absolute
filesystem's objects to be
push
ed inside of
a profilesHomeDirPath
directory. When an error is encountered
during pushAll
, create
attempts to
rollback. If the rollback fails, the profile is considered
Dangling
. Only
Valid
profiles are returned.
Since: 0.1.0.0
showCreateError :: CreateError -> Text Source #
Error thrown by list
.
Since: 0.1.0.0
Constructors
ProfilesHomeDirDoesNotExistError !Absolute |
|
ListDirectoryError !Absolute !IOException |
|
Arguments
:: forall m. (MonadReader Env m, MonadError ListError m, MonadIO m) | |
=> ListOptions | Options that control |
-> m [Profile] |
List profiles in profilesHomeDirPath
directory.
Since: 0.1.0.0
showListError :: ListError -> Text Source #
Profile
s state.
Since: 0.1.0.0
Constructors
Dangling | When an error is encountered during
|
Valid |
Constructors
Profile | |
Instances
FromJSON Profile Source # | |
ToJSON Profile Source # | |
Defined in PFile.Profile.Internal.Profile | |
Generic Profile Source # | |
type Rep Profile Source # | |
Defined in PFile.Profile.Internal.Profile type Rep Profile = D1 ('MetaData "Profile" "PFile.Profile.Internal.Profile" "pfile-0.1.0.1-2LtZGa2mKrg5ZSmQeq7wuJ" 'False) (C1 ('MetaCons "Profile" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Name) :*: (S1 ('MetaSel ('Just "state") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 State) :*: S1 ('MetaSel ('Just "entries") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Entry])))) |
Entry
represents a filesystem's object (directory, directory link, file,
file link) that is mount
ed (or
push
ed) inside of a Profile
.
Since: 0.1.0.0
Constructors
Entry | |
Instances
FromJSON Entry Source # | |
ToJSON Entry Source # | |
Defined in PFile.Profile.Internal.Profile | |
Generic Entry Source # | |
type Rep Entry Source # | |
Defined in PFile.Profile.Internal.Profile type Rep Entry = D1 ('MetaData "Entry" "PFile.Profile.Internal.Profile" "pfile-0.1.0.1-2LtZGa2mKrg5ZSmQeq7wuJ" 'False) (C1 ('MetaCons "Entry" 'PrefixI 'True) (S1 ('MetaSel ('Just "mountPath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Mount) :*: S1 ('MetaSel ('Just "originPath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Absolute))) |
absoluteRoot :: MonadReader Env m => Name -> m Root Source #
profileRoot :: MonadReader Env m => Name -> m Absolute Source #
Get directory path where absoluteRoot
and profileState
of a Profile
named Name
are located.
Since: 0.1.0.0
profileState :: MonadReader Env m => Name -> m Absolute Source #
Error thrown by dump
.
Since: 0.1.0.0
Constructors
CreateParentInDumpError !CreateParentError | Unable to create a parent directory for
|
DumpError !Absolute !IOException |
|
Error thrown by load
.
Since: 0.1.0.0
Constructors
LoadError !Absolute !IOException |
|
DecodeError !Absolute ![Char] | Decoding error was encountered during |
dump :: (MonadReader Env m, MonadError DumpError m, MonadIO m) => Profile -> m () Source #
Dump Profile
to its profileState
.
Since: 0.1.0.0
load :: (MonadReader Env m, MonadError LoadError m, MonadIO m) => Name -> m Profile Source #
Load Profile
named Name
from its
profileState
.
Since: 0.1.0.0
showDumpError :: DumpError -> Text Source #
showLoadError :: LoadError -> Text Source #
Error thrown by link
.
Since: 0.1.0.0
Constructors
PurgeLinkError !PurgeError | Error was encountered during |
ValidateLinkError !UnlinkedEntryValidateError | Validation error of entries was encountered. |
LinkRollbackError |
|
LinkError !LinkError |
|
data SwitchError Source #
Error thrown by switch
.
Since: 0.1.0.0
Constructors
UnlinkCurrentError !UnlinkError | Error was encountered during |
LinkNextError !LinkError | Error was encountered during |
newtype SwitchOptions Source #
switch
options.
Since: 0.1.0.0
Constructors
SwitchOptions | |
Fields
|
data UnpackError Source #
Error thrown by unpack
.
Since: 0.1.0.0
Constructors
PurgeUnpackError !PurgeError | Error was encountered during |
UnlinkUnpackError !UnlinkError | Error was encountered during |
UnpackRollbackError |
|
Fields
| |
UnpackError !UnpackError |
link :: forall m. (MonadError LinkError m, MonadIO m) => SwitchOptions -> Profile -> m () Source #
unpack :: forall m. (MonadError UnpackError m, MonadIO m) => SwitchOptions -> Profile -> m () Source #
Arguments
:: (MonadError SwitchError m, MonadIO m) | |
=> SwitchOptions | Options that control |
-> Profile | Current profile. |
-> Profile | Next profile. |
-> m () |
showLinkError :: LinkError -> Text Source #
showSwitchError :: SwitchError -> Text Source #
showUnpackError :: UnpackError -> Text Source #