2010-10-27 20:53:54 +00:00
|
|
|
|
{- git-annex monad
|
|
|
|
|
-
|
2012-12-30 03:10:18 +00:00
|
|
|
|
- Copyright 2010-2012 Joey Hess <joey@kitenet.net>
|
2010-10-27 20:53:54 +00:00
|
|
|
|
-
|
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
|
-}
|
2010-10-10 19:04:07 +00:00
|
|
|
|
|
2012-10-24 18:43:32 +00:00
|
|
|
|
{-# LANGUAGE PackageImports, GeneralizedNewtypeDeriving, TypeFamilies, MultiParamTypeClasses #-}
|
2011-08-19 18:28:07 +00:00
|
|
|
|
|
2010-10-11 21:52:46 +00:00
|
|
|
|
module Annex (
|
2011-01-26 01:49:04 +00:00
|
|
|
|
Annex,
|
|
|
|
|
AnnexState(..),
|
2012-10-17 20:01:09 +00:00
|
|
|
|
FileInfo(..),
|
2012-10-04 19:48:59 +00:00
|
|
|
|
PreferredContentMap,
|
2010-10-14 07:18:11 +00:00
|
|
|
|
new,
|
2011-10-27 18:38:59 +00:00
|
|
|
|
newState,
|
2010-10-14 07:18:11 +00:00
|
|
|
|
run,
|
2010-11-01 03:24:16 +00:00
|
|
|
|
eval,
|
2012-06-05 01:21:52 +00:00
|
|
|
|
exec,
|
2011-01-26 04:17:38 +00:00
|
|
|
|
getState,
|
|
|
|
|
changeState,
|
more command-specific options
Made --from and --to command-specific options.
Added generic storage for values of command-specific options,
which allows removing some of the special case fields in AnnexState.
(Also added generic storage for command-specific flags, although there are
not yet any.)
Note that this storage uses a Map, so repeatedly looking up the same value
is slightly more expensive than looking up an AnnexState field. But, the
value can be looked up once in the seek stage, transformed as necessary,
and passed in a closure to the start stage, and this avoids that overhead.
Still, I'm hesitant to use this for things like force or fast flags.
It's probably best to reserve it for flags that are only used by a few
commands, or options like --from and --to that it's important only be
allowed to be used with commands that implement them, to avoid user
confusion.
2012-01-06 07:06:25 +00:00
|
|
|
|
setFlag,
|
|
|
|
|
setField,
|
2012-04-30 17:59:05 +00:00
|
|
|
|
setOutput,
|
more command-specific options
Made --from and --to command-specific options.
Added generic storage for values of command-specific options,
which allows removing some of the special case fields in AnnexState.
(Also added generic storage for command-specific flags, although there are
not yet any.)
Note that this storage uses a Map, so repeatedly looking up the same value
is slightly more expensive than looking up an AnnexState field. But, the
value can be looked up once in the seek stage, transformed as necessary,
and passed in a closure to the start stage, and this avoids that overhead.
Still, I'm hesitant to use this for things like force or fast flags.
It's probably best to reserve it for flags that are only used by a few
commands, or options like --from and --to that it's important only be
allowed to be used with commands that implement them, to avoid user
confusion.
2012-01-06 07:06:25 +00:00
|
|
|
|
getFlag,
|
|
|
|
|
getField,
|
2012-02-25 22:02:49 +00:00
|
|
|
|
addCleanup,
|
2011-11-08 19:34:10 +00:00
|
|
|
|
gitRepo,
|
|
|
|
|
inRepo,
|
|
|
|
|
fromRepo,
|
2013-01-01 17:52:47 +00:00
|
|
|
|
getGitConfig,
|
|
|
|
|
changeGitConfig,
|
2012-12-30 03:10:18 +00:00
|
|
|
|
changeGitRepo,
|
2010-10-11 21:52:46 +00:00
|
|
|
|
) where
|
2010-10-10 19:04:07 +00:00
|
|
|
|
|
2012-10-24 18:43:32 +00:00
|
|
|
|
import "mtl" Control.Monad.State.Strict
|
2011-12-06 15:37:58 +00:00
|
|
|
|
import Control.Monad.Trans.Control (StM, MonadBaseControl, liftBaseWith, restoreM)
|
|
|
|
|
import Control.Monad.Base (liftBase, MonadBase)
|
2012-01-20 19:34:52 +00:00
|
|
|
|
import System.Posix.Types (Fd)
|
2010-10-16 20:20:49 +00:00
|
|
|
|
|
2011-10-04 02:24:57 +00:00
|
|
|
|
import Common
|
2011-06-30 17:16:57 +00:00
|
|
|
|
import qualified Git
|
2011-12-13 19:05:07 +00:00
|
|
|
|
import qualified Git.Config
|
2011-09-28 19:15:42 +00:00
|
|
|
|
import Git.CatFile
|
2012-02-14 03:42:44 +00:00
|
|
|
|
import Git.CheckAttr
|
2012-04-21 23:42:49 +00:00
|
|
|
|
import Git.SharedRepository
|
2011-12-20 18:37:53 +00:00
|
|
|
|
import qualified Git.Queue
|
2011-06-02 01:56:04 +00:00
|
|
|
|
import Types.Backend
|
2013-01-01 17:52:47 +00:00
|
|
|
|
import Types.GitConfig
|
2011-09-19 00:11:39 +00:00
|
|
|
|
import qualified Types.Remote
|
2011-06-02 01:56:04 +00:00
|
|
|
|
import Types.Crypto
|
2011-06-22 19:58:30 +00:00
|
|
|
|
import Types.BranchState
|
2011-06-24 01:25:39 +00:00
|
|
|
|
import Types.TrustLevel
|
2012-10-01 19:12:04 +00:00
|
|
|
|
import Types.Group
|
2012-04-27 17:23:52 +00:00
|
|
|
|
import Types.Messages
|
2012-10-04 19:48:59 +00:00
|
|
|
|
import Types.UUID
|
2012-01-30 02:55:06 +00:00
|
|
|
|
import Utility.State
|
2011-09-18 21:47:49 +00:00
|
|
|
|
import qualified Utility.Matcher
|
2011-12-08 20:01:46 +00:00
|
|
|
|
import qualified Data.Map as M
|
2012-10-05 20:52:44 +00:00
|
|
|
|
import qualified Data.Set as S
|
2011-01-26 01:49:04 +00:00
|
|
|
|
|
|
|
|
|
-- git-annex's monad
|
2011-08-19 18:28:07 +00:00
|
|
|
|
newtype Annex a = Annex { runAnnex :: StateT AnnexState IO a }
|
|
|
|
|
deriving (
|
|
|
|
|
Monad,
|
|
|
|
|
MonadIO,
|
2011-08-25 04:28:55 +00:00
|
|
|
|
MonadState AnnexState,
|
|
|
|
|
Functor,
|
|
|
|
|
Applicative
|
2011-08-19 18:28:07 +00:00
|
|
|
|
)
|
2011-01-26 01:49:04 +00:00
|
|
|
|
|
2011-12-06 15:37:58 +00:00
|
|
|
|
instance MonadBase IO Annex where
|
|
|
|
|
liftBase = Annex . liftBase
|
|
|
|
|
|
|
|
|
|
instance MonadBaseControl IO Annex where
|
|
|
|
|
newtype StM Annex a = StAnnex (StM (StateT AnnexState IO) a)
|
|
|
|
|
liftBaseWith f = Annex $ liftBaseWith $ \runInIO ->
|
|
|
|
|
f $ liftM StAnnex . runInIO . runAnnex
|
|
|
|
|
restoreM = Annex . restoreM . unStAnnex
|
2012-10-29 01:27:15 +00:00
|
|
|
|
where
|
|
|
|
|
unStAnnex (StAnnex st) = st
|
2011-01-26 01:49:04 +00:00
|
|
|
|
|
2011-12-31 08:19:10 +00:00
|
|
|
|
type Matcher a = Either [Utility.Matcher.Token a] (Utility.Matcher.Matcher a)
|
|
|
|
|
|
2012-10-17 20:01:09 +00:00
|
|
|
|
data FileInfo = FileInfo
|
|
|
|
|
{ relFile :: FilePath -- may be relative to cwd
|
|
|
|
|
, matchFile :: FilePath -- filepath to match on; may be relative to top
|
|
|
|
|
}
|
|
|
|
|
|
|
|
|
|
type PreferredContentMap = M.Map UUID (Utility.Matcher.Matcher (S.Set UUID -> FileInfo -> Annex Bool))
|
2012-10-04 19:48:59 +00:00
|
|
|
|
|
2011-01-26 01:49:04 +00:00
|
|
|
|
-- internal state storage
|
2011-01-26 04:17:38 +00:00
|
|
|
|
data AnnexState = AnnexState
|
|
|
|
|
{ repo :: Git.Repo
|
2013-01-01 17:52:47 +00:00
|
|
|
|
, gitconfig :: GitConfig
|
2011-12-31 08:11:39 +00:00
|
|
|
|
, backends :: [BackendA Annex]
|
|
|
|
|
, remotes :: [Types.Remote.RemoteA Annex]
|
2012-04-27 17:23:52 +00:00
|
|
|
|
, output :: MessageState
|
2011-01-26 04:17:38 +00:00
|
|
|
|
, force :: Bool
|
2011-03-22 21:41:06 +00:00
|
|
|
|
, fast :: Bool
|
2011-09-15 17:30:04 +00:00
|
|
|
|
, auto :: Bool
|
2011-06-22 19:58:30 +00:00
|
|
|
|
, branchstate :: BranchState
|
2012-02-15 15:13:13 +00:00
|
|
|
|
, repoqueue :: Maybe Git.Queue.Queue
|
2011-09-28 19:15:42 +00:00
|
|
|
|
, catfilehandle :: Maybe CatFileHandle
|
2012-02-14 03:42:44 +00:00
|
|
|
|
, checkattrhandle :: Maybe CheckAttrHandle
|
2011-05-18 23:34:46 +00:00
|
|
|
|
, forcebackend :: Maybe String
|
2012-10-17 20:01:09 +00:00
|
|
|
|
, limit :: Matcher (FileInfo -> Annex Bool)
|
add ConfigMonitor thread
Monitors git-annex branch for changes, which are noticed by the Merger
thread whenever the branch ref is changed (either due to an incoming push,
or a local change), and refreshes cached config values for modified config
files.
Rate limited to run no more often than once per minute. This is important
because frequent git-annex branch changes happen when files are being
added, or transferred, etc.
A primary use case is that, when preferred content changes are made,
and get pushed to remotes, the remotes start honoring those settings.
Other use cases include propigating repository description and trust
changes to remotes, and learning when a remote has added a new special
remote, so the webapp can present the GUI to enable that special remote
locally.
Also added a uuid.log cache. All other config files already had caches.
2012-10-20 20:37:06 +00:00
|
|
|
|
, uuidmap :: Maybe UUIDMap
|
2012-10-04 19:48:59 +00:00
|
|
|
|
, preferredcontentmap :: Maybe PreferredContentMap
|
2012-04-21 23:42:49 +00:00
|
|
|
|
, shared :: Maybe SharedRepository
|
2012-01-10 03:31:44 +00:00
|
|
|
|
, forcetrust :: TrustMap
|
2011-06-24 01:25:39 +00:00
|
|
|
|
, trustmap :: Maybe TrustMap
|
2012-10-01 19:12:04 +00:00
|
|
|
|
, groupmap :: Maybe GroupMap
|
2012-04-29 18:02:18 +00:00
|
|
|
|
, ciphers :: M.Map StorableCipher Cipher
|
2012-01-20 19:34:52 +00:00
|
|
|
|
, lockpool :: M.Map FilePath Fd
|
more command-specific options
Made --from and --to command-specific options.
Added generic storage for values of command-specific options,
which allows removing some of the special case fields in AnnexState.
(Also added generic storage for command-specific flags, although there are
not yet any.)
Note that this storage uses a Map, so repeatedly looking up the same value
is slightly more expensive than looking up an AnnexState field. But, the
value can be looked up once in the seek stage, transformed as necessary,
and passed in a closure to the start stage, and this avoids that overhead.
Still, I'm hesitant to use this for things like force or fast flags.
It's probably best to reserve it for flags that are only used by a few
commands, or options like --from and --to that it's important only be
allowed to be used with commands that implement them, to avoid user
confusion.
2012-01-06 07:06:25 +00:00
|
|
|
|
, flags :: M.Map String Bool
|
|
|
|
|
, fields :: M.Map String String
|
2012-02-25 22:02:49 +00:00
|
|
|
|
, cleanup :: M.Map String (Annex ())
|
2013-02-19 20:26:07 +00:00
|
|
|
|
, inodeschanged :: Maybe Bool
|
2011-04-16 20:41:46 +00:00
|
|
|
|
}
|
2011-01-26 04:17:38 +00:00
|
|
|
|
|
2011-07-05 22:31:46 +00:00
|
|
|
|
newState :: Git.Repo -> AnnexState
|
|
|
|
|
newState gitrepo = AnnexState
|
2011-01-26 04:17:38 +00:00
|
|
|
|
{ repo = gitrepo
|
2013-01-01 17:52:47 +00:00
|
|
|
|
, gitconfig = extractGitConfig gitrepo
|
2011-01-26 04:17:38 +00:00
|
|
|
|
, backends = []
|
2011-03-27 20:17:56 +00:00
|
|
|
|
, remotes = []
|
2012-04-27 17:23:52 +00:00
|
|
|
|
, output = defaultMessageState
|
2011-01-26 04:17:38 +00:00
|
|
|
|
, force = False
|
2011-03-22 21:41:06 +00:00
|
|
|
|
, fast = False
|
2011-09-15 17:30:04 +00:00
|
|
|
|
, auto = False
|
2011-06-22 19:58:30 +00:00
|
|
|
|
, branchstate = startBranchState
|
2012-02-15 15:13:13 +00:00
|
|
|
|
, repoqueue = Nothing
|
2011-09-28 19:15:42 +00:00
|
|
|
|
, catfilehandle = Nothing
|
2012-02-14 03:42:44 +00:00
|
|
|
|
, checkattrhandle = Nothing
|
2011-05-18 23:34:46 +00:00
|
|
|
|
, forcebackend = Nothing
|
2011-09-18 21:47:49 +00:00
|
|
|
|
, limit = Left []
|
add ConfigMonitor thread
Monitors git-annex branch for changes, which are noticed by the Merger
thread whenever the branch ref is changed (either due to an incoming push,
or a local change), and refreshes cached config values for modified config
files.
Rate limited to run no more often than once per minute. This is important
because frequent git-annex branch changes happen when files are being
added, or transferred, etc.
A primary use case is that, when preferred content changes are made,
and get pushed to remotes, the remotes start honoring those settings.
Other use cases include propigating repository description and trust
changes to remotes, and learning when a remote has added a new special
remote, so the webapp can present the GUI to enable that special remote
locally.
Also added a uuid.log cache. All other config files already had caches.
2012-10-20 20:37:06 +00:00
|
|
|
|
, uuidmap = Nothing
|
2012-10-04 19:48:59 +00:00
|
|
|
|
, preferredcontentmap = Nothing
|
2012-04-21 23:42:49 +00:00
|
|
|
|
, shared = Nothing
|
2012-01-10 03:31:44 +00:00
|
|
|
|
, forcetrust = M.empty
|
2011-06-24 01:25:39 +00:00
|
|
|
|
, trustmap = Nothing
|
2012-10-01 19:12:04 +00:00
|
|
|
|
, groupmap = Nothing
|
2011-12-08 20:01:46 +00:00
|
|
|
|
, ciphers = M.empty
|
2012-01-20 19:34:52 +00:00
|
|
|
|
, lockpool = M.empty
|
more command-specific options
Made --from and --to command-specific options.
Added generic storage for values of command-specific options,
which allows removing some of the special case fields in AnnexState.
(Also added generic storage for command-specific flags, although there are
not yet any.)
Note that this storage uses a Map, so repeatedly looking up the same value
is slightly more expensive than looking up an AnnexState field. But, the
value can be looked up once in the seek stage, transformed as necessary,
and passed in a closure to the start stage, and this avoids that overhead.
Still, I'm hesitant to use this for things like force or fast flags.
It's probably best to reserve it for flags that are only used by a few
commands, or options like --from and --to that it's important only be
allowed to be used with commands that implement them, to avoid user
confusion.
2012-01-06 07:06:25 +00:00
|
|
|
|
, flags = M.empty
|
|
|
|
|
, fields = M.empty
|
2012-02-25 22:02:49 +00:00
|
|
|
|
, cleanup = M.empty
|
2013-02-19 20:26:07 +00:00
|
|
|
|
, inodeschanged = Nothing
|
2011-01-26 04:17:38 +00:00
|
|
|
|
}
|
2010-10-14 07:18:11 +00:00
|
|
|
|
|
2012-05-18 22:20:53 +00:00
|
|
|
|
{- Makes an Annex state object for the specified git repo.
|
|
|
|
|
- Ensures the config is read, if it was not already. -}
|
2011-07-05 22:31:46 +00:00
|
|
|
|
new :: Git.Repo -> IO AnnexState
|
2012-06-29 14:00:05 +00:00
|
|
|
|
new = newState <$$> Git.Config.read
|
2010-10-14 07:18:11 +00:00
|
|
|
|
|
2010-10-26 19:59:50 +00:00
|
|
|
|
{- performs an action in the Annex monad -}
|
2011-01-11 22:13:26 +00:00
|
|
|
|
run :: AnnexState -> Annex a -> IO (a, AnnexState)
|
2011-08-19 18:28:07 +00:00
|
|
|
|
run s a = runStateT (runAnnex a) s
|
2011-01-11 22:13:26 +00:00
|
|
|
|
eval :: AnnexState -> Annex a -> IO a
|
2011-08-19 18:28:07 +00:00
|
|
|
|
eval s a = evalStateT (runAnnex a) s
|
2012-06-05 01:21:52 +00:00
|
|
|
|
exec :: AnnexState -> Annex a -> IO AnnexState
|
|
|
|
|
exec s a = execStateT (runAnnex a) s
|
2010-10-14 07:18:11 +00:00
|
|
|
|
|
more command-specific options
Made --from and --to command-specific options.
Added generic storage for values of command-specific options,
which allows removing some of the special case fields in AnnexState.
(Also added generic storage for command-specific flags, although there are
not yet any.)
Note that this storage uses a Map, so repeatedly looking up the same value
is slightly more expensive than looking up an AnnexState field. But, the
value can be looked up once in the seek stage, transformed as necessary,
and passed in a closure to the start stage, and this avoids that overhead.
Still, I'm hesitant to use this for things like force or fast flags.
It's probably best to reserve it for flags that are only used by a few
commands, or options like --from and --to that it's important only be
allowed to be used with commands that implement them, to avoid user
confusion.
2012-01-06 07:06:25 +00:00
|
|
|
|
{- Sets a flag to True -}
|
|
|
|
|
setFlag :: String -> Annex ()
|
|
|
|
|
setFlag flag = changeState $ \s ->
|
2012-02-25 22:02:49 +00:00
|
|
|
|
s { flags = M.insertWith' const flag True $ flags s }
|
more command-specific options
Made --from and --to command-specific options.
Added generic storage for values of command-specific options,
which allows removing some of the special case fields in AnnexState.
(Also added generic storage for command-specific flags, although there are
not yet any.)
Note that this storage uses a Map, so repeatedly looking up the same value
is slightly more expensive than looking up an AnnexState field. But, the
value can be looked up once in the seek stage, transformed as necessary,
and passed in a closure to the start stage, and this avoids that overhead.
Still, I'm hesitant to use this for things like force or fast flags.
It's probably best to reserve it for flags that are only used by a few
commands, or options like --from and --to that it's important only be
allowed to be used with commands that implement them, to avoid user
confusion.
2012-01-06 07:06:25 +00:00
|
|
|
|
|
|
|
|
|
{- Sets a field to a value -}
|
|
|
|
|
setField :: String -> String -> Annex ()
|
|
|
|
|
setField field value = changeState $ \s ->
|
2012-02-25 22:02:49 +00:00
|
|
|
|
s { fields = M.insertWith' const field value $ fields s }
|
|
|
|
|
|
|
|
|
|
{- Adds a cleanup action to perform. -}
|
|
|
|
|
addCleanup :: String -> Annex () -> Annex ()
|
|
|
|
|
addCleanup uid a = changeState $ \s ->
|
|
|
|
|
s { cleanup = M.insertWith' const uid a $ cleanup s }
|
more command-specific options
Made --from and --to command-specific options.
Added generic storage for values of command-specific options,
which allows removing some of the special case fields in AnnexState.
(Also added generic storage for command-specific flags, although there are
not yet any.)
Note that this storage uses a Map, so repeatedly looking up the same value
is slightly more expensive than looking up an AnnexState field. But, the
value can be looked up once in the seek stage, transformed as necessary,
and passed in a closure to the start stage, and this avoids that overhead.
Still, I'm hesitant to use this for things like force or fast flags.
It's probably best to reserve it for flags that are only used by a few
commands, or options like --from and --to that it's important only be
allowed to be used with commands that implement them, to avoid user
confusion.
2012-01-06 07:06:25 +00:00
|
|
|
|
|
2012-04-30 17:59:05 +00:00
|
|
|
|
{- Sets the type of output to emit. -}
|
|
|
|
|
setOutput :: OutputType -> Annex ()
|
|
|
|
|
setOutput o = changeState $ \s ->
|
|
|
|
|
s { output = (output s) { outputType = o } }
|
|
|
|
|
|
more command-specific options
Made --from and --to command-specific options.
Added generic storage for values of command-specific options,
which allows removing some of the special case fields in AnnexState.
(Also added generic storage for command-specific flags, although there are
not yet any.)
Note that this storage uses a Map, so repeatedly looking up the same value
is slightly more expensive than looking up an AnnexState field. But, the
value can be looked up once in the seek stage, transformed as necessary,
and passed in a closure to the start stage, and this avoids that overhead.
Still, I'm hesitant to use this for things like force or fast flags.
It's probably best to reserve it for flags that are only used by a few
commands, or options like --from and --to that it's important only be
allowed to be used with commands that implement them, to avoid user
confusion.
2012-01-06 07:06:25 +00:00
|
|
|
|
{- Checks if a flag was set. -}
|
|
|
|
|
getFlag :: String -> Annex Bool
|
|
|
|
|
getFlag flag = fromMaybe False . M.lookup flag <$> getState flags
|
|
|
|
|
|
|
|
|
|
{- Gets the value of a field. -}
|
|
|
|
|
getField :: String -> Annex (Maybe String)
|
|
|
|
|
getField field = M.lookup field <$> getState fields
|
|
|
|
|
|
2011-11-08 19:34:10 +00:00
|
|
|
|
{- Returns the annex's git repository. -}
|
2010-10-14 07:18:11 +00:00
|
|
|
|
gitRepo :: Annex Git.Repo
|
2011-01-26 01:49:04 +00:00
|
|
|
|
gitRepo = getState repo
|
2011-11-08 19:34:10 +00:00
|
|
|
|
|
|
|
|
|
{- Runs an IO action in the annex's git repository. -}
|
|
|
|
|
inRepo :: (Git.Repo -> IO a) -> Annex a
|
2011-11-12 18:24:07 +00:00
|
|
|
|
inRepo a = liftIO . a =<< gitRepo
|
2011-11-08 19:34:10 +00:00
|
|
|
|
|
|
|
|
|
{- Extracts a value from the annex's git repisitory. -}
|
|
|
|
|
fromRepo :: (Git.Repo -> a) -> Annex a
|
|
|
|
|
fromRepo a = a <$> gitRepo
|
2012-12-30 03:10:18 +00:00
|
|
|
|
|
2013-01-01 17:52:47 +00:00
|
|
|
|
{- Gets the GitConfig settings. -}
|
|
|
|
|
getGitConfig :: Annex GitConfig
|
|
|
|
|
getGitConfig = getState gitconfig
|
2012-12-30 03:10:18 +00:00
|
|
|
|
|
2013-01-01 17:52:47 +00:00
|
|
|
|
{- Modifies a GitConfig setting. -}
|
|
|
|
|
changeGitConfig :: (GitConfig -> GitConfig) -> Annex ()
|
|
|
|
|
changeGitConfig a = changeState $ \s -> s { gitconfig = a (gitconfig s) }
|
2012-12-30 03:10:18 +00:00
|
|
|
|
|
2013-01-01 17:52:47 +00:00
|
|
|
|
{- Changing the git Repo data also involves re-extracting its GitConfig. -}
|
2012-12-30 03:10:18 +00:00
|
|
|
|
changeGitRepo :: Git.Repo -> Annex ()
|
|
|
|
|
changeGitRepo r = changeState $ \s -> s
|
|
|
|
|
{ repo = r
|
2013-01-01 17:52:47 +00:00
|
|
|
|
, gitconfig = extractGitConfig r
|
2012-12-30 03:10:18 +00:00
|
|
|
|
}
|