module Data.Git.Phoenix.Uber where
import Control.Lens ((%~), _2)
import Data.Binary qualified as B
import Data.ByteString.Lazy qualified as L
import Data.ByteString.Lazy.Char8 qualified as L8
import Data.Git.Phoenix.App
import Data.Git.Phoenix.CmdArgs (InDir)
import Data.Git.Phoenix.Io
import Data.Git.Phoenix.Object
import Data.Git.Phoenix.Prelude
import Data.Git.Phoenix.Sha
import Data.List qualified as I
import Data.Map.Strict qualified as M
type ShaDedupMap = M.Map ComHash Int
data GitObject
= GitObject
{ GitObject -> ComHash
gobHash :: !ComHash
, GitObject -> FilePath
gobOrigin :: !FilePath
}
deriving (Int -> GitObject -> ShowS
[GitObject] -> ShowS
GitObject -> FilePath
(Int -> GitObject -> ShowS)
-> (GitObject -> FilePath)
-> ([GitObject] -> ShowS)
-> Show GitObject
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GitObject -> ShowS
showsPrec :: Int -> GitObject -> ShowS
$cshow :: GitObject -> FilePath
show :: GitObject -> FilePath
$cshowList :: [GitObject] -> ShowS
showList :: [GitObject] -> ShowS
Show, GitObject -> GitObject -> Bool
(GitObject -> GitObject -> Bool)
-> (GitObject -> GitObject -> Bool) -> Eq GitObject
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GitObject -> GitObject -> Bool
== :: GitObject -> GitObject -> Bool
$c/= :: GitObject -> GitObject -> Bool
/= :: GitObject -> GitObject -> Bool
Eq, (forall x. GitObject -> Rep GitObject x)
-> (forall x. Rep GitObject x -> GitObject) -> Generic GitObject
forall x. Rep GitObject x -> GitObject
forall x. GitObject -> Rep GitObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GitObject -> Rep GitObject x
from :: forall x. GitObject -> Rep GitObject x
$cto :: forall x. Rep GitObject x -> GitObject
to :: forall x. Rep GitObject x -> GitObject
Generic)
instance NFData GitObject
gitObjectFilePath :: GitObject -> FilePath
gitObjectFilePath :: GitObject -> FilePath
gitObjectFilePath = (FilePath -> ShowS) -> (FilePath, FilePath) -> FilePath
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry FilePath -> ShowS
(</>) ((FilePath, FilePath) -> FilePath)
-> (GitObject -> (FilePath, FilePath)) -> GitObject -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> FilePath -> (FilePath, FilePath)
forall a. Int -> [a] -> ([a], [a])
I.splitAt Int
2 (FilePath -> (FilePath, FilePath))
-> (GitObject -> FilePath) -> GitObject -> (FilePath, FilePath)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ComHash -> FilePath
showDigest (ComHash -> FilePath)
-> (GitObject -> ComHash) -> GitObject -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GitObject -> ComHash
gobHash
mkGitObject :: PhoenixM m => FilePath -> m (Maybe GitObject)
mkGitObject :: forall (m :: * -> *). PhoenixM m => FilePath -> m (Maybe GitObject)
mkGitObject FilePath
fp =
FilePath -> (Handle -> m (Maybe GitObject)) -> m (Maybe GitObject)
forall a (m :: * -> *).
(NFData a, MonadUnliftIO m, HasInHandlesSem m) =>
FilePath -> (Handle -> m a) -> m a
withHandle FilePath
fp ((Handle -> m (Maybe GitObject)) -> m (Maybe GitObject))
-> (Handle -> m (Maybe GitObject)) -> m (Maybe GitObject)
forall a b. (a -> b) -> a -> b
$ \Handle
inH -> do
magicBs <- Handle -> Int -> m ComHash
forall (m :: * -> *). MonadIO m => Handle -> Int -> m ComHash
hGet Handle
inH Int
2
if zlibP magicBs
then do
(`catch` skipCorruptedFile) $ do
headerBs <- (toLazy magicBs <>) . toLazy <$> hGet inH 510
if gitObjectP $ decompress headerBs
then do
!goh <- sha1 . decompress . (headerBs <>) <$> hGetContents inH
pure . Just $! GitObject goh fp
else
pure Nothing
else pure Nothing
where
skipCorruptedFile :: DecompressError -> m (Maybe a)
skipCorruptedFile (DecompressError
_ :: DecompressError) = do
IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ $(trIo "Skip corrupted file/fp")
Maybe a -> m (Maybe a)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe a
forall a. Maybe a
Nothing
zlibNoCompression :: ComHash
zlibNoCompression = ComHash
"\x0078\x0001"
zlibDefaultCompression :: ComHash
zlibDefaultCompression = ComHash
"\x0078\x009C"
zlibBestCompression :: ComHash
zlibBestCompression = ComHash
"\x0078\x00DA"
zlibP :: ComHash -> Bool
zlibP ComHash
bs =
ComHash
zlibNoCompression ComHash -> ComHash -> Bool
forall a. Eq a => a -> a -> Bool
== ComHash
bs Bool -> Bool -> Bool
||
ComHash
zlibDefaultCompression ComHash -> ComHash -> Bool
forall a. Eq a => a -> a -> Bool
== ComHash
bs Bool -> Bool -> Bool
||
ComHash
zlibBestCompression ComHash -> ComHash -> Bool
forall a. Eq a => a -> a -> Bool
== ComHash
bs
findGitObjects :: PhoenixCoCon m => FilePath -> ConduitT i GitObject m ()
findGitObjects :: forall (m :: * -> *) i.
PhoenixCoCon m =>
FilePath -> ConduitT i GitObject m ()
findGitObjects FilePath
photorecOutDir =
Bool -> FilePath -> ConduitT i FilePath m ()
forall (m :: * -> *) i.
MonadResource m =>
Bool -> FilePath -> ConduitT i FilePath m ()
sourceDirectoryDeep Bool
False FilePath
photorecOutDir
ConduitT i FilePath m ()
-> ConduitT FilePath GitObject m () -> ConduitT i GitObject m ()
forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
.| (FilePath -> m (Maybe GitObject))
-> ConduitT FilePath (Maybe GitObject) m ()
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ConduitT a b m ()
mapMC FilePath -> m (Maybe GitObject)
forall (m :: * -> *). PhoenixM m => FilePath -> m (Maybe GitObject)
mkGitObject
ConduitT FilePath (Maybe GitObject) m ()
-> ConduitT (Maybe GitObject) GitObject m ()
-> ConduitT FilePath GitObject m ()
forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
.| ConduitT (Maybe GitObject) (Element (Maybe GitObject)) m ()
ConduitT (Maybe GitObject) GitObject m ()
forall (m :: * -> *) mono.
(Monad m, MonoFoldable mono) =>
ConduitT mono (Element mono) m ()
concatC
alrr :: Monad m => (x -> m y) -> (x, z) -> m z
alrr :: forall (m :: * -> *) x y z. Monad m => (x -> m y) -> (x, z) -> m z
alrr x -> m y
f (x
a, !z
r) = x -> m y
f x
a m y -> m z -> m z
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> z -> m z
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure z
r
replaceSymLinkWithDisambiguate :: MonadUnliftIO m => FilePath -> GitObject -> m ()
replaceSymLinkWithDisambiguate :: forall (m :: * -> *).
MonadUnliftIO m =>
FilePath -> GitObject -> m ()
replaceSymLinkWithDisambiguate FilePath
uberGob GitObject
gob = do
firstGobOrigin <- FilePath -> ByteString
L8.pack (FilePath -> ByteString) -> m FilePath -> m ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> m FilePath
forall (m :: * -> *). MonadIO m => FilePath -> m FilePath
getSymbolicLinkTarget FilePath
uberGob
removeFile uberGob
withBinaryFile uberGob WriteMode $ \Handle
oh ->
Handle -> ByteString -> m ()
forall (m :: * -> *). MonadIO m => Handle -> ByteString -> m ()
hPut Handle
oh (ByteString -> m ())
-> ([ByteString] -> ByteString) -> [ByteString] -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat ([ByteString] -> m ()) -> [ByteString] -> m ()
forall a b. (a -> b) -> a -> b
$ [ ByteString
compressedDisambiguate
, Int64 -> ByteString
forall a. Binary a => a -> ByteString
B.encode (Int64 -> ByteString) -> Int64 -> ByteString
forall a b. (a -> b) -> a -> b
$ ByteString -> Int64
L.length ByteString
firstGobOrigin
, ByteString
firstGobOrigin
, Int64 -> ByteString
forall a. Binary a => a -> ByteString
B.encode (Int64 -> ByteString) -> Int64 -> ByteString
forall a b. (a -> b) -> a -> b
$ ByteString -> Int64
L.length ByteString
gobPacked
, ByteString
gobPacked
]
where
gobPacked :: ByteString
gobPacked = FilePath -> ByteString
L8.pack (FilePath -> ByteString) -> FilePath -> ByteString
forall a b. (a -> b) -> a -> b
$ GitObject -> FilePath
gobOrigin GitObject
gob
appendPathToUberGob :: MonadUnliftIO m => FilePath -> GitObject -> m ()
appendPathToUberGob :: forall (m :: * -> *).
MonadUnliftIO m =>
FilePath -> GitObject -> m ()
appendPathToUberGob FilePath
uberGob GitObject
gob =
FilePath -> IOMode -> (Handle -> m ()) -> m ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
FilePath -> IOMode -> (Handle -> m a) -> m a
withBinaryFile FilePath
uberGob IOMode
AppendMode ((Handle -> m ()) -> m ()) -> (Handle -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \Handle
oh ->
Handle -> ByteString -> m ()
forall (m :: * -> *). MonadIO m => Handle -> ByteString -> m ()
hPut Handle
oh (ByteString -> m ()) -> ByteString -> m ()
forall a b. (a -> b) -> a -> b
$ ByteString
gobLen ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
gobPacked
where
gobPacked :: ByteString
gobPacked = FilePath -> ByteString
L8.pack (FilePath -> ByteString) -> FilePath -> ByteString
forall a b. (a -> b) -> a -> b
$ GitObject -> FilePath
gobOrigin GitObject
gob
gobLen :: ByteString
gobLen = Int64 -> ByteString
forall a. Binary a => a -> ByteString
B.encode (Int64 -> ByteString) -> Int64 -> ByteString
forall a b. (a -> b) -> a -> b
$ ByteString -> Int64
L.length ByteString
gobPacked
storeGitObject :: PhoenixUberM m => (ShaDedupMap, Int, Int) -> GitObject -> m (ShaDedupMap, Int, Int)
storeGitObject :: forall (m :: * -> *).
PhoenixUberM m =>
(ShaDedupMap, Int, Int) -> GitObject -> m (ShaDedupMap, Int, Int)
storeGitObject (ShaDedupMap
dedupMap, !Int
countDown, !Int
mapSize) GitObject
gob = do
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
countDown Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ do
FilePath -> m ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
putStrLn (FilePath -> m ()) -> FilePath -> m ()
forall a b. (a -> b) -> a -> b
$ FilePath
"GIT objects found: " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> FilePath
forall b a. (Show a, IsString b) => a -> b
show Int
mapSize
(,if Int
countDown Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 then Int
10000 else Int
countDown Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1, Int
mapSize Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
(ShaDedupMap -> (ShaDedupMap, Int, Int))
-> m ShaDedupMap -> m (ShaDedupMap, Int, Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Maybe Int -> m ()) -> (Maybe Int, ShaDedupMap) -> m ShaDedupMap
forall (m :: * -> *) x y z. Monad m => (x -> m y) -> (x, z) -> m z
alrr Maybe Int -> m ()
writeGitObject ((Maybe Int, ShaDedupMap) -> m ShaDedupMap)
-> (Maybe Int, ShaDedupMap) -> m ShaDedupMap
forall a b. (a -> b) -> a -> b
$ (ComHash -> Int -> Int -> Int)
-> ComHash -> Int -> ShaDedupMap -> (Maybe Int, ShaDedupMap)
forall k a.
Ord k =>
(k -> a -> a -> a) -> k -> a -> Map k a -> (Maybe a, Map k a)
M.insertLookupWithKey (\ComHash
_h -> Int -> Int -> Int
forall a. Num a => a -> a -> a
(+)) (GitObject -> ComHash
gobHash GitObject
gob) Int
1 ShaDedupMap
dedupMap)
where
gobPath :: FilePath
gobPath = GitObject -> FilePath
gitObjectFilePath GitObject
gob
writeGitObject :: Maybe Int -> m ()
writeGitObject = \case
Maybe Int
Nothing -> do
dod <- (PhoenixUberConf -> FilePath) -> m FilePath
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks ((PhoenixUberConf -> FilePath) -> m FilePath)
-> (PhoenixUberConf -> FilePath) -> m FilePath
forall a b. (a -> b) -> a -> b
$ Tagged OutDir FilePath -> FilePath
forall {k} (s :: k) b. Tagged s b -> b
untag (Tagged OutDir FilePath -> FilePath)
-> (PhoenixUberConf -> Tagged OutDir FilePath)
-> PhoenixUberConf
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PhoenixUberConf -> Tagged OutDir FilePath
destObjectDir
createDirectoryIfMissing False (dod </> dropFileName gobPath)
createFileLink (gobOrigin gob) (dod </> gobPath)
Just Int
_dedupSuffix -> do
dod <- (PhoenixUberConf -> FilePath) -> m FilePath
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks ((PhoenixUberConf -> FilePath) -> m FilePath)
-> (PhoenixUberConf -> FilePath) -> m FilePath
forall a b. (a -> b) -> a -> b
$ Tagged OutDir FilePath -> FilePath
forall {k} (s :: k) b. Tagged s b -> b
untag (Tagged OutDir FilePath -> FilePath)
-> (PhoenixUberConf -> Tagged OutDir FilePath)
-> PhoenixUberConf
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PhoenixUberConf -> Tagged OutDir FilePath
destObjectDir
let uberGob = FilePath
dod FilePath -> ShowS
</> FilePath
gobPath
pathIsSymbolicLink uberGob >>= \case
Bool
True ->
FilePath -> GitObject -> m ()
forall (m :: * -> *).
MonadUnliftIO m =>
FilePath -> GitObject -> m ()
replaceSymLinkWithDisambiguate FilePath
uberGob GitObject
gob
Bool
False ->
FilePath -> GitObject -> m ()
forall (m :: * -> *).
MonadUnliftIO m =>
FilePath -> GitObject -> m ()
appendPathToUberGob FilePath
uberGob GitObject
gob
recoverFrom :: PhoenixUberM m => Tagged InDir FilePath -> m ()
recoverFrom :: forall (m :: * -> *).
PhoenixUberM m =>
Tagged InDir FilePath -> m ()
recoverFrom (Tagged FilePath
photorecOutDir) =
m (Int, [Int]) -> m (Seconds, (Int, [Int]))
forall (m :: * -> *) a. MonadIO m => m a -> m (Seconds, a)
duration (FilePath -> m FilePath
forall (m :: * -> *). MonadIO m => FilePath -> m FilePath
makeAbsolute FilePath
photorecOutDir m FilePath -> (FilePath -> m (Int, [Int])) -> m (Int, [Int])
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FilePath -> m (Int, [Int])
forall {f :: * -> *}.
(MonadUnliftIO f, MonadFail f, HasInHandlesSem f,
MonadReader PhoenixUberConf f) =>
FilePath -> f (Int, [Int])
go) m (Seconds, (Int, [Int]))
-> ((Seconds, (Int, [Int])) -> m ()) -> m ()
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Seconds, (Int, [Int])) -> m ()
reportCollisions
where
go :: FilePath -> f (Int, [Int])
go FilePath
absInDir =
((ShaDedupMap -> Identity [Int])
-> (Int, ShaDedupMap) -> Identity (Int, [Int])
forall s t a b. Field2 s t a b => Lens s t a b
Lens (Int, ShaDedupMap) (Int, [Int]) ShaDedupMap [Int]
_2 ((ShaDedupMap -> Identity [Int])
-> (Int, ShaDedupMap) -> Identity (Int, [Int]))
-> (ShaDedupMap -> [Int]) -> (Int, ShaDedupMap) -> (Int, [Int])
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ ShaDedupMap -> [Int]
forall k a. Map k a -> [a]
M.elems) ((Int, ShaDedupMap) -> (Int, [Int]))
-> ((ShaDedupMap, Int, Int) -> (Int, ShaDedupMap))
-> (ShaDedupMap, Int, Int)
-> (Int, [Int])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\(ShaDedupMap
m, Int
_, Int
objectsStored) -> (Int
objectsStored, ShaDedupMap
m)) ((ShaDedupMap, Int, Int) -> (Int, [Int]))
-> f (ShaDedupMap, Int, Int) -> f (Int, [Int])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ConduitT () Void (ResourceT f) (ShaDedupMap, Int, Int)
-> f (ShaDedupMap, Int, Int)
forall (m :: * -> *) r.
MonadUnliftIO m =>
ConduitT () Void (ResourceT m) r -> m r
runConduitRes
( FilePath -> ConduitT () GitObject (ResourceT f) ()
forall (m :: * -> *) i.
PhoenixCoCon m =>
FilePath -> ConduitT i GitObject m ()
findGitObjects FilePath
absInDir
ConduitT () GitObject (ResourceT f) ()
-> ConduitT GitObject Void (ResourceT f) (ShaDedupMap, Int, Int)
-> ConduitT () Void (ResourceT f) (ShaDedupMap, Int, Int)
forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
.| ((ShaDedupMap, Int, Int)
-> GitObject -> ResourceT f (ShaDedupMap, Int, Int))
-> (ShaDedupMap, Int, Int)
-> ConduitT GitObject Void (ResourceT f) (ShaDedupMap, Int, Int)
forall (m :: * -> *) a b o.
Monad m =>
(a -> b -> m a) -> a -> ConduitT b o m a
foldMC (ShaDedupMap, Int, Int)
-> GitObject -> ResourceT f (ShaDedupMap, Int, Int)
forall (m :: * -> *).
PhoenixUberM m =>
(ShaDedupMap, Int, Int) -> GitObject -> m (ShaDedupMap, Int, Int)
storeGitObject (ShaDedupMap
forall a. Monoid a => a
mempty, Int
10, Int
0)
)
reportCollisions :: (Seconds, (Int, [Int])) -> m ()
reportCollisions = \case
(Seconds
_, (Int
_, [])) ->
FilePath -> m ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
putStrLn (FilePath -> m ()) -> FilePath -> m ()
forall a b. (a -> b) -> a -> b
$ FilePath
"Dir [" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
photorecOutDir FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
"] doesn't have Git files"
(Seconds
durSecs, (Int
objectStored, [Int]
collisions)) -> do
FilePath -> m ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
putStrLn (FilePath -> m ()) -> ShowS -> FilePath -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> ShowS
forall r. PrintfType r => FilePath -> r
printf FilePath
"Duration: %s" (FilePath -> m ()) -> FilePath -> m ()
forall a b. (a -> b) -> a -> b
$ Seconds -> FilePath
showDuration Seconds
durSecs
FilePath -> m ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
putStrLn (FilePath -> m ()) -> (Int -> FilePath) -> Int -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Int -> FilePath
forall r. PrintfType r => FilePath -> r
printf FilePath
"Found: %d" (Int -> m ()) -> Int -> m ()
forall a b. (a -> b) -> a -> b
$ Int
objectStored
FilePath -> m ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
putStrLn (FilePath -> m ()) -> (Seconds -> FilePath) -> Seconds -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Seconds -> FilePath
forall r. PrintfType r => FilePath -> r
printf FilePath
"Speed: %.2f files per second" (Seconds -> m ()) -> Seconds -> m ()
forall a b. (a -> b) -> a -> b
$ Int -> Seconds
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
objectStored Seconds -> Seconds -> Seconds
forall a. Fractional a => a -> a -> a
/ Seconds
durSecs
case [Int] -> Int
forall a. Ord a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
I.maximum [Int]
collisions of
Int
1 -> () -> m ()
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Int
cn -> FilePath -> m ()
forall (m :: * -> *). MonadIO m => FilePath -> m ()
putStrLn (FilePath -> m ()) -> FilePath -> m ()
forall a b. (a -> b) -> a -> b
$ FilePath
"Maximum number of SHA collisions: " FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> FilePath
forall b a. (Show a, IsString b) => a -> b
show Int
cn