module Charon.Data.PathData.Formatting
(
PathDataFormat (..),
_FormatMultiline,
_FormatTabular,
_FormatSingleline,
ColFormat (..),
_ColFormatFixed,
_ColFormatMax,
Coloring (..),
Sort (..),
readSort,
sortFn,
formatTabularHeader,
formatTabularHeaderColor,
formatTabularRow,
formatTabularRowColor,
formatMultiline,
formatSingleline,
formatSinglelineColor,
sortNameCreated,
sortSizeName,
sortReverse,
formatFileNameLenMin,
formatOriginalPathLenMin,
minTableWidth,
reservedLineLen,
)
where
import Charon.Data.PathData (PathData)
import Charon.Data.Timestamp qualified as Timestamp
import Charon.Prelude
import Charon.Utils qualified as U
import Data.Char qualified as Ch
import Data.Text qualified as T
import System.Console.Pretty (Color)
import System.Console.Pretty qualified as CPretty
data ColFormat
=
ColFormatFixed Natural
|
ColFormatMax
deriving stock (ColFormat -> ColFormat -> Bool
(ColFormat -> ColFormat -> Bool)
-> (ColFormat -> ColFormat -> Bool) -> Eq ColFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ColFormat -> ColFormat -> Bool
== :: ColFormat -> ColFormat -> Bool
$c/= :: ColFormat -> ColFormat -> Bool
/= :: ColFormat -> ColFormat -> Bool
Eq, Int -> ColFormat -> ShowS
[ColFormat] -> ShowS
ColFormat -> [Char]
(Int -> ColFormat -> ShowS)
-> (ColFormat -> [Char])
-> ([ColFormat] -> ShowS)
-> Show ColFormat
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ColFormat -> ShowS
showsPrec :: Int -> ColFormat -> ShowS
$cshow :: ColFormat -> [Char]
show :: ColFormat -> [Char]
$cshowList :: [ColFormat] -> ShowS
showList :: [ColFormat] -> ShowS
Show)
_ColFormatFixed :: Prism' ColFormat Natural
_ColFormatFixed :: Prism' ColFormat Natural
_ColFormatFixed =
(Natural -> ColFormat)
-> (ColFormat -> Either ColFormat Natural)
-> Prism' ColFormat Natural
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism
Natural -> ColFormat
ColFormatFixed
( \ColFormat
x -> case ColFormat
x of
ColFormatFixed Natural
lbl -> Natural -> Either ColFormat Natural
forall a b. b -> Either a b
Right Natural
lbl
ColFormat
_ -> ColFormat -> Either ColFormat Natural
forall a b. a -> Either a b
Left ColFormat
x
)
{-# INLINE _ColFormatFixed #-}
_ColFormatMax :: Prism' ColFormat ()
_ColFormatMax :: Prism' ColFormat ()
_ColFormatMax =
(() -> ColFormat)
-> (ColFormat -> Either ColFormat ()) -> Prism' ColFormat ()
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism
(ColFormat -> () -> ColFormat
forall a b. a -> b -> a
const ColFormat
ColFormatMax)
( \ColFormat
x -> case ColFormat
x of
ColFormat
ColFormatMax -> () -> Either ColFormat ()
forall a b. b -> Either a b
Right ()
ColFormat
_ -> ColFormat -> Either ColFormat ()
forall a b. a -> Either a b
Left ColFormat
x
)
{-# INLINE _ColFormatMax #-}
data Coloring
=
ColoringOn
|
ColoringOff
|
ColoringDetect
deriving stock (Coloring -> Coloring -> Bool
(Coloring -> Coloring -> Bool)
-> (Coloring -> Coloring -> Bool) -> Eq Coloring
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Coloring -> Coloring -> Bool
== :: Coloring -> Coloring -> Bool
$c/= :: Coloring -> Coloring -> Bool
/= :: Coloring -> Coloring -> Bool
Eq, Int -> Coloring -> ShowS
[Coloring] -> ShowS
Coloring -> [Char]
(Int -> Coloring -> ShowS)
-> (Coloring -> [Char]) -> ([Coloring] -> ShowS) -> Show Coloring
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Coloring -> ShowS
showsPrec :: Int -> Coloring -> ShowS
$cshow :: Coloring -> [Char]
show :: Coloring -> [Char]
$cshowList :: [Coloring] -> ShowS
showList :: [Coloring] -> ShowS
Show)
data PathDataFormat
=
FormatMultiline
|
FormatTabular Coloring (Maybe ColFormat) (Maybe ColFormat)
|
FormatSingleline Coloring
deriving stock (PathDataFormat -> PathDataFormat -> Bool
(PathDataFormat -> PathDataFormat -> Bool)
-> (PathDataFormat -> PathDataFormat -> Bool) -> Eq PathDataFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PathDataFormat -> PathDataFormat -> Bool
== :: PathDataFormat -> PathDataFormat -> Bool
$c/= :: PathDataFormat -> PathDataFormat -> Bool
/= :: PathDataFormat -> PathDataFormat -> Bool
Eq, Int -> PathDataFormat -> ShowS
[PathDataFormat] -> ShowS
PathDataFormat -> [Char]
(Int -> PathDataFormat -> ShowS)
-> (PathDataFormat -> [Char])
-> ([PathDataFormat] -> ShowS)
-> Show PathDataFormat
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PathDataFormat -> ShowS
showsPrec :: Int -> PathDataFormat -> ShowS
$cshow :: PathDataFormat -> [Char]
show :: PathDataFormat -> [Char]
$cshowList :: [PathDataFormat] -> ShowS
showList :: [PathDataFormat] -> ShowS
Show)
_FormatMultiline :: Prism' PathDataFormat ()
_FormatMultiline :: Prism' PathDataFormat ()
_FormatMultiline =
(() -> PathDataFormat)
-> (PathDataFormat -> Either PathDataFormat ())
-> Prism' PathDataFormat ()
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism
(PathDataFormat -> () -> PathDataFormat
forall a b. a -> b -> a
const PathDataFormat
FormatMultiline)
( \PathDataFormat
x -> case PathDataFormat
x of
PathDataFormat
FormatMultiline -> () -> Either PathDataFormat ()
forall a b. b -> Either a b
Right ()
PathDataFormat
_ -> PathDataFormat -> Either PathDataFormat ()
forall a b. a -> Either a b
Left PathDataFormat
x
)
{-# INLINE _FormatMultiline #-}
_FormatTabular :: Prism' PathDataFormat (Coloring, Maybe ColFormat, Maybe ColFormat)
_FormatTabular :: Prism' PathDataFormat (Coloring, Maybe ColFormat, Maybe ColFormat)
_FormatTabular =
((Coloring, Maybe ColFormat, Maybe ColFormat) -> PathDataFormat)
-> (PathDataFormat
-> Either
PathDataFormat (Coloring, Maybe ColFormat, Maybe ColFormat))
-> Prism'
PathDataFormat (Coloring, Maybe ColFormat, Maybe ColFormat)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism
(\(Coloring
a, Maybe ColFormat
b, Maybe ColFormat
c) -> Coloring -> Maybe ColFormat -> Maybe ColFormat -> PathDataFormat
FormatTabular Coloring
a Maybe ColFormat
b Maybe ColFormat
c)
( \PathDataFormat
x -> case PathDataFormat
x of
FormatTabular Coloring
a Maybe ColFormat
b Maybe ColFormat
c -> (Coloring, Maybe ColFormat, Maybe ColFormat)
-> Either
PathDataFormat (Coloring, Maybe ColFormat, Maybe ColFormat)
forall a b. b -> Either a b
Right (Coloring
a, Maybe ColFormat
b, Maybe ColFormat
c)
PathDataFormat
_ -> PathDataFormat
-> Either
PathDataFormat (Coloring, Maybe ColFormat, Maybe ColFormat)
forall a b. a -> Either a b
Left PathDataFormat
x
)
{-# INLINE _FormatTabular #-}
_FormatSingleline :: Prism' PathDataFormat Coloring
_FormatSingleline :: Prism' PathDataFormat Coloring
_FormatSingleline =
(Coloring -> PathDataFormat)
-> (PathDataFormat -> Either PathDataFormat Coloring)
-> Prism' PathDataFormat Coloring
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism
Coloring -> PathDataFormat
FormatSingleline
( \PathDataFormat
x -> case PathDataFormat
x of
FormatSingleline Coloring
c -> Coloring -> Either PathDataFormat Coloring
forall a b. b -> Either a b
Right Coloring
c
PathDataFormat
_ -> PathDataFormat -> Either PathDataFormat Coloring
forall a b. a -> Either a b
Left PathDataFormat
x
)
{-# INLINE _FormatSingleline #-}
sortNameCreated :: PathData -> PathData -> Ordering
sortNameCreated :: PathData -> PathData -> Ordering
sortNameCreated PathData
x PathData
y = case PathData -> PathData -> Ordering
sortName PathData
x PathData
y of
Ordering
EQ -> PathData -> PathData -> Ordering
sortCreated PathData
x PathData
y
Ordering
other -> Ordering
other
sortSizeName :: PathData -> PathData -> Ordering
sortSizeName :: PathData -> PathData -> Ordering
sortSizeName PathData
x PathData
y = case PathData -> PathData -> Ordering
sortSize PathData
x PathData
y of
Ordering
EQ -> PathData -> PathData -> Ordering
sortName PathData
x PathData
y
Ordering
other -> Ordering
other
sortReverse :: (a -> b -> Ordering) -> a -> b -> Ordering
sortReverse :: forall a b. (a -> b -> Ordering) -> a -> b -> Ordering
sortReverse a -> b -> Ordering
f a
x b
y = case a -> b -> Ordering
f a
x b
y of
Ordering
EQ -> Ordering
EQ
Ordering
LT -> Ordering
GT
Ordering
GT -> Ordering
LT
sortCreated :: PathData -> PathData -> Ordering
sortCreated :: PathData -> PathData -> Ordering
sortCreated = (PathData -> Timestamp) -> PathData -> PathData -> Ordering
forall b a. Ord b => (a -> b) -> a -> a -> Ordering
mapOrd (Optic' A_Lens NoIx PathData Timestamp -> PathData -> Timestamp
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Lens NoIx PathData Timestamp
#created)
sortName :: PathData -> PathData -> Ordering
sortName :: PathData -> PathData -> Ordering
sortName PathData
pd1 PathData
pd2 = case ([Char] -> [Char] -> ([Char], [Char]))
-> Either EncodingException [Char]
-> Either EncodingException [Char]
-> Either EncodingException ([Char], [Char])
forall a b c.
(a -> b -> c)
-> Either EncodingException a
-> Either EncodingException b
-> Either EncodingException c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,) (OsPath -> Either EncodingException [Char]
decodeOsToFp OsPath
p1) (OsPath -> Either EncodingException [Char]
decodeOsToFp OsPath
p2) of
Right ([Char]
s1, [Char]
s2) -> ShowS -> [Char] -> [Char] -> Ordering
forall b a. Ord b => (a -> b) -> a -> a -> Ordering
mapOrd ((Char -> Char) -> ShowS
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Char -> Char
Ch.toLower) [Char]
s1 [Char]
s2
Left EncodingException
_ -> OsPath
p1 OsPath -> OsPath -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` OsPath
p2
where
p1 :: OsPath
p1 = PathData
pd1 PathData -> Optic' A_Lens NoIx PathData OsPath -> OsPath
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. (Optic
A_Lens
NoIx
PathData
PathData
(PathI 'TrashEntryFileName)
(PathI 'TrashEntryFileName)
#fileName Optic
A_Lens
NoIx
PathData
PathData
(PathI 'TrashEntryFileName)
(PathI 'TrashEntryFileName)
-> Optic
An_Iso
NoIx
(PathI 'TrashEntryFileName)
(PathI 'TrashEntryFileName)
OsPath
OsPath
-> Optic' A_Lens NoIx PathData OsPath
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic
An_Iso
NoIx
(PathI 'TrashEntryFileName)
(PathI 'TrashEntryFileName)
OsPath
OsPath
#unPathI)
p2 :: OsPath
p2 = PathData
pd2 PathData -> Optic' A_Lens NoIx PathData OsPath -> OsPath
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. (Optic
A_Lens
NoIx
PathData
PathData
(PathI 'TrashEntryFileName)
(PathI 'TrashEntryFileName)
#fileName Optic
A_Lens
NoIx
PathData
PathData
(PathI 'TrashEntryFileName)
(PathI 'TrashEntryFileName)
-> Optic
An_Iso
NoIx
(PathI 'TrashEntryFileName)
(PathI 'TrashEntryFileName)
OsPath
OsPath
-> Optic' A_Lens NoIx PathData OsPath
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic
An_Iso
NoIx
(PathI 'TrashEntryFileName)
(PathI 'TrashEntryFileName)
OsPath
OsPath
#unPathI)
sortSize :: PathData -> PathData -> Ordering
sortSize :: PathData -> PathData -> Ordering
sortSize = (PathData -> Bytes 'B Natural) -> PathData -> PathData -> Ordering
forall b a. Ord b => (a -> b) -> a -> a -> Ordering
mapOrd (Optic' A_Lens NoIx PathData (Bytes 'B Natural)
-> PathData -> Bytes 'B Natural
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Lens NoIx PathData (Bytes 'B Natural)
#size)
mapOrd :: (Ord b) => (a -> b) -> a -> a -> Ordering
mapOrd :: forall b a. Ord b => (a -> b) -> a -> a -> Ordering
mapOrd a -> b
f a
x a
y = a -> b
f a
x b -> b -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` a -> b
f a
y
formatMultiline :: PathData -> Text
formatMultiline :: PathData -> Text
formatMultiline = PathData -> Text
forall a. Pretty a => a -> Text
U.renderPretty
formatSingleline :: PathData -> Text
formatSingleline :: PathData -> Text
formatSingleline = (Text -> Text) -> PathData -> Text
formatSingleline' Text -> Text
forall a. a -> a
id
formatSinglelineColor :: Color -> PathData -> Text
formatSinglelineColor :: Color -> PathData -> Text
formatSinglelineColor = (Text -> Text) -> PathData -> Text
formatSingleline' ((Text -> Text) -> PathData -> Text)
-> (Color -> Text -> Text) -> Color -> PathData -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Color -> Text -> Text
forall a. Pretty a => Color -> a -> a
CPretty.color
formatSingleline' :: (Text -> Text) -> PathData -> Text
formatSingleline' :: (Text -> Text) -> PathData -> Text
formatSingleline' Text -> Text
f PathData
pd =
Text -> Text
f
(Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat
[ Timestamp -> Text
Timestamp.toTextSpace (Timestamp -> Text) -> Timestamp -> Text
forall a b. (a -> b) -> a -> b
$ PathData
pd PathData -> Optic' A_Lens NoIx PathData Timestamp -> Timestamp
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx PathData Timestamp
#created,
Text
" ",
[Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ OsPath -> [Char]
decodeOsToFpDisplayEx (OsPath -> [Char]) -> OsPath -> [Char]
forall a b. (a -> b) -> a -> b
$ PathData
pd PathData -> Optic' A_Lens NoIx PathData OsPath -> OsPath
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic
A_Lens
NoIx
PathData
PathData
(PathI 'TrashEntryOriginalPath)
(PathI 'TrashEntryOriginalPath)
#originalPath Optic
A_Lens
NoIx
PathData
PathData
(PathI 'TrashEntryOriginalPath)
(PathI 'TrashEntryOriginalPath)
-> Optic
An_Iso
NoIx
(PathI 'TrashEntryOriginalPath)
(PathI 'TrashEntryOriginalPath)
OsPath
OsPath
-> Optic' A_Lens NoIx PathData OsPath
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic
An_Iso
NoIx
(PathI 'TrashEntryOriginalPath)
(PathI 'TrashEntryOriginalPath)
OsPath
OsPath
#unPathI
]
formatTabularHeader :: Natural -> Natural -> Text
= (Text -> Text) -> Natural -> Natural -> Text
formatTabularHeader' Text -> Text
forall a. a -> a
id
formatTabularHeaderColor :: Color -> Natural -> Natural -> Text
= (Text -> Text) -> Natural -> Natural -> Text
formatTabularHeader' ((Text -> Text) -> Natural -> Natural -> Text)
-> (Color -> Text -> Text) -> Color -> Natural -> Natural -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Color -> Text -> Text
forall a. Pretty a => Color -> a -> a
CPretty.color
formatTabularHeader' :: (Text -> Text) -> Natural -> Natural -> Text
Text -> Text
f Natural
nameLen Natural
origLen =
Text -> Text
f
(Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat
[ Natural -> Text -> Text
fixLen Natural
nameLen Text
"Name",
Text
sep,
Natural -> Text -> Text
fixLen Natural
origLen Text
"Original",
Text
sep,
Natural -> Text -> Text
fixLen Natural
formatTypeLen Text
"Type",
Text
sep,
Natural -> Text -> Text
fixLen Natural
formatSizeLen Text
"Size",
Text
sep,
Text
"Created",
Text
"\n",
Text
titleLen
]
where
totalLen :: Natural
totalLen = Natural
nameLen Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
+ Natural
origLen Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
+ Natural
reservedLineLen
titleLen :: Text
titleLen = Int -> Text -> Text
T.replicate (Natural -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
totalLen) Text
"-"
reservedLineLen :: Natural
reservedLineLen :: Natural
reservedLineLen =
Natural
formatTypeLen Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
+ Natural
formatSizeLen Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
+ Natural
formatCreatedLen Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
+ Natural
formatSeparatorsLen
minTableWidth :: Natural
minTableWidth :: Natural
minTableWidth =
Natural
reservedLineLen Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
+ Natural
formatFileNameLenMin Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
+ Natural
formatOriginalPathLenMin
formatTabularRow :: Natural -> Natural -> PathData -> Text
formatTabularRow :: Natural -> Natural -> PathData -> Text
formatTabularRow = (Text -> Text) -> Natural -> Natural -> PathData -> Text
formatTabularRow' Text -> Text
forall a. a -> a
id
formatTabularRowColor :: Color -> Natural -> Natural -> PathData -> Text
formatTabularRowColor :: Color -> Natural -> Natural -> PathData -> Text
formatTabularRowColor = (Text -> Text) -> Natural -> Natural -> PathData -> Text
formatTabularRow' ((Text -> Text) -> Natural -> Natural -> PathData -> Text)
-> (Color -> Text -> Text)
-> Color
-> Natural
-> Natural
-> PathData
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Color -> Text -> Text
forall a. Pretty a => Color -> a -> a
CPretty.color
formatTabularRow' :: (Text -> Text) -> Natural -> Natural -> PathData -> Text
formatTabularRow' :: (Text -> Text) -> Natural -> Natural -> PathData -> Text
formatTabularRow' Text -> Text
f Natural
nameLen Natural
origLen PathData
pd =
Text -> Text
f
(Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat
[ Natural -> [Char] -> Text
fixLen' Natural
nameLen (OsPath -> [Char]
decodeOsToFpDisplayEx (OsPath -> [Char]) -> OsPath -> [Char]
forall a b. (a -> b) -> a -> b
$ PathData
pd PathData -> Optic' A_Lens NoIx PathData OsPath -> OsPath
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic
A_Lens
NoIx
PathData
PathData
(PathI 'TrashEntryFileName)
(PathI 'TrashEntryFileName)
#fileName Optic
A_Lens
NoIx
PathData
PathData
(PathI 'TrashEntryFileName)
(PathI 'TrashEntryFileName)
-> Optic
An_Iso
NoIx
(PathI 'TrashEntryFileName)
(PathI 'TrashEntryFileName)
OsPath
OsPath
-> Optic' A_Lens NoIx PathData OsPath
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic
An_Iso
NoIx
(PathI 'TrashEntryFileName)
(PathI 'TrashEntryFileName)
OsPath
OsPath
#unPathI),
Text
sep,
Natural -> [Char] -> Text
fixLen' Natural
origLen (OsPath -> [Char]
decodeOsToFpDisplayEx (OsPath -> [Char]) -> OsPath -> [Char]
forall a b. (a -> b) -> a -> b
$ PathData
pd PathData -> Optic' A_Lens NoIx PathData OsPath -> OsPath
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic
A_Lens
NoIx
PathData
PathData
(PathI 'TrashEntryOriginalPath)
(PathI 'TrashEntryOriginalPath)
#originalPath Optic
A_Lens
NoIx
PathData
PathData
(PathI 'TrashEntryOriginalPath)
(PathI 'TrashEntryOriginalPath)
-> Optic
An_Iso
NoIx
(PathI 'TrashEntryOriginalPath)
(PathI 'TrashEntryOriginalPath)
OsPath
OsPath
-> Optic' A_Lens NoIx PathData OsPath
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic
An_Iso
NoIx
(PathI 'TrashEntryOriginalPath)
(PathI 'TrashEntryOriginalPath)
OsPath
OsPath
#unPathI),
Text
sep,
PathType -> Text
forall {a}. IsString a => PathType -> a
paddedType (PathData
pd PathData -> Optic' A_Lens NoIx PathData PathType -> PathType
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. (Optic A_Lens NoIx PathData PathData PathTypeW PathTypeW
#pathType Optic A_Lens NoIx PathData PathData PathTypeW PathTypeW
-> Optic An_Iso NoIx PathTypeW PathTypeW PathType PathType
-> Optic' A_Lens NoIx PathData PathType
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic An_Iso NoIx PathTypeW PathTypeW PathType PathType
#unPathTypeW)),
Text
sep,
Natural -> Text -> Text
fixLen Natural
formatSizeLen (Bytes 'B Natural -> Text
U.normalizedFormat (Bytes 'B Natural -> Text) -> Bytes 'B Natural -> Text
forall a b. (a -> b) -> a -> b
$ PathData
pd PathData
-> Optic' A_Lens NoIx PathData (Bytes 'B Natural)
-> Bytes 'B Natural
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx PathData (Bytes 'B Natural)
#size),
Text
sep,
Timestamp -> Text
Timestamp.toTextSpace (PathData
pd PathData -> Optic' A_Lens NoIx PathData Timestamp -> Timestamp
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx PathData Timestamp
#created)
]
where
paddedType :: PathType -> a
paddedType PathType
PathTypeFile = a
"F "
paddedType PathType
PathTypeDirectory = a
"D "
paddedType PathType
PathTypeSymbolicLink = a
"L "
paddedType PathType
PathTypeOther = a
"O "
sep :: Text
sep :: Text
sep = Text
" | "
fixLen' :: Natural -> String -> Text
fixLen' :: Natural -> [Char] -> Text
fixLen' Natural
w [Char]
s = Natural -> Text -> Text
fixLen Natural
w ([Char] -> Text
T.pack [Char]
s)
fixLen :: Natural -> Text -> Text
fixLen :: Natural -> Text -> Text
fixLen Natural
w Text
t
| Int
w' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Text -> Int
T.length Text
t = Int -> Text -> Text
T.take (Int
w' Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
3) Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"..."
| Bool
otherwise = Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
T.replicate (Int
w' Int -> Int -> Int
forall a. Num a => a -> a -> a
- Text -> Int
T.length Text
t) Text
" "
where
w' :: Int
w' = Natural -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
w
formatTypeLen :: Natural
formatTypeLen :: Natural
formatTypeLen = Natural
4
formatFileNameLenMin :: Natural
formatFileNameLenMin :: Natural
formatFileNameLenMin = Natural
4
formatOriginalPathLenMin :: Natural
formatOriginalPathLenMin :: Natural
formatOriginalPathLenMin = Natural
8
formatSizeLen :: Natural
formatSizeLen :: Natural
formatSizeLen = Natural
7
formatCreatedLen :: Natural
formatCreatedLen :: Natural
formatCreatedLen = Natural
19
formatSeparatorsLen :: Natural
formatSeparatorsLen :: Natural
formatSeparatorsLen = Natural
12
data Sort
=
Name
|
Size
deriving stock (Sort -> Sort -> Bool
(Sort -> Sort -> Bool) -> (Sort -> Sort -> Bool) -> Eq Sort
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Sort -> Sort -> Bool
== :: Sort -> Sort -> Bool
$c/= :: Sort -> Sort -> Bool
/= :: Sort -> Sort -> Bool
Eq, Int -> Sort -> ShowS
[Sort] -> ShowS
Sort -> [Char]
(Int -> Sort -> ShowS)
-> (Sort -> [Char]) -> ([Sort] -> ShowS) -> Show Sort
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Sort -> ShowS
showsPrec :: Int -> Sort -> ShowS
$cshow :: Sort -> [Char]
show :: Sort -> [Char]
$cshowList :: [Sort] -> ShowS
showList :: [Sort] -> ShowS
Show)
readSort :: (MonadFail m) => Text -> m Sort
readSort :: forall (m :: * -> *). MonadFail m => Text -> m Sort
readSort Text
"name" = Sort -> m Sort
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Sort
Name
readSort Text
"size" = Sort -> m Sort
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Sort
Size
readSort Text
other = [Char] -> m Sort
forall a. [Char] -> m a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> m Sort) -> [Char] -> m Sort
forall a b. (a -> b) -> a -> b
$ [Char]
"Unrecognized sort: " [Char] -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> [Char]
T.unpack Text
other
sortFn :: Bool -> Sort -> PathData -> PathData -> Ordering
sortFn :: Bool -> Sort -> PathData -> PathData -> Ordering
sortFn Bool
b = \case
Sort
Name -> (PathData -> PathData -> Ordering)
-> PathData -> PathData -> Ordering
rev PathData -> PathData -> Ordering
sortNameCreated
Sort
Size -> (PathData -> PathData -> Ordering)
-> PathData -> PathData -> Ordering
rev PathData -> PathData -> Ordering
sortSizeName
where
rev :: (PathData -> PathData -> Ordering)
-> PathData -> PathData -> Ordering
rev
| Bool
b = (PathData -> PathData -> Ordering)
-> PathData -> PathData -> Ordering
forall a b. (a -> b -> Ordering) -> a -> b -> Ordering
sortReverse
| Bool
otherwise = (PathData -> PathData -> Ordering)
-> PathData -> PathData -> Ordering
forall a. a -> a
id