pfile-0.1.0.1: CLI program for profiles management.
Copyright(c) 2024 Illia Shkroba
LicenseBSD3
MaintainerIllia Shkroba <[email protected]>
Stabilityunstable
Portabilitynon-portable (Non-Unix systems are not supported)
Safe HaskellSafe-Inferred
LanguageHaskell2010

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

Documentation

data LoadCurrentError Source #

Error thrown by loadCurrent.

Since: 0.1.0.0

Constructors

CanonicalizeCurrentError !Absolute !IOException

Unable to canonicalize currentLinkPath.

LoadCurrentError !LoadError

Error was encountered during load.

data SetCurrentError Source #

Error thrown by setCurrent.

Since: 0.1.0.0

Constructors

UnsetCurrentError !UnsetCurrentError

Error was encountered during unsetCurrent.

CurrentLinkError !CreateDirectoryLinkError

Unable to create a directory link currentLinkPath pointing at a new current Profile.

newtype UnsetCurrentError Source #

Error thrown by unsetCurrent.

Since: 0.1.0.0

Constructors

CurrentLinkRemoveError RemoveError

Unable to remove a directory link currentLinkPath.

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 Name was found in profilesHomeDirPath.

PushRollbackError

create attempted to rollback due to CreateRollbackCause. The rollback has failed with a list of PopErrors. Since the rollback has failed, the profile passed to create is considered Dangling.

Fields

PushCreateError !CreateRollbackCause

create attempted to rollback due to CreateRollbackCause. The rollback has succeeded. The profile passed to create was not created.

newtype CreateOptions Source #

create options.

Since: 0.1.0.0

Constructors

CreateOptions 

Fields

create Source #

Arguments

:: forall m. (MonadReader Env m, MonadError CreateError m, MonadIO m) 
=> CreateOptions

Options that control create behaviour (currently only linkHandlingStrategy).

-> Name

Name of a profile to be created. The name will be used as a directory name for the profile in profilesHomeDirPath.

-> [Absolute]

List of Absolute paths of filesystem's objects to be pushed into a profile.

-> m Profile 

Create a new profile called Name with a list of Absolute filesystem's objects to be pushed 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

data ListError Source #

Error thrown by list.

Since: 0.1.0.0

Constructors

ProfilesHomeDirDoesNotExistError !Absolute

profilesHomeDirPath does not exist.

ListDirectoryError !Absolute !IOException

IOException was encountered during directory listing.

newtype ListOptions Source #

list options.

Since: 0.1.0.0

Constructors

ListOptions 

Fields

list Source #

Arguments

:: forall m. (MonadReader Env m, MonadError ListError m, MonadIO m) 
=> ListOptions

Options that control list behaviour (currently only shouldFilterDangling).

-> m [Profile] 

List profiles in profilesHomeDirPath directory.

Since: 0.1.0.0

data State Source #

Profiles state.

Since: 0.1.0.0

Constructors

Dangling

When an error is encountered during pushAll, create attempts to rollback. If the rollback fails, the profile is considered Dangling.

Valid

When create succeeds, the created profile has Valid state.

Instances

Instances details
FromJSON State Source # 
Instance details

Defined in PFile.Profile.Internal.Profile

ToJSON State Source # 
Instance details

Defined in PFile.Profile.Internal.Profile

newtype Name Source #

Name of a Profile.

Since: 0.1.0.0

Constructors

Name 

Fields

Instances

Instances details
FromJSON Name Source # 
Instance details

Defined in PFile.Profile.Internal.Profile

ToJSON Name Source # 
Instance details

Defined in PFile.Profile.Internal.Profile

data Profile Source #

Profile holds a list of Entryies.

Since: 0.1.0.0

Constructors

Profile 

Fields

Instances

Instances details
FromJSON Profile Source # 
Instance details

Defined in PFile.Profile.Internal.Profile

ToJSON Profile Source # 
Instance details

Defined in PFile.Profile.Internal.Profile

Generic Profile Source # 
Instance details

Defined in PFile.Profile.Internal.Profile

Associated Types

type Rep Profile :: Type -> Type #

Methods

from :: Profile -> Rep Profile x #

to :: Rep Profile x -> Profile #

type Rep Profile Source # 
Instance details

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]))))

data Entry Source #

Entry represents a filesystem's object (directory, directory link, file, file link) that is mounted (or pushed) inside of a Profile.

Since: 0.1.0.0

Constructors

Entry 

Fields

Instances

Instances details
FromJSON Entry Source # 
Instance details

Defined in PFile.Profile.Internal.Profile

ToJSON Entry Source # 
Instance details

Defined in PFile.Profile.Internal.Profile

Generic Entry Source # 
Instance details

Defined in PFile.Profile.Internal.Profile

Associated Types

type Rep Entry :: Type -> Type #

Methods

from :: Entry -> Rep Entry x #

to :: Rep Entry x -> Entry #

type Rep Entry Source # 
Instance details

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 #

Get directory path where entries of a Profile named Name are stored.

Since: 0.1.0.0

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 #

Get file path where serialized Profile named Name is stored.

Since: 0.1.0.0

data DumpError Source #

Error thrown by dump.

Since: 0.1.0.0

Constructors

CreateParentInDumpError !CreateParentError

Unable to create a parent directory for profileState.

DumpError !Absolute !IOException

IOException was encountered during encodeFile.

data LoadError Source #

Error thrown by load.

Since: 0.1.0.0

Constructors

LoadError !Absolute !IOException

IOException was encountered during eitherDecodeFileStrict.

DecodeError !Absolute ![Char]

Decoding error was encountered during eitherDecodeFileStrict.

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

data LinkError Source #

Error thrown by link.

Since: 0.1.0.0

Constructors

PurgeLinkError !PurgeError

Error was encountered during purge.

ValidateLinkError !UnlinkedEntryValidateError

Validation error of entries was encountered.

LinkRollbackError

link attempted to rollback due to LinkError. The rollback has failed with a list of RemoveErrors. Since the rollback has failed, the profile passed to link was partially linked - some links were created and should be removed manually.

Fields

LinkError !LinkError

link attempted to rollback due to LinkError. The rollback has succeeded. The profile passed to link was not linked.

data SwitchError Source #

Error thrown by switch.

Since: 0.1.0.0

Constructors

UnlinkCurrentError !UnlinkError

Error was encountered during unlink.

LinkNextError !LinkError

Error was encountered during link.

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 purge.

UnlinkUnpackError !UnlinkError

Error was encountered during unlink.

UnpackRollbackError

unpack attempted to rollback due to UnpackError. The rollback has failed with a list of RemoveErrors. Since the rollback has failed, the profile passed to unpack was partially unpacked - some entries were unpacked and should be removed manually.

Fields

UnpackError !UnpackError 

link :: forall m. (MonadError LinkError m, MonadIO m) => SwitchOptions -> Profile -> m () Source #

Create links pointing at Entryies inside of the Profile with linkAll.

Since: 0.1.0.0

unpack :: forall m. (MonadError UnpackError m, MonadIO m) => SwitchOptions -> Profile -> m () Source #

Unpack Profiles entries back to their original locations with unpackAll.

Since: 0.1.0.0

switch Source #

Arguments

:: (MonadError SwitchError m, MonadIO m) 
=> SwitchOptions

Options that control switch behaviour (currently only forceRemoveOccupied).

-> Profile

Current profile.

-> Profile

Next profile.

-> m () 

Switch from the current profile to the next profile. switch unlinks the current profile and then links the next profile.

Since: 0.1.0.0