{-# LANGUAGE CPP #-}
module Charon.Exception
(
TrashEntryNotFoundE (..),
TrashEntryWildcardNotFoundE (..),
TrashEntryFileNotFoundE (..),
TrashEntryInfoNotFoundE (..),
TrashEntryInfoBadExtE (..),
RenameDuplicateE (..),
RestoreCollisionE (..),
RootE (..),
EmptyPathE (..),
DotsPathE (..),
FileNameEmptyE (..),
UniquePathNotPrefixE (..),
InfoDecodeE (..),
EmptySearchResults (..),
BackendDetectE (..),
)
where
import Charon.Backend.Data (Backend)
import Charon.Backend.Data qualified as Backend
import Charon.Data.Paths
( PathI (MkPathI),
PathIndex
( TrashEntryFileName,
TrashEntryInfo,
TrashEntryOriginalPath,
TrashEntryPath,
TrashHome
),
)
import Charon.Data.Paths qualified as Paths
import Charon.Data.UniqueSeq (UniqueSeq)
import Charon.Prelude
import GHC.Exts (IsList (toList))
import System.OsPath (encodeUtf)
newtype RenameDuplicateE = MkRenameDuplicateE (PathI TrashEntryPath)
deriving stock (Int -> RenameDuplicateE -> ShowS
[RenameDuplicateE] -> ShowS
RenameDuplicateE -> String
(Int -> RenameDuplicateE -> ShowS)
-> (RenameDuplicateE -> String)
-> ([RenameDuplicateE] -> ShowS)
-> Show RenameDuplicateE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RenameDuplicateE -> ShowS
showsPrec :: Int -> RenameDuplicateE -> ShowS
$cshow :: RenameDuplicateE -> String
show :: RenameDuplicateE -> String
$cshowList :: [RenameDuplicateE] -> ShowS
showList :: [RenameDuplicateE] -> ShowS
Show)
instance Exception RenameDuplicateE where
displayException :: RenameDuplicateE -> String
displayException (MkRenameDuplicateE PathI 'TrashEntryPath
n) =
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Failed renaming duplicate file: '",
OsPath -> String
decodeOsToFpDisplayEx (OsPath -> String) -> OsPath -> String
forall a b. (a -> b) -> a -> b
$ PathI 'TrashEntryPath
n PathI 'TrashEntryPath
-> Optic' An_Iso NoIx (PathI 'TrashEntryPath) OsPath -> OsPath
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' An_Iso NoIx (PathI 'TrashEntryPath) OsPath
#unPathI,
String
"'"
]
newtype TrashEntryNotFoundE = MkTrashEntryNotFoundE (PathI TrashEntryFileName)
deriving stock (Int -> TrashEntryNotFoundE -> ShowS
[TrashEntryNotFoundE] -> ShowS
TrashEntryNotFoundE -> String
(Int -> TrashEntryNotFoundE -> ShowS)
-> (TrashEntryNotFoundE -> String)
-> ([TrashEntryNotFoundE] -> ShowS)
-> Show TrashEntryNotFoundE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TrashEntryNotFoundE -> ShowS
showsPrec :: Int -> TrashEntryNotFoundE -> ShowS
$cshow :: TrashEntryNotFoundE -> String
show :: TrashEntryNotFoundE -> String
$cshowList :: [TrashEntryNotFoundE] -> ShowS
showList :: [TrashEntryNotFoundE] -> ShowS
Show)
instance Exception TrashEntryNotFoundE where
displayException :: TrashEntryNotFoundE -> String
displayException (MkTrashEntryNotFoundE PathI 'TrashEntryFileName
name) =
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"No entry for '",
OsPath -> String
decodeOsToFpDisplayEx (OsPath -> String) -> OsPath -> String
forall a b. (a -> b) -> a -> b
$ PathI 'TrashEntryFileName
name PathI 'TrashEntryFileName
-> Optic' An_Iso NoIx (PathI 'TrashEntryFileName) OsPath -> OsPath
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' An_Iso NoIx (PathI 'TrashEntryFileName) OsPath
#unPathI,
String
"'"
]
newtype TrashEntryWildcardNotFoundE
= MkTrashEntryWildcardNotFoundE (PathI TrashEntryFileName)
deriving stock (Int -> TrashEntryWildcardNotFoundE -> ShowS
[TrashEntryWildcardNotFoundE] -> ShowS
TrashEntryWildcardNotFoundE -> String
(Int -> TrashEntryWildcardNotFoundE -> ShowS)
-> (TrashEntryWildcardNotFoundE -> String)
-> ([TrashEntryWildcardNotFoundE] -> ShowS)
-> Show TrashEntryWildcardNotFoundE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TrashEntryWildcardNotFoundE -> ShowS
showsPrec :: Int -> TrashEntryWildcardNotFoundE -> ShowS
$cshow :: TrashEntryWildcardNotFoundE -> String
show :: TrashEntryWildcardNotFoundE -> String
$cshowList :: [TrashEntryWildcardNotFoundE] -> ShowS
showList :: [TrashEntryWildcardNotFoundE] -> ShowS
Show)
instance Exception TrashEntryWildcardNotFoundE where
displayException :: TrashEntryWildcardNotFoundE -> String
displayException (MkTrashEntryWildcardNotFoundE PathI 'TrashEntryFileName
name) =
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"No entries found for wildcard search '",
OsPath -> String
decodeOsToFpDisplayEx (OsPath -> String) -> OsPath -> String
forall a b. (a -> b) -> a -> b
$ PathI 'TrashEntryFileName
name PathI 'TrashEntryFileName
-> Optic' An_Iso NoIx (PathI 'TrashEntryFileName) OsPath -> OsPath
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' An_Iso NoIx (PathI 'TrashEntryFileName) OsPath
#unPathI,
String
"'"
]
data TrashEntryFileNotFoundE
= MkTrashEntryFileNotFoundE
(PathI TrashHome)
(PathI TrashEntryFileName)
deriving stock (Int -> TrashEntryFileNotFoundE -> ShowS
[TrashEntryFileNotFoundE] -> ShowS
TrashEntryFileNotFoundE -> String
(Int -> TrashEntryFileNotFoundE -> ShowS)
-> (TrashEntryFileNotFoundE -> String)
-> ([TrashEntryFileNotFoundE] -> ShowS)
-> Show TrashEntryFileNotFoundE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TrashEntryFileNotFoundE -> ShowS
showsPrec :: Int -> TrashEntryFileNotFoundE -> ShowS
$cshow :: TrashEntryFileNotFoundE -> String
show :: TrashEntryFileNotFoundE -> String
$cshowList :: [TrashEntryFileNotFoundE] -> ShowS
showList :: [TrashEntryFileNotFoundE] -> ShowS
Show)
instance Exception TrashEntryFileNotFoundE where
displayException :: TrashEntryFileNotFoundE -> String
displayException (MkTrashEntryFileNotFoundE (MkPathI OsPath
thome) PathI 'TrashEntryFileName
name) =
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"The file '",
OsPath -> String
decodeOsToFpDisplayEx (OsPath -> String) -> OsPath -> String
forall a b. (a -> b) -> a -> b
$ PathI 'TrashEntryFileName
name PathI 'TrashEntryFileName
-> Optic' An_Iso NoIx (PathI 'TrashEntryFileName) OsPath -> OsPath
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' An_Iso NoIx (PathI 'TrashEntryFileName) OsPath
#unPathI,
String
"' was not found in the trash '",
OsPath -> String
decodeOsToFpDisplayEx OsPath
thome,
String
"' despite being listed in the index. This can be ",
String
"fixed by manually deleting the info file or deleting everything ",
String
"(i.e. charon empty -f)."
]
data TrashEntryInfoNotFoundE
= MkTrashEntryInfoNotFoundE
(PathI TrashHome)
(PathI TrashEntryFileName)
deriving stock (Int -> TrashEntryInfoNotFoundE -> ShowS
[TrashEntryInfoNotFoundE] -> ShowS
TrashEntryInfoNotFoundE -> String
(Int -> TrashEntryInfoNotFoundE -> ShowS)
-> (TrashEntryInfoNotFoundE -> String)
-> ([TrashEntryInfoNotFoundE] -> ShowS)
-> Show TrashEntryInfoNotFoundE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TrashEntryInfoNotFoundE -> ShowS
showsPrec :: Int -> TrashEntryInfoNotFoundE -> ShowS
$cshow :: TrashEntryInfoNotFoundE -> String
show :: TrashEntryInfoNotFoundE -> String
$cshowList :: [TrashEntryInfoNotFoundE] -> ShowS
showList :: [TrashEntryInfoNotFoundE] -> ShowS
Show)
instance Exception TrashEntryInfoNotFoundE where
displayException :: TrashEntryInfoNotFoundE -> String
displayException (MkTrashEntryInfoNotFoundE (MkPathI OsPath
thome) (MkPathI OsPath
name)) =
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"The file '",
OsPath -> String
decodeOsToFpDisplayEx OsPath
nameExt,
String
"' was not found in the trash '",
OsPath -> String
decodeOsToFpDisplayEx OsPath
thome,
String
"' index despite existing in the trash itself. This can be fixed by ",
String
"manually deleting the entry or deleting everything ",
String
"(i.e. charon empty -f)."
]
where
nameExt :: OsPath
nameExt = case String -> Maybe OsPath
forall (m :: * -> *). MonadThrow m => String -> m OsPath
encodeUtf String
".<ext>" of
Maybe OsPath
Nothing -> OsPath
name
Just OsPath
s -> OsPath
name OsPath -> OsPath -> OsPath
forall a. Semigroup a => a -> a -> a
<> OsPath
s
data TrashEntryInfoBadExtE
= MkTrashEntryInfoBadExtE
(PathI TrashEntryFileName)
OsPath
OsPath
deriving stock (Int -> TrashEntryInfoBadExtE -> ShowS
[TrashEntryInfoBadExtE] -> ShowS
TrashEntryInfoBadExtE -> String
(Int -> TrashEntryInfoBadExtE -> ShowS)
-> (TrashEntryInfoBadExtE -> String)
-> ([TrashEntryInfoBadExtE] -> ShowS)
-> Show TrashEntryInfoBadExtE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TrashEntryInfoBadExtE -> ShowS
showsPrec :: Int -> TrashEntryInfoBadExtE -> ShowS
$cshow :: TrashEntryInfoBadExtE -> String
show :: TrashEntryInfoBadExtE -> String
$cshowList :: [TrashEntryInfoBadExtE] -> ShowS
showList :: [TrashEntryInfoBadExtE] -> ShowS
Show)
instance Exception TrashEntryInfoBadExtE where
displayException :: TrashEntryInfoBadExtE -> String
displayException (MkTrashEntryInfoBadExtE PathI 'TrashEntryFileName
name OsPath
actualExt OsPath
expectedExt) =
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"The trash index file '",
OsPath -> String
decodeOsToFpDisplayEx (OsPath -> String) -> OsPath -> String
forall a b. (a -> b) -> a -> b
$ PathI 'TrashEntryFileName
name PathI 'TrashEntryFileName
-> Optic' An_Iso NoIx (PathI 'TrashEntryFileName) OsPath -> OsPath
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' An_Iso NoIx (PathI 'TrashEntryFileName) OsPath
#unPathI,
String
"' has an unexpected file extension: '",
OsPath -> String
decodeOsToFpDisplayEx OsPath
actualExt,
String
"'. Expected '",
OsPath -> String
decodeOsToFpDisplayEx OsPath
expectedExt,
String
"'"
]
newtype BackendDetectE = MkBackendDetectE Backend
deriving stock (Int -> BackendDetectE -> ShowS
[BackendDetectE] -> ShowS
BackendDetectE -> String
(Int -> BackendDetectE -> ShowS)
-> (BackendDetectE -> String)
-> ([BackendDetectE] -> ShowS)
-> Show BackendDetectE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BackendDetectE -> ShowS
showsPrec :: Int -> BackendDetectE -> ShowS
$cshow :: BackendDetectE -> String
show :: BackendDetectE -> String
$cshowList :: [BackendDetectE] -> ShowS
showList :: [BackendDetectE] -> ShowS
Show)
instance Exception BackendDetectE where
displayException :: BackendDetectE -> String
displayException (MkBackendDetectE Backend
wantedExt) =
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Wanted backend '",
Backend -> String
forall s. IsString s => Backend -> s
Backend.backendName Backend
wantedExt,
String
"', but detected something else"
]
data RestoreCollisionE
= MkRestoreCollisionE
(PathI TrashEntryFileName)
(PathI TrashEntryOriginalPath)
deriving stock (Int -> RestoreCollisionE -> ShowS
[RestoreCollisionE] -> ShowS
RestoreCollisionE -> String
(Int -> RestoreCollisionE -> ShowS)
-> (RestoreCollisionE -> String)
-> ([RestoreCollisionE] -> ShowS)
-> Show RestoreCollisionE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestoreCollisionE -> ShowS
showsPrec :: Int -> RestoreCollisionE -> ShowS
$cshow :: RestoreCollisionE -> String
show :: RestoreCollisionE -> String
$cshowList :: [RestoreCollisionE] -> ShowS
showList :: [RestoreCollisionE] -> ShowS
Show)
instance Exception RestoreCollisionE where
displayException :: RestoreCollisionE -> String
displayException (MkRestoreCollisionE PathI 'TrashEntryFileName
n PathI 'TrashEntryOriginalPath
o) =
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Cannot restore the trash file '",
OsPath -> String
decodeOsToFpDisplayEx (OsPath -> String) -> OsPath -> String
forall a b. (a -> b) -> a -> b
$ PathI 'TrashEntryFileName
n PathI 'TrashEntryFileName
-> Optic' An_Iso NoIx (PathI 'TrashEntryFileName) OsPath -> OsPath
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' An_Iso NoIx (PathI 'TrashEntryFileName) OsPath
#unPathI,
String
"' as one exists at the original location: '",
OsPath -> String
decodeOsToFpDisplayEx (OsPath -> String) -> OsPath -> String
forall a b. (a -> b) -> a -> b
$ PathI 'TrashEntryOriginalPath
o PathI 'TrashEntryOriginalPath
-> Optic' An_Iso NoIx (PathI 'TrashEntryOriginalPath) OsPath
-> OsPath
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' An_Iso NoIx (PathI 'TrashEntryOriginalPath) OsPath
#unPathI,
String
"'"
]
data RootE = MkRootE
deriving stock (Int -> RootE -> ShowS
[RootE] -> ShowS
RootE -> String
(Int -> RootE -> ShowS)
-> (RootE -> String) -> ([RootE] -> ShowS) -> Show RootE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RootE -> ShowS
showsPrec :: Int -> RootE -> ShowS
$cshow :: RootE -> String
show :: RootE -> String
$cshowList :: [RootE] -> ShowS
showList :: [RootE] -> ShowS
Show)
instance Exception RootE where
displayException :: RootE -> String
displayException RootE
_ = String
"Attempted to delete root! This is not allowed."
data EmptyPathE = MkEmptyPathE
deriving stock (Int -> EmptyPathE -> ShowS
[EmptyPathE] -> ShowS
EmptyPathE -> String
(Int -> EmptyPathE -> ShowS)
-> (EmptyPathE -> String)
-> ([EmptyPathE] -> ShowS)
-> Show EmptyPathE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EmptyPathE -> ShowS
showsPrec :: Int -> EmptyPathE -> ShowS
$cshow :: EmptyPathE -> String
show :: EmptyPathE -> String
$cshowList :: [EmptyPathE] -> ShowS
showList :: [EmptyPathE] -> ShowS
Show)
instance Exception EmptyPathE where
displayException :: EmptyPathE -> String
displayException EmptyPathE
_ = String
"Attempted to delete the empty path! This is not allowed."
newtype DotsPathE = MkDotsPathE (PathI TrashEntryOriginalPath)
deriving stock (Int -> DotsPathE -> ShowS
[DotsPathE] -> ShowS
DotsPathE -> String
(Int -> DotsPathE -> ShowS)
-> (DotsPathE -> String)
-> ([DotsPathE] -> ShowS)
-> Show DotsPathE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DotsPathE -> ShowS
showsPrec :: Int -> DotsPathE -> ShowS
$cshow :: DotsPathE -> String
show :: DotsPathE -> String
$cshowList :: [DotsPathE] -> ShowS
showList :: [DotsPathE] -> ShowS
Show)
instance Exception DotsPathE where
displayException :: DotsPathE -> String
displayException (MkDotsPathE PathI 'TrashEntryOriginalPath
p) =
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Attempted to delete the special path '",
OsPath -> String
decodeOsToFpDisplayEx (OsPath -> String) -> OsPath -> String
forall a b. (a -> b) -> a -> b
$ PathI 'TrashEntryOriginalPath
p PathI 'TrashEntryOriginalPath
-> Optic' An_Iso NoIx (PathI 'TrashEntryOriginalPath) OsPath
-> OsPath
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' An_Iso NoIx (PathI 'TrashEntryOriginalPath) OsPath
#unPathI,
String
"'! This is not allowed."
]
newtype FileNameEmptyE = MkFileNameEmptyE (PathI TrashEntryOriginalPath)
deriving stock (Int -> FileNameEmptyE -> ShowS
[FileNameEmptyE] -> ShowS
FileNameEmptyE -> String
(Int -> FileNameEmptyE -> ShowS)
-> (FileNameEmptyE -> String)
-> ([FileNameEmptyE] -> ShowS)
-> Show FileNameEmptyE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FileNameEmptyE -> ShowS
showsPrec :: Int -> FileNameEmptyE -> ShowS
$cshow :: FileNameEmptyE -> String
show :: FileNameEmptyE -> String
$cshowList :: [FileNameEmptyE] -> ShowS
showList :: [FileNameEmptyE] -> ShowS
Show)
instance Exception FileNameEmptyE where
displayException :: FileNameEmptyE -> String
displayException (MkFileNameEmptyE PathI 'TrashEntryOriginalPath
p) =
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Derived empty file name from the path '",
OsPath -> String
decodeOsToFpDisplayEx (OsPath -> String) -> OsPath -> String
forall a b. (a -> b) -> a -> b
$ PathI 'TrashEntryOriginalPath
p PathI 'TrashEntryOriginalPath
-> Optic' An_Iso NoIx (PathI 'TrashEntryOriginalPath) OsPath
-> OsPath
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' An_Iso NoIx (PathI 'TrashEntryOriginalPath) OsPath
#unPathI,
String
"'"
]
data UniquePathNotPrefixE
= MkUniquePathNotPrefixE
(PathI TrashEntryFileName)
(PathI TrashEntryFileName)
deriving stock (Int -> UniquePathNotPrefixE -> ShowS
[UniquePathNotPrefixE] -> ShowS
UniquePathNotPrefixE -> String
(Int -> UniquePathNotPrefixE -> ShowS)
-> (UniquePathNotPrefixE -> String)
-> ([UniquePathNotPrefixE] -> ShowS)
-> Show UniquePathNotPrefixE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UniquePathNotPrefixE -> ShowS
showsPrec :: Int -> UniquePathNotPrefixE -> ShowS
$cshow :: UniquePathNotPrefixE -> String
show :: UniquePathNotPrefixE -> String
$cshowList :: [UniquePathNotPrefixE] -> ShowS
showList :: [UniquePathNotPrefixE] -> ShowS
Show)
instance Exception UniquePathNotPrefixE where
displayException :: UniquePathNotPrefixE -> String
displayException (MkUniquePathNotPrefixE PathI 'TrashEntryFileName
origName PathI 'TrashEntryFileName
newName) =
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Original path name '",
OsPath -> String
decodeOsToFpDisplayEx (OsPath -> String) -> OsPath -> String
forall a b. (a -> b) -> a -> b
$ PathI 'TrashEntryFileName
origName PathI 'TrashEntryFileName
-> Optic' An_Iso NoIx (PathI 'TrashEntryFileName) OsPath -> OsPath
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' An_Iso NoIx (PathI 'TrashEntryFileName) OsPath
#unPathI,
String
"' is not a prefix of the new unique name '",
OsPath -> String
decodeOsToFpDisplayEx (OsPath -> String) -> OsPath -> String
forall a b. (a -> b) -> a -> b
$ PathI 'TrashEntryFileName
newName PathI 'TrashEntryFileName
-> Optic' An_Iso NoIx (PathI 'TrashEntryFileName) OsPath -> OsPath
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' An_Iso NoIx (PathI 'TrashEntryFileName) OsPath
#unPathI,
String
"'"
]
data InfoDecodeE = MkInfoDecodeE (PathI TrashEntryInfo) ByteString String
deriving stock (Int -> InfoDecodeE -> ShowS
[InfoDecodeE] -> ShowS
InfoDecodeE -> String
(Int -> InfoDecodeE -> ShowS)
-> (InfoDecodeE -> String)
-> ([InfoDecodeE] -> ShowS)
-> Show InfoDecodeE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InfoDecodeE -> ShowS
showsPrec :: Int -> InfoDecodeE -> ShowS
$cshow :: InfoDecodeE -> String
show :: InfoDecodeE -> String
$cshowList :: [InfoDecodeE] -> ShowS
showList :: [InfoDecodeE] -> ShowS
Show)
instance Exception InfoDecodeE where
displayException :: InfoDecodeE -> String
displayException (MkInfoDecodeE PathI 'TrashEntryInfo
path ByteString
bs String
err) =
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Could not decode file '",
OsPath -> String
decodeOsToFpDisplayEx (OsPath -> String) -> OsPath -> String
forall a b. (a -> b) -> a -> b
$ PathI 'TrashEntryInfo
path PathI 'TrashEntryInfo
-> Optic' An_Iso NoIx (PathI 'TrashEntryInfo) OsPath -> OsPath
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' An_Iso NoIx (PathI 'TrashEntryInfo) OsPath
#unPathI,
String
"' with contents:\n",
ByteString -> String
bsToStrLenient ByteString
bs,
String
"\nError: ",
String
err
]
newtype EmptySearchResults
= MkEmptySearchResults (UniqueSeq (PathI TrashEntryFileName))
deriving stock (Int -> EmptySearchResults -> ShowS
[EmptySearchResults] -> ShowS
EmptySearchResults -> String
(Int -> EmptySearchResults -> ShowS)
-> (EmptySearchResults -> String)
-> ([EmptySearchResults] -> ShowS)
-> Show EmptySearchResults
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EmptySearchResults -> ShowS
showsPrec :: Int -> EmptySearchResults -> ShowS
$cshow :: EmptySearchResults -> String
show :: EmptySearchResults -> String
$cshowList :: [EmptySearchResults] -> ShowS
showList :: [EmptySearchResults] -> ShowS
Show)
instance Exception EmptySearchResults where
displayException :: EmptySearchResults -> String
displayException (MkEmptySearchResults UniqueSeq (PathI 'TrashEntryFileName)
useq) =
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Search for paths failed: ",
[PathI 'TrashEntryFileName] -> String
forall (a :: PathIndex). [PathI a] -> String
Paths.showPaths ([PathI 'TrashEntryFileName] -> String)
-> [PathI 'TrashEntryFileName] -> String
forall a b. (a -> b) -> a -> b
$ Seq (PathI 'TrashEntryFileName)
-> [Item (Seq (PathI 'TrashEntryFileName))]
forall l. IsList l => l -> [Item l]
toList (UniqueSeq (PathI 'TrashEntryFileName)
useq UniqueSeq (PathI 'TrashEntryFileName)
-> Optic'
A_Getter
NoIx
(UniqueSeq (PathI 'TrashEntryFileName))
(Seq (PathI 'TrashEntryFileName))
-> Seq (PathI 'TrashEntryFileName)
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Getter
NoIx
(UniqueSeq (PathI 'TrashEntryFileName))
(Seq (PathI 'TrashEntryFileName))
#seq)
]