{-# LANGUAGE CPP #-}
{-# LANGUAGE QuasiQuotes #-}
module Charon.Prelude
( module X,
bsToStr,
bsToStrLenient,
showt,
displayExceptiont,
decodeOsToFpDisplayExT,
packed,
unpacked,
pathDotTrash,
pathCharon,
doesAnyPathExist,
doesAnyPathNotExist,
usingReaderT,
)
where
import Control.Applicative as X
( Alternative ((<|>)),
Applicative (liftA2, pure, (<*>)),
(*>),
)
import Control.DeepSeq as X (NFData)
import Control.Monad as X
( Monad ((>>=)),
join,
unless,
void,
when,
(<=<),
(=<<),
(>=>),
)
import Control.Monad.Fail as X (MonadFail (fail))
import Control.Monad.IO.Class as X (MonadIO (liftIO))
import Control.Monad.Reader as X
( MonadReader (ask),
ReaderT,
asks,
local,
runReaderT,
)
import Data.Bifunctor as X (Bifunctor (bimap))
import Data.Bool as X (Bool (False, True), not, otherwise, (&&), (||))
import Data.ByteString as X (ByteString)
import Data.Bytes as X (Bytes (MkBytes), Size (B), _MkBytes)
import Data.Char as X (Char)
import Data.Either as X (Either (Left, Right), either)
import Data.Eq as X (Eq ((/=), (==)))
import Data.Foldable as X
( Foldable (foldMap', foldl', foldr, length),
for_,
null,
sequenceA_,
traverse_,
)
import Data.Function as X (const, flip, id, ($), (.))
import Data.Functor as X (Functor (fmap), ($>), (<$>), (<&>))
import Data.HashMap.Strict as X (HashMap)
import Data.HashSet as X (HashSet)
import Data.Hashable as X (Hashable (hashWithSalt))
import Data.Int as X (Int)
import Data.Kind as X (Constraint, Type)
import Data.List as X (filter, zipWith, (++))
import Data.List.NonEmpty as X (NonEmpty ((:|)))
import Data.Maybe as X (Maybe (Just, Nothing), fromMaybe, maybe)
import Data.Monoid as X (Monoid (mconcat, mempty))
import Data.Ord as X
( Ord (compare, (<), (<=), (>), (>=)),
Ordering (EQ, GT, LT),
min,
)
import Data.Proxy as X (Proxy (Proxy))
import Data.Semigroup as X (Semigroup ((<>)))
import Data.Sequence as X (Seq ((:<|), (:|>)))
import Data.Sequence.NonEmpty as X (NESeq ((:<||), (:||>)))
import Data.String as X (IsString (fromString), String)
import Data.Text as X (Text)
import Data.Text qualified as T
import Data.Traversable as X (traverse)
import Data.Tuple as X (curry, fst, uncurry)
#if MIN_VERSION_base(4, 17, 0)
import Data.Type.Equality as X (type (~))
#endif
import Data.Vector as X (Vector)
import Data.Word as X (Word16, Word8)
import Effects.Concurrent.Async as X (MonadAsync)
import Effects.Exception as X
( Exception (displayException),
ExceptionCS (MkExceptionCS),
ExitCode (ExitFailure, ExitSuccess),
IOException,
MonadCatch,
MonadMask,
MonadThrow,
SomeException,
addCS,
bracket,
catch,
catchAny,
catchAnyCS,
catchCS,
displayNoCS,
exitFailure,
finally,
throwCS,
throwM,
throwString,
try,
tryAny,
tryAnyCS,
tryCS,
)
import Effects.FileSystem.FileReader as X
( MonadFileReader (readBinaryFile),
decodeUtf8,
decodeUtf8Lenient,
readFileUtf8ThrowM,
)
import Effects.FileSystem.FileWriter as X
( MonadFileWriter (appendBinaryFile, writeBinaryFile),
encodeUtf8,
)
import Effects.FileSystem.HandleWriter as X
( MonadHandleWriter
( hClose,
hFlush,
hPut,
openBinaryFile
),
)
import Effects.FileSystem.PathReader as X
( MonadPathReader
( canonicalizePath,
doesDirectoryExist,
doesFileExist,
doesPathExist,
getFileSize,
getHomeDirectory,
listDirectory,
makeAbsolute
),
PathType
( PathTypeDirectory,
PathTypeFile,
PathTypeOther,
PathTypeSymbolicLink
),
doesSymbolicLinkExist,
getXdgConfig,
)
import Effects.FileSystem.PathWriter as X
( MonadPathWriter
( createDirectoryIfMissing,
removeDirectoryRecursive,
removePathForcibly,
renameDirectory,
renameFile
),
)
import Effects.FileSystem.Utils as X
( OsPath,
decodeOsToFp,
decodeOsToFpDisplayEx,
decodeOsToFpThrowM,
encodeFpToOs,
encodeFpToOsThrowM,
osp,
(<.>),
(</>),
)
import Effects.IORef as X
( IORef,
MonadIORef,
modifyIORef',
newIORef,
readIORef,
writeIORef,
)
import Effects.LoggerNS as X
( LogLevel (LevelDebug, LevelError, LevelInfo, LevelWarn),
MonadLogger (monadLoggerLog),
MonadLoggerNS (getNamespace, localNamespace),
addNamespace,
levelFatal,
levelTrace,
logDebug,
logError,
logFatal,
logInfo,
logTrace,
logWarn,
)
import Effects.Optparse as X (MonadOptparse (execParser))
import Effects.System.PosixCompat as X (MonadPosixCompat)
import Effects.System.Terminal as X
( MonadTerminal (putStr, putStrLn),
print,
putTextLn,
)
import Effects.Time as X (MonadTime)
import GHC.Enum as X (Bounded (maxBound, minBound), Enum (toEnum))
import GHC.Err as X (error, undefined)
import GHC.Float as X (Double)
import GHC.Generics as X (Generic)
import GHC.Integer as X (Integer)
import GHC.Natural as X (Natural)
import GHC.Num as X (Num ((*), (+), (-)))
import GHC.Real as X (Integral (div), even, fromIntegral, realToFrac)
import GHC.Stack as X
( CallStack,
HasCallStack,
callStack,
prettyCallStack,
)
import Optics.Core as X
( A_Getter,
A_Lens,
A_Setter,
AffineTraversal',
Getter,
Is,
Iso',
LabelOptic (labelOptic),
LabelOptic',
Lens,
Lens',
Optic',
Prism',
iso,
lens,
over',
preview,
prism,
review,
set',
to,
view,
(%),
(%?),
(&),
(.~),
(^.),
(^?),
_1,
_2,
_3,
_4,
_Just,
)
import Optics.Core.Extras as X (is)
import Optics.TH as X
( generateUpdateableOptics,
makeFieldLabelsNoPrefix,
makeFieldLabelsWith,
makePrisms,
noPrefixFieldLabels,
)
import PathSize as X (findLargestPaths)
import Prettyprinter as X
( Doc,
Pretty (pretty),
layoutCompact,
line,
vsep,
(<+>),
)
import Prettyprinter.Render.Text as X (renderStrict)
import System.IO as X
( BufferMode (NoBuffering),
FilePath,
Handle,
IO,
IOMode (AppendMode),
)
import Text.Show as X (Show (show))
showt :: (Show a) => a -> Text
showt :: forall a. Show a => a -> Text
showt = String -> Text
T.pack (String -> Text) -> (a -> String) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show
displayExceptiont :: (Exception e) => e -> Text
displayExceptiont :: forall e. Exception e => e -> Text
displayExceptiont = String -> Text
T.pack (String -> Text) -> (e -> String) -> e -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> String
forall e. Exception e => e -> String
displayException
bsToStr :: ByteString -> String
bsToStr :: ByteString -> String
bsToStr = (UnicodeException -> String)
-> (Text -> String) -> Either UnicodeException Text -> String
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either UnicodeException -> String
forall e. Exception e => e -> String
displayException Text -> String
T.unpack (Either UnicodeException Text -> String)
-> (ByteString -> Either UnicodeException Text)
-> ByteString
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either UnicodeException Text
decodeUtf8
bsToStrLenient :: ByteString -> String
bsToStrLenient :: ByteString -> String
bsToStrLenient = Text -> String
T.unpack (Text -> String) -> (ByteString -> Text) -> ByteString -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
decodeUtf8Lenient
packed :: Iso' String Text
packed :: Iso' String Text
packed = (String -> Text) -> (Text -> String) -> Iso' String Text
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso String -> Text
T.pack Text -> String
T.unpack
{-# INLINE packed #-}
unpacked :: Iso' Text String
unpacked :: Iso' Text String
unpacked = (Text -> String) -> (String -> Text) -> Iso' Text String
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Text -> String
T.unpack String -> Text
T.pack
{-# INLINE unpacked #-}
usingReaderT :: b -> ReaderT b m a -> m a
usingReaderT :: forall b (m :: * -> *) a. b -> ReaderT b m a -> m a
usingReaderT = (ReaderT b m a -> b -> m a) -> b -> ReaderT b m a -> m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip ReaderT b m a -> b -> m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT
pathCharon :: OsPath
pathCharon :: OsPath
pathCharon = [osp|charon|]
pathDotTrash :: OsPath
pathDotTrash :: OsPath
pathDotTrash = [osp|.trash|]
doesAnyPathExist ::
( HasCallStack,
MonadCatch m,
MonadPathReader m
) =>
OsPath ->
m Bool
doesAnyPathExist :: forall (m :: * -> *).
(HasCallStack, MonadCatch m, MonadPathReader m) =>
OsPath -> m Bool
doesAnyPathExist OsPath
p = do
Bool
symlinkExists <- OsPath -> m Bool
forall (m :: * -> *).
(HasCallStack, MonadCatch m, MonadPathReader m) =>
OsPath -> m Bool
doesSymbolicLinkExist OsPath
p
if Bool
symlinkExists
then Bool -> m Bool
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True
else OsPath -> m Bool
forall (m :: * -> *).
(MonadPathReader m, HasCallStack) =>
OsPath -> m Bool
doesPathExist OsPath
p
doesAnyPathNotExist ::
( HasCallStack,
MonadCatch m,
MonadPathReader m
) =>
OsPath ->
m Bool
doesAnyPathNotExist :: forall (m :: * -> *).
(HasCallStack, MonadCatch m, MonadPathReader m) =>
OsPath -> m Bool
doesAnyPathNotExist = (Bool -> Bool) -> m Bool -> m Bool
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Bool -> Bool
not (m Bool -> m Bool) -> (OsPath -> m Bool) -> OsPath -> m Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> m Bool
forall (m :: * -> *).
(HasCallStack, MonadCatch m, MonadPathReader m) =>
OsPath -> m Bool
doesAnyPathExist
decodeOsToFpDisplayExT :: OsPath -> Text
decodeOsToFpDisplayExT :: OsPath -> Text
decodeOsToFpDisplayExT = String -> Text
T.pack (String -> Text) -> (OsPath -> String) -> OsPath -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OsPath -> String
decodeOsToFpDisplayEx