more OsPath conversion
Finally reached Annex code in this conversion. Sponsored-by: Graham Spencer
This commit is contained in:
parent
51a6cd1ee6
commit
f9d42c37c0
9 changed files with 64 additions and 37 deletions
|
@ -16,6 +16,7 @@ module Utility.FileIO
|
||||||
(
|
(
|
||||||
withFile,
|
withFile,
|
||||||
openFile,
|
openFile,
|
||||||
|
openBinaryFile,
|
||||||
readFile,
|
readFile,
|
||||||
readFile',
|
readFile',
|
||||||
writeFile,
|
writeFile,
|
||||||
|
@ -51,6 +52,11 @@ openFile f m = do
|
||||||
f' <- toOsPath <$> convertToWindowsNativeNamespace (fromOsPath f)
|
f' <- toOsPath <$> convertToWindowsNativeNamespace (fromOsPath f)
|
||||||
O.openFile f' m
|
O.openFile f' m
|
||||||
|
|
||||||
|
openBinaryFile :: OsPath -> IOMode -> IO Handle
|
||||||
|
openBinaryFile f m = do
|
||||||
|
f' <- toOsPath <$> convertToWindowsNativeNamespace (fromOsPath f)
|
||||||
|
O.openBinaryFile f' m
|
||||||
|
|
||||||
readFile :: OsPath -> IO L.ByteString
|
readFile :: OsPath -> IO L.ByteString
|
||||||
readFile f = do
|
readFile f = do
|
||||||
f' <- toOsPath <$> convertToWindowsNativeNamespace (fromOsPath f)
|
f' <- toOsPath <$> convertToWindowsNativeNamespace (fromOsPath f)
|
||||||
|
@ -104,6 +110,9 @@ withFile = System.IO.withFile . fromRawFilePath
|
||||||
openFile :: OsPath -> IOMode -> IO Handle
|
openFile :: OsPath -> IOMode -> IO Handle
|
||||||
openFile = System.IO.openFile . fromRawFilePath
|
openFile = System.IO.openFile . fromRawFilePath
|
||||||
|
|
||||||
|
openBinaryFile :: OsPath -> IOMode -> IO Handle
|
||||||
|
openBinaryFile = System.IO.openBinaryFile . fromRawFilePath
|
||||||
|
|
||||||
readFile :: OsPath -> IO L.ByteString
|
readFile :: OsPath -> IO L.ByteString
|
||||||
readFile = L.readFile . fromRawFilePath
|
readFile = L.readFile . fromRawFilePath
|
||||||
|
|
||||||
|
|
|
@ -24,6 +24,7 @@ import System.PosixCompat.Files (fileSize)
|
||||||
#endif
|
#endif
|
||||||
import System.PosixCompat.Files (FileStatus)
|
import System.PosixCompat.Files (FileStatus)
|
||||||
import qualified Utility.RawFilePath as R
|
import qualified Utility.RawFilePath as R
|
||||||
|
import Utility.OsPath
|
||||||
|
|
||||||
type FileSize = Integer
|
type FileSize = Integer
|
||||||
|
|
||||||
|
@ -33,18 +34,18 @@ type FileSize = Integer
|
||||||
- FileOffset which maxes out at 2 gb.
|
- FileOffset which maxes out at 2 gb.
|
||||||
- See https://github.com/jystic/unix-compat/issues/16
|
- See https://github.com/jystic/unix-compat/issues/16
|
||||||
-}
|
-}
|
||||||
getFileSize :: R.RawFilePath -> IO FileSize
|
getFileSize :: OsPath -> IO FileSize
|
||||||
#ifndef mingw32_HOST_OS
|
#ifndef mingw32_HOST_OS
|
||||||
getFileSize f = fmap (fromIntegral . fileSize) (R.getFileStatus f)
|
getFileSize f = fmap (fromIntegral . fileSize) (R.getFileStatus (fromOsPath f))
|
||||||
#else
|
#else
|
||||||
getFileSize f = bracket (F.openFile (toOsPath f) ReadMode) hClose hFileSize
|
getFileSize f = bracket (F.openFile f ReadMode) hClose hFileSize
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
{- Gets the size of the file, when its FileStatus is already known.
|
{- Gets the size of the file, when its FileStatus is already known.
|
||||||
-
|
-
|
||||||
- On windows, uses getFileSize. Otherwise, the FileStatus contains the
|
- On windows, uses getFileSize. Otherwise, the FileStatus contains the
|
||||||
- size, so this does not do any work. -}
|
- size, so this does not do any work. -}
|
||||||
getFileSize' :: R.RawFilePath -> FileStatus -> IO FileSize
|
getFileSize' :: OsPath -> FileStatus -> IO FileSize
|
||||||
#ifndef mingw32_HOST_OS
|
#ifndef mingw32_HOST_OS
|
||||||
getFileSize' _ s = return $ fromIntegral $ fileSize s
|
getFileSize' _ s = return $ fromIntegral $ fileSize s
|
||||||
#else
|
#else
|
||||||
|
|
|
@ -182,7 +182,7 @@ feedRead cmd params passphrase feeder reader = do
|
||||||
withTmpFile (toOsPath "gpg") $ \tmpfile h -> do
|
withTmpFile (toOsPath "gpg") $ \tmpfile h -> do
|
||||||
liftIO $ B.hPutStr h passphrase
|
liftIO $ B.hPutStr h passphrase
|
||||||
liftIO $ hClose h
|
liftIO $ hClose h
|
||||||
let passphrasefile = [Param "--passphrase-file", File (fromRawFilePath (fromOsPath tmpfile))]
|
let passphrasefile = [Param "--passphrase-file", File (fromOsPath tmpfile)]
|
||||||
go $ passphrasefile ++ params
|
go $ passphrasefile ++ params
|
||||||
#endif
|
#endif
|
||||||
where
|
where
|
||||||
|
@ -441,7 +441,7 @@ testHarness tmpdir cmd a = ifM (inSearchPath (unGpgCmd cmd))
|
||||||
go Nothing = return Nothing
|
go Nothing = return Nothing
|
||||||
|
|
||||||
makenewdir n = do
|
makenewdir n = do
|
||||||
let subdir = tmpdir </> show n
|
let subdir = toOsPath tmpdir </> toOsPath (show n)
|
||||||
catchIOErrorType AlreadyExists (const $ makenewdir $ n + 1) $ do
|
catchIOErrorType AlreadyExists (const $ makenewdir $ n + 1) $ do
|
||||||
createDirectory subdir
|
createDirectory subdir
|
||||||
return subdir
|
return subdir
|
||||||
|
|
|
@ -49,6 +49,7 @@ import Common
|
||||||
import Utility.TimeStamp
|
import Utility.TimeStamp
|
||||||
import Utility.QuickCheck
|
import Utility.QuickCheck
|
||||||
import qualified Utility.RawFilePath as R
|
import qualified Utility.RawFilePath as R
|
||||||
|
import qualified Utility.FileIO as F
|
||||||
|
|
||||||
import System.PosixCompat.Types
|
import System.PosixCompat.Types
|
||||||
import System.PosixCompat.Files (isRegularFile, fileID)
|
import System.PosixCompat.Files (isRegularFile, fileID)
|
||||||
|
@ -189,20 +190,20 @@ readInodeCache s = case words s of
|
||||||
return $ InodeCache $ InodeCachePrim i sz (MTimeHighRes t)
|
return $ InodeCache $ InodeCachePrim i sz (MTimeHighRes t)
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
|
|
||||||
genInodeCache :: RawFilePath -> TSDelta -> IO (Maybe InodeCache)
|
genInodeCache :: OsPath -> TSDelta -> IO (Maybe InodeCache)
|
||||||
genInodeCache f delta = catchDefaultIO Nothing $
|
genInodeCache f delta = catchDefaultIO Nothing $
|
||||||
toInodeCache delta f =<< R.getSymbolicLinkStatus f
|
toInodeCache delta f =<< R.getSymbolicLinkStatus (fromOsPath f)
|
||||||
|
|
||||||
toInodeCache :: TSDelta -> RawFilePath -> FileStatus -> IO (Maybe InodeCache)
|
toInodeCache :: TSDelta -> OsPath -> FileStatus -> IO (Maybe InodeCache)
|
||||||
toInodeCache d f s = toInodeCache' d f s (fileID s)
|
toInodeCache d f s = toInodeCache' d f s (fileID s)
|
||||||
|
|
||||||
toInodeCache' :: TSDelta -> RawFilePath -> FileStatus -> FileID -> IO (Maybe InodeCache)
|
toInodeCache' :: TSDelta -> OsPath -> FileStatus -> FileID -> IO (Maybe InodeCache)
|
||||||
toInodeCache' (TSDelta getdelta) f s inode
|
toInodeCache' (TSDelta getdelta) f s inode
|
||||||
| isRegularFile s = do
|
| isRegularFile s = do
|
||||||
delta <- getdelta
|
delta <- getdelta
|
||||||
sz <- getFileSize' f s
|
sz <- getFileSize' f s
|
||||||
#ifdef mingw32_HOST_OS
|
#ifdef mingw32_HOST_OS
|
||||||
mtime <- utcTimeToPOSIXSeconds <$> getModificationTime (fromRawFilePath f)
|
mtime <- utcTimeToPOSIXSeconds <$> getModificationTime f
|
||||||
#else
|
#else
|
||||||
let mtime = Posix.modificationTimeHiRes s
|
let mtime = Posix.modificationTimeHiRes s
|
||||||
#endif
|
#endif
|
||||||
|
@ -214,8 +215,8 @@ toInodeCache' (TSDelta getdelta) f s inode
|
||||||
- Its InodeCache at the time of its creation is written to the cache file,
|
- Its InodeCache at the time of its creation is written to the cache file,
|
||||||
- so changes can later be detected. -}
|
- so changes can later be detected. -}
|
||||||
data SentinalFile = SentinalFile
|
data SentinalFile = SentinalFile
|
||||||
{ sentinalFile :: RawFilePath
|
{ sentinalFile :: OsPath
|
||||||
, sentinalCacheFile :: RawFilePath
|
, sentinalCacheFile :: OsPath
|
||||||
}
|
}
|
||||||
deriving (Show)
|
deriving (Show)
|
||||||
|
|
||||||
|
@ -232,8 +233,8 @@ noTSDelta = TSDelta (pure 0)
|
||||||
|
|
||||||
writeSentinalFile :: SentinalFile -> IO ()
|
writeSentinalFile :: SentinalFile -> IO ()
|
||||||
writeSentinalFile s = do
|
writeSentinalFile s = do
|
||||||
writeFile (fromRawFilePath (sentinalFile s)) ""
|
F.writeFile' (sentinalFile s) mempty
|
||||||
maybe noop (writeFile (fromRawFilePath (sentinalCacheFile s)) . showInodeCache)
|
maybe noop (writeFile (fromOsPath (sentinalCacheFile s)) . showInodeCache)
|
||||||
=<< genInodeCache (sentinalFile s) noTSDelta
|
=<< genInodeCache (sentinalFile s) noTSDelta
|
||||||
|
|
||||||
data SentinalStatus = SentinalStatus
|
data SentinalStatus = SentinalStatus
|
||||||
|
@ -262,7 +263,7 @@ checkSentinalFile s = do
|
||||||
Just new -> return $ calc old new
|
Just new -> return $ calc old new
|
||||||
where
|
where
|
||||||
loadoldcache = catchDefaultIO Nothing $
|
loadoldcache = catchDefaultIO Nothing $
|
||||||
readInodeCache <$> readFile (fromRawFilePath (sentinalCacheFile s))
|
readInodeCache <$> readFile (fromOsPath (sentinalCacheFile s))
|
||||||
gennewcache = genInodeCache (sentinalFile s) noTSDelta
|
gennewcache = genInodeCache (sentinalFile s) noTSDelta
|
||||||
calc (InodeCache (InodeCachePrim oldinode oldsize oldmtime)) (InodeCache (InodeCachePrim newinode newsize newmtime)) =
|
calc (InodeCache (InodeCachePrim oldinode oldsize oldmtime)) (InodeCache (InodeCachePrim newinode newsize newmtime)) =
|
||||||
SentinalStatus (not unchanged) tsdelta
|
SentinalStatus (not unchanged) tsdelta
|
||||||
|
@ -287,7 +288,7 @@ checkSentinalFile s = do
|
||||||
dummy = SentinalStatus True noTSDelta
|
dummy = SentinalStatus True noTSDelta
|
||||||
|
|
||||||
sentinalFileExists :: SentinalFile -> IO Bool
|
sentinalFileExists :: SentinalFile -> IO Bool
|
||||||
sentinalFileExists s = allM R.doesPathExist [sentinalCacheFile s, sentinalFile s]
|
sentinalFileExists s = allM doesPathExist [sentinalCacheFile s, sentinalFile s]
|
||||||
|
|
||||||
instance Arbitrary InodeCache where
|
instance Arbitrary InodeCache where
|
||||||
arbitrary =
|
arbitrary =
|
||||||
|
|
|
@ -35,7 +35,7 @@ rotateLog logfile = go 0
|
||||||
where
|
where
|
||||||
go num
|
go num
|
||||||
| num > maxLogs = return ()
|
| num > maxLogs = return ()
|
||||||
| otherwise = whenM (doesFileExist currfile) $ do
|
| otherwise = whenM (doesFileExist (toOsPath currfile)) $ do
|
||||||
go (num + 1)
|
go (num + 1)
|
||||||
rename (toRawFilePath currfile) (toRawFilePath nextfile)
|
rename (toRawFilePath currfile) (toRawFilePath nextfile)
|
||||||
where
|
where
|
||||||
|
@ -50,7 +50,7 @@ rotatedLog logfile n = logfile ++ "." ++ show n
|
||||||
|
|
||||||
{- Lists most recent logs last. -}
|
{- Lists most recent logs last. -}
|
||||||
listLogs :: FilePath -> IO [FilePath]
|
listLogs :: FilePath -> IO [FilePath]
|
||||||
listLogs logfile = filterM doesFileExist $ reverse $
|
listLogs logfile = filterM (doesFileExist . toOsPath) $ reverse $
|
||||||
logfile : map (rotatedLog logfile) [1..maxLogs]
|
logfile : map (rotatedLog logfile) [1..maxLogs]
|
||||||
|
|
||||||
maxLogs :: Int
|
maxLogs :: Int
|
||||||
|
|
|
@ -15,6 +15,7 @@ module Utility.Lsof (
|
||||||
import Common
|
import Common
|
||||||
import BuildInfo
|
import BuildInfo
|
||||||
import Utility.Env.Set
|
import Utility.Env.Set
|
||||||
|
import qualified Utility.OsString as OS
|
||||||
|
|
||||||
import System.Posix.Types
|
import System.Posix.Types
|
||||||
|
|
||||||
|
@ -30,12 +31,14 @@ data ProcessInfo = ProcessInfo ProcessID CmdLine
|
||||||
- path where the program was found. Make sure at runtime that lsof is
|
- path where the program was found. Make sure at runtime that lsof is
|
||||||
- available, and if it's not in PATH, adjust PATH to contain it. -}
|
- available, and if it's not in PATH, adjust PATH to contain it. -}
|
||||||
setup :: IO ()
|
setup :: IO ()
|
||||||
setup = do
|
setup = when (isAbsolute cmd) $ do
|
||||||
let cmd = fromMaybe "lsof" BuildInfo.lsof
|
|
||||||
when (isAbsolute cmd) $ do
|
|
||||||
path <- getSearchPath
|
path <- getSearchPath
|
||||||
let path' = takeDirectory cmd : path
|
let path' = fromOsPath $ OS.intercalate sep $
|
||||||
setEnv "PATH" (intercalate [searchPathSeparator] path') True
|
takeDirectory cmd : path
|
||||||
|
setEnv "PATH" path' True
|
||||||
|
where
|
||||||
|
cmd = toOsPath $ fromMaybe "lsof" BuildInfo.lsof
|
||||||
|
sep = OS.singleton searchPathSeparator
|
||||||
|
|
||||||
{- Checks each of the files in a directory to find open files.
|
{- Checks each of the files in a directory to find open files.
|
||||||
- Note that this will find hard links to files elsewhere that are open. -}
|
- Note that this will find hard links to files elsewhere that are open. -}
|
||||||
|
|
|
@ -227,7 +227,7 @@ defaultChunkSize = 32 * k - chunkOverhead
|
||||||
-}
|
-}
|
||||||
watchFileSize
|
watchFileSize
|
||||||
:: (MonadIO m, MonadMask m)
|
:: (MonadIO m, MonadMask m)
|
||||||
=> RawFilePath
|
=> OsPath
|
||||||
-> MeterUpdate
|
-> MeterUpdate
|
||||||
-> (MeterUpdate -> m a)
|
-> (MeterUpdate -> m a)
|
||||||
-> m a
|
-> m a
|
||||||
|
|
|
@ -50,6 +50,7 @@ import Utility.IPAddress
|
||||||
import qualified Utility.RawFilePath as R
|
import qualified Utility.RawFilePath as R
|
||||||
import Utility.Hash (IncrementalVerifier(..))
|
import Utility.Hash (IncrementalVerifier(..))
|
||||||
import Utility.Url.Parse
|
import Utility.Url.Parse
|
||||||
|
import qualified Utility.FileIO as F
|
||||||
|
|
||||||
import Network.URI
|
import Network.URI
|
||||||
import Network.HTTP.Types
|
import Network.HTTP.Types
|
||||||
|
@ -311,8 +312,8 @@ getUrlInfo url uo = case parseURIRelaxed url of
|
||||||
=<< curlRestrictedParams r u defport (basecurlparams url')
|
=<< curlRestrictedParams r u defport (basecurlparams url')
|
||||||
|
|
||||||
existsfile u = do
|
existsfile u = do
|
||||||
let f = toRawFilePath (unEscapeString (uriPath u))
|
let f = toOsPath (unEscapeString (uriPath u))
|
||||||
s <- catchMaybeIO $ R.getSymbolicLinkStatus f
|
s <- catchMaybeIO $ R.getSymbolicLinkStatus (fromOsPath f)
|
||||||
case s of
|
case s of
|
||||||
Just stat -> do
|
Just stat -> do
|
||||||
sz <- getFileSize' f stat
|
sz <- getFileSize' f stat
|
||||||
|
@ -362,10 +363,10 @@ headRequest r = r
|
||||||
-
|
-
|
||||||
- When the download fails, returns an error message.
|
- When the download fails, returns an error message.
|
||||||
-}
|
-}
|
||||||
download :: MeterUpdate -> Maybe IncrementalVerifier -> URLString -> FilePath -> UrlOptions -> IO (Either String ())
|
download :: MeterUpdate -> Maybe IncrementalVerifier -> URLString -> OsPath -> UrlOptions -> IO (Either String ())
|
||||||
download = download' False
|
download = download' False
|
||||||
|
|
||||||
download' :: Bool -> MeterUpdate -> Maybe IncrementalVerifier -> URLString -> FilePath -> UrlOptions -> IO (Either String ())
|
download' :: Bool -> MeterUpdate -> Maybe IncrementalVerifier -> URLString -> OsPath -> UrlOptions -> IO (Either String ())
|
||||||
download' nocurlerror meterupdate iv url file uo =
|
download' nocurlerror meterupdate iv url file uo =
|
||||||
catchJust matchHttpException go showhttpexception
|
catchJust matchHttpException go showhttpexception
|
||||||
`catchNonAsync` (dlfailed . show)
|
`catchNonAsync` (dlfailed . show)
|
||||||
|
@ -421,8 +422,8 @@ download' nocurlerror meterupdate iv url file uo =
|
||||||
-- curl does not create destination file
|
-- curl does not create destination file
|
||||||
-- if the url happens to be empty, so pre-create.
|
-- if the url happens to be empty, so pre-create.
|
||||||
unlessM (doesFileExist file) $
|
unlessM (doesFileExist file) $
|
||||||
writeFile file ""
|
F.writeFile file mempty
|
||||||
ifM (boolSystem "curl" (curlparams ++ [Param "-o", File file, File rawurl]))
|
ifM (boolSystem "curl" (curlparams ++ [Param "-o", File (fromOsPath file), File rawurl]))
|
||||||
( return $ Right ()
|
( return $ Right ()
|
||||||
, return $ Left "download failed"
|
, return $ Left "download failed"
|
||||||
)
|
)
|
||||||
|
@ -434,7 +435,7 @@ download' nocurlerror meterupdate iv url file uo =
|
||||||
noverification
|
noverification
|
||||||
let src = unEscapeString (uriPath u)
|
let src = unEscapeString (uriPath u)
|
||||||
withMeteredFile src meterupdate $
|
withMeteredFile src meterupdate $
|
||||||
L.writeFile file
|
F.writeFile file
|
||||||
return $ Right ()
|
return $ Right ()
|
||||||
|
|
||||||
-- Conduit does not support ftp, so will throw an exception on a
|
-- Conduit does not support ftp, so will throw an exception on a
|
||||||
|
@ -461,9 +462,9 @@ download' nocurlerror meterupdate iv url file uo =
|
||||||
- thrown for reasons other than http status codes will still be thrown
|
- thrown for reasons other than http status codes will still be thrown
|
||||||
- as usual.)
|
- as usual.)
|
||||||
-}
|
-}
|
||||||
downloadConduit :: MeterUpdate -> Maybe IncrementalVerifier -> Request -> FilePath -> UrlOptions -> IO ()
|
downloadConduit :: MeterUpdate -> Maybe IncrementalVerifier -> Request -> OsPath -> UrlOptions -> IO ()
|
||||||
downloadConduit meterupdate iv req file uo =
|
downloadConduit meterupdate iv req file uo =
|
||||||
catchMaybeIO (getFileSize (toRawFilePath file)) >>= \case
|
catchMaybeIO (getFileSize file) >>= \case
|
||||||
Just sz | sz > 0 -> resumedownload sz
|
Just sz | sz > 0 -> resumedownload sz
|
||||||
_ -> join $ runResourceT $ do
|
_ -> join $ runResourceT $ do
|
||||||
liftIO $ debug "Utility.Url" (show req')
|
liftIO $ debug "Utility.Url" (show req')
|
||||||
|
@ -566,7 +567,7 @@ sinkResponseFile
|
||||||
=> MeterUpdate
|
=> MeterUpdate
|
||||||
-> Maybe IncrementalVerifier
|
-> Maybe IncrementalVerifier
|
||||||
-> BytesProcessed
|
-> BytesProcessed
|
||||||
-> FilePath
|
-> OsPath
|
||||||
-> IOMode
|
-> IOMode
|
||||||
-> Response (ConduitM () B8.ByteString m ())
|
-> Response (ConduitM () B8.ByteString m ())
|
||||||
-> m ()
|
-> m ()
|
||||||
|
@ -577,7 +578,7 @@ sinkResponseFile meterupdate iv initialp file mode resp = do
|
||||||
return (const noop)
|
return (const noop)
|
||||||
(Just iv', _) -> return (updateIncrementalVerifier iv')
|
(Just iv', _) -> return (updateIncrementalVerifier iv')
|
||||||
(Nothing, _) -> return (const noop)
|
(Nothing, _) -> return (const noop)
|
||||||
(fr, fh) <- allocate (openBinaryFile file mode) hClose
|
(fr, fh) <- allocate (F.openBinaryFile file mode) hClose
|
||||||
runConduit $ responseBody resp .| go ui initialp fh
|
runConduit $ responseBody resp .| go ui initialp fh
|
||||||
release fr
|
release fr
|
||||||
where
|
where
|
||||||
|
|
|
@ -26,6 +26,18 @@ status.
|
||||||
Make Utility.SystemDirectory import it when built with OsPath,
|
Make Utility.SystemDirectory import it when built with OsPath,
|
||||||
and the remaining 6 hours or work will explain itself..
|
and the remaining 6 hours or work will explain itself..
|
||||||
This has been started in the `ospath` branch.
|
This has been started in the `ospath` branch.
|
||||||
|
* As part of the OsPath conversion, Git.LsFiles has several
|
||||||
|
`pipeNullSplit'` calls that have toOsPath mapped over the results.
|
||||||
|
That adds an additional copy, so the lazy ByteString is converted to strict,
|
||||||
|
and then to ShortByteString, with a copy each time. This is in the
|
||||||
|
critical path for large git repos, and might be a noticable slowdown.
|
||||||
|
There is currently no easy way to go direct from a lazy ByteString to a
|
||||||
|
ShortByteString, although it would certianly be possible to write low
|
||||||
|
level code to do it efficiently. Alternatively, it would be possible to
|
||||||
|
read a strict ByteString direct from a handle, like hGetLine does
|
||||||
|
(although in this case it would need to stop at the terminating 0 byte)
|
||||||
|
and unsafePerformIO to stream to a list would avoid needing to rewrite
|
||||||
|
this code to not use a list.
|
||||||
|
|
||||||
[[!tag confirmed]]
|
[[!tag confirmed]]
|
||||||
|
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue