From 3ee44cf8feb11fc439c02eb0eb8f12d290b01120 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 22 Jun 2012 13:04:03 -0400 Subject: [PATCH 001/331] add assistant command like watch, but more magic --- Assistant.hs | 6 +++--- Command/Assistant.hs | 18 ++++++++++++++++++ Command/Watch.hs | 18 +++++++++--------- GitAnnex.hs | 2 ++ doc/git-annex.mdwn | 4 ++++ 5 files changed, 36 insertions(+), 12 deletions(-) create mode 100644 Command/Assistant.hs diff --git a/Assistant.hs b/Assistant.hs index e924d94777..33c7cef36c 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -55,10 +55,10 @@ import Utility.LogFile import Control.Concurrent -startDaemon :: Bool -> Annex () -startDaemon foreground +startDaemon :: Bool -> Bool -> Annex () +startDaemon assistant foreground | foreground = do - showStart "watch" "." + showStart (if assistant then "assistant" else "watch") "." go id | otherwise = do logfd <- liftIO . openLog =<< fromRepo gitAnnexLogFile diff --git a/Command/Assistant.hs b/Command/Assistant.hs new file mode 100644 index 0000000000..60eac5d219 --- /dev/null +++ b/Command/Assistant.hs @@ -0,0 +1,18 @@ +{- git-annex assistant + - + - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Command.Assistant where + +import Command +import qualified Command.Watch + +def :: [Command] +def = [withOptions [Command.Watch.foregroundOption, Command.Watch.stopOption] $ + command "assistant" paramNothing seek "automatically handle changes"] + +seek :: [CommandSeek] +seek = Command.Watch.mkSeek True diff --git a/Command/Watch.hs b/Command/Watch.hs index 5681b38619..744844c4dc 100644 --- a/Command/Watch.hs +++ b/Command/Watch.hs @@ -1,6 +1,3 @@ -{-# LANGUAGE CPP #-} -{-# LANGUAGE BangPatterns #-} - {- git-annex watch command - - Copyright 2012 Joey Hess @@ -19,10 +16,13 @@ def :: [Command] def = [withOptions [foregroundOption, stopOption] $ command "watch" paramNothing seek "watch for changes"] -seek :: [CommandSeek] -seek = [withFlag stopOption $ \stopdaemon -> +mkSeek :: Bool -> [CommandSeek] +mkSeek assistant = [withFlag stopOption $ \stopdaemon -> withFlag foregroundOption $ \foreground -> - withNothing $ start foreground stopdaemon] + withNothing $ start assistant foreground stopdaemon] + +seek :: [CommandSeek] +seek = mkSeek False foregroundOption :: Option foregroundOption = Option.flag [] "foreground" "do not daemonize" @@ -30,9 +30,9 @@ foregroundOption = Option.flag [] "foreground" "do not daemonize" stopOption :: Option stopOption = Option.flag [] "stop" "stop daemon" -start :: Bool -> Bool -> CommandStart -start foreground stopdaemon = notBareRepo $ do +start :: Bool -> Bool -> Bool -> CommandStart +start assistant foreground stopdaemon = notBareRepo $ do if stopdaemon then stopDaemon - else startDaemon foreground -- does not return + else startDaemon assistant foreground -- does not return stop diff --git a/GitAnnex.hs b/GitAnnex.hs index a4c5eb8490..ee451352f4 100644 --- a/GitAnnex.hs +++ b/GitAnnex.hs @@ -59,6 +59,7 @@ import qualified Command.Map import qualified Command.Upgrade import qualified Command.Version import qualified Command.Watch +import qualified Command.Assistant cmds :: [Command] cmds = concat @@ -101,6 +102,7 @@ cmds = concat , Command.Upgrade.def , Command.Version.def , Command.Watch.def + , Command.Assistant.def ] options :: [Option] diff --git a/doc/git-annex.mdwn b/doc/git-annex.mdwn index 39fad04882..965a07f0d7 100644 --- a/doc/git-annex.mdwn +++ b/doc/git-annex.mdwn @@ -180,6 +180,10 @@ subdirectories). To not daemonize, run with --foreground ; to stop a running daemon, run with --stop +* assistant + + Like watch, but also automatically syncs changes to other remotes. + # REPOSITORY SETUP COMMANDS * init [description] From 28e28bc0436cb0a33e570b1a1f678e80a770a21a Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 22 Jun 2012 13:39:44 -0400 Subject: [PATCH 002/331] stub syncer thread and commit channel --- Assistant.hs | 17 +++++++++-------- Assistant/Changes.hs | 25 +++++++++--------------- Assistant/Commits.hs | 32 +++++++++++++++++++++++++++++++ Assistant/Committer.hs | 6 ++++-- Assistant/Syncer.hs | 29 ++++++++++++++++++++++++++++ Assistant/ThreadedMonad.hs | 3 ++- Assistant/Watcher.hs | 4 +--- Utility/TSet.hs | 39 ++++++++++++++++++++++++++++++++++++++ 8 files changed, 125 insertions(+), 30 deletions(-) create mode 100644 Assistant/Commits.hs create mode 100644 Assistant/Syncer.hs create mode 100644 Utility/TSet.hs diff --git a/Assistant.hs b/Assistant.hs index 33c7cef36c..5a3fa5a9d4 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -22,9 +22,11 @@ - Thread 5: committer - Waits for changes to occur, and runs the git queue to update its - index, then commits. - - Thread 6: status logger + - Thread 6: syncer + - Waits for commits to be made, and syncs the git repo to remotes. + - Thread 7: status logger - Wakes up periodically and records the daemon's status to disk. - - Thread 7: sanity checker + - Thread 8: sanity checker - Wakes up periodically (rarely) and does sanity checks. - - ThreadState: (MVar) @@ -47,8 +49,10 @@ import Common.Annex import Assistant.ThreadedMonad import Assistant.DaemonStatus import Assistant.Changes +import Assistant.Commits import Assistant.Watcher import Assistant.Committer +import Assistant.Syncer import Assistant.SanityChecker import qualified Utility.Daemon import Utility.LogFile @@ -70,12 +74,9 @@ startDaemon assistant foreground dstatus <- startDaemonStatus liftIO $ a $ do changechan <- newChangeChan - -- The commit thread is started early, - -- so that the user can immediately - -- begin adding files and having them - -- committed, even while the startup scan - -- is taking place. - _ <- forkIO $ commitThread st changechan + commitchan <- newCommitChan + _ <- forkIO $ commitThread st changechan commitchan + _ <- forkIO $ syncThread st commitchan _ <- forkIO $ daemonStatusThread st dstatus _ <- forkIO $ sanityCheckerThread st dstatus changechan -- Does not return. diff --git a/Assistant/Changes.hs b/Assistant/Changes.hs index 173ba19220..47eae83ef6 100644 --- a/Assistant/Changes.hs +++ b/Assistant/Changes.hs @@ -8,14 +8,14 @@ module Assistant.Changes where import Common.Annex import qualified Annex.Queue import Types.KeySource +import Utility.TSet -import Control.Concurrent.STM import Data.Time.Clock data ChangeType = AddChange | LinkChange | RmChange | RmDirChange deriving (Show, Eq) -type ChangeChan = TChan Change +type ChangeChan = TSet Change data Change = Change @@ -29,11 +29,8 @@ data Change } deriving (Show) -runChangeChan :: STM a -> IO a -runChangeChan = atomically - newChangeChan :: IO ChangeChan -newChangeChan = atomically newTChan +newChangeChan = newTSet {- Handlers call this when they made a change that needs to get committed. -} madeChange :: FilePath -> ChangeType -> Annex (Maybe Change) @@ -65,17 +62,13 @@ finishedChange c = c {- Gets all unhandled changes. - Blocks until at least one change is made. -} getChanges :: ChangeChan -> IO [Change] -getChanges chan = runChangeChan $ do - c <- readTChan chan - go [c] - where - go l = do - v <- tryReadTChan chan - case v of - Nothing -> return l - Just c -> go (c:l) +getChanges = getTSet {- Puts unhandled changes back into the channel. - Note: Original order is not preserved. -} refillChanges :: ChangeChan -> [Change] -> IO () -refillChanges chan cs = runChangeChan $ mapM_ (writeTChan chan) cs +refillChanges = putTSet + +{- Records a change in the channel. -} +recordChange :: ChangeChan -> Change -> IO () +recordChange = putTSet1 diff --git a/Assistant/Commits.hs b/Assistant/Commits.hs new file mode 100644 index 0000000000..152544e7ce --- /dev/null +++ b/Assistant/Commits.hs @@ -0,0 +1,32 @@ +{- git-annex assistant commit tracking + - + - Copyright 2012 Joey Hess + -} + +module Assistant.Commits where + +import Utility.TSet + +import Data.Time.Clock + +type CommitChan = TSet Commit + +data Commit = Commit UTCTime + deriving (Show) + +newCommitChan :: IO CommitChan +newCommitChan = newTSet + +{- Gets all unhandled commits. + - Blocks until at least one commit is made. -} +getCommits :: CommitChan -> IO [Commit] +getCommits = getTSet + +{- Puts unhandled commits back into the channel. + - Note: Original order is not preserved. -} +refillCommits :: CommitChan -> [Commit] -> IO () +refillCommits = putTSet + +{- Records a commit in the channel. -} +recordCommit :: CommitChan -> Commit -> IO () +recordCommit = putTSet1 diff --git a/Assistant/Committer.hs b/Assistant/Committer.hs index 63df8cafcc..acdee1408d 100644 --- a/Assistant/Committer.hs +++ b/Assistant/Committer.hs @@ -7,6 +7,7 @@ module Assistant.Committer where import Common.Annex import Assistant.Changes +import Assistant.Commits import Assistant.ThreadedMonad import Assistant.Watcher import qualified Annex @@ -26,8 +27,8 @@ import qualified Data.Set as S import Data.Either {- This thread makes git commits at appropriate times. -} -commitThread :: ThreadState -> ChangeChan -> IO () -commitThread st changechan = runEvery (Seconds 1) $ do +commitThread :: ThreadState -> ChangeChan -> CommitChan -> IO () +commitThread st changechan commitchan = runEvery (Seconds 1) $ do -- We already waited one second as a simple rate limiter. -- Next, wait until at least one change is available for -- processing. @@ -40,6 +41,7 @@ commitThread st changechan = runEvery (Seconds 1) $ do if shouldCommit time readychanges then do void $ tryIO $ runThreadState st commitStaged + recordCommit commitchan (Commit time) else refillChanges changechan readychanges else refillChanges changechan changes diff --git a/Assistant/Syncer.hs b/Assistant/Syncer.hs new file mode 100644 index 0000000000..059859c073 --- /dev/null +++ b/Assistant/Syncer.hs @@ -0,0 +1,29 @@ +{- git-annex assistant git syncing thread + - + - Copyright 2012 Joey Hess + -} + +module Assistant.Syncer where + +import Assistant.Commits +import Assistant.ThreadedMonad +import qualified Command.Sync +import Utility.ThreadScheduler + +{- This thread syncs git commits out to remotes. -} +syncThread :: ThreadState -> CommitChan -> IO () +syncThread st commitchan = runEvery (Seconds 2) $ do + -- We already waited two seconds as a simple rate limiter. + -- Next, wait until at least one commit has been made + commits <- getCommits commitchan + -- Now see if now's a good time to sync. + if shouldSync commits + then syncToRemotes + else refillCommits commitchan commits + +{- Decide if now is a good time to sync commits to remotes. -} +shouldSync :: [Commit] -> Bool +shouldSync commits = not (null commits) + +syncToRemotes :: IO () +syncToRemotes = return () -- TOOD diff --git a/Assistant/ThreadedMonad.hs b/Assistant/ThreadedMonad.hs index 51f579d07f..91a311deeb 100644 --- a/Assistant/ThreadedMonad.hs +++ b/Assistant/ThreadedMonad.hs @@ -32,7 +32,8 @@ withThreadState a = do {- Runs an Annex action, using the state from the MVar. - - - This serializes calls by threads. -} + - This serializes calls by threads; only one thread can run in Annex at a + - time. -} runThreadState :: ThreadState -> Annex a -> IO a runThreadState mvar a = do startstate <- takeMVar mvar diff --git a/Assistant/Watcher.hs b/Assistant/Watcher.hs index db58f01e8b..78330c8d0a 100644 --- a/Assistant/Watcher.hs +++ b/Assistant/Watcher.hs @@ -27,7 +27,6 @@ import Annex.Content import Annex.CatFile import Git.Types -import Control.Concurrent.STM import Data.Bits.Utils import qualified Data.ByteString.Lazy as L @@ -96,8 +95,7 @@ runHandler st dstatus changechan handler file filestatus = void $ do case r of Left e -> print e Right Nothing -> noop - Right (Just change) -> void $ - runChangeChan $ writeTChan changechan change + Right (Just change) -> recordChange changechan change where go = runThreadState st $ handler file filestatus dstatus diff --git a/Utility/TSet.hs b/Utility/TSet.hs new file mode 100644 index 0000000000..24d345477c --- /dev/null +++ b/Utility/TSet.hs @@ -0,0 +1,39 @@ +{- Transactional sets + - + - Copyright 2012 Joey Hess + -} + +module Utility.TSet where + +import Common + +import Control.Concurrent.STM + +type TSet = TChan + +runTSet :: STM a -> IO a +runTSet = atomically + +newTSet :: IO (TSet a) +newTSet = atomically newTChan + +{- Gets the contents of the TSet. Blocks until at least one item is + - present. -} +getTSet :: TSet a -> IO [a] +getTSet tset = runTSet $ do + c <- readTChan tset + go [c] + where + go l = do + v <- tryReadTChan tset + case v of + Nothing -> return l + Just c -> go (c:l) + +{- Puts items into a TSet. -} +putTSet :: TSet a -> [a] -> IO () +putTSet tset vs = runTSet $ mapM_ (writeTChan tset) vs + +{- Put a single item into a TSet. -} +putTSet1 :: TSet a -> a -> IO () +putTSet1 tset v = void $ runTSet $ writeTChan tset v From e9630e90decac4fe0c999af88131bd4b7c9d979f Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 22 Jun 2012 15:46:21 -0400 Subject: [PATCH 003/331] the syncer now pushes out changes to remotes, in parallel Note that, since this always pushes branch synced/master to the remote, it assumes that master has already gotten all the commits that are on the remote merged in. Otherwise, fast-forward prevention may prevent the push. That's probably ok, because the next stage is to automatically detect incoming pushes and merge. --- Assistant/Syncer.hs | 64 ++++++++++++++++++++++++++++++-------- Command/Sync.hs | 43 ++++++++++++++++--------- Utility/Parallel.hs | 20 ++++++++++++ Utility/ThreadScheduler.hs | 6 ++++ 4 files changed, 105 insertions(+), 28 deletions(-) create mode 100644 Utility/Parallel.hs diff --git a/Assistant/Syncer.hs b/Assistant/Syncer.hs index 059859c073..c579c1c280 100644 --- a/Assistant/Syncer.hs +++ b/Assistant/Syncer.hs @@ -5,25 +5,63 @@ module Assistant.Syncer where +import Common.Annex import Assistant.Commits import Assistant.ThreadedMonad import qualified Command.Sync import Utility.ThreadScheduler +import Utility.Parallel + +import Data.Time.Clock + +data FailedSync = FailedSync + { failedRemote :: Remote + , failedTimeStamp :: UTCTime + } {- This thread syncs git commits out to remotes. -} syncThread :: ThreadState -> CommitChan -> IO () -syncThread st commitchan = runEvery (Seconds 2) $ do - -- We already waited two seconds as a simple rate limiter. - -- Next, wait until at least one commit has been made - commits <- getCommits commitchan - -- Now see if now's a good time to sync. - if shouldSync commits - then syncToRemotes - else refillCommits commitchan commits +syncThread st commitchan = do + remotes <- runThreadState st $ Command.Sync.syncRemotes [] + runEveryWith (Seconds 2) [] $ \failedsyncs -> do + -- We already waited two seconds as a simple rate limiter. + -- Next, wait until at least one commit has been made + commits <- getCommits commitchan + -- Now see if now's a good time to sync. + time <- getCurrentTime + if shouldSync time commits failedsyncs + then syncToRemotes time st remotes + else do + refillCommits commitchan commits + return failedsyncs -{- Decide if now is a good time to sync commits to remotes. -} -shouldSync :: [Commit] -> Bool -shouldSync commits = not (null commits) +{- Decide if now is a good time to sync to remotes. + - + - Current strategy: Immediately sync all commits. The commit machinery + - already determines batches of changes, so we can't easily determine + - batches better. + - + - TODO: FailedSyncs are only retried the next time there's a commit. + - Should retry them periodically, or when a remote that was not available + - becomes available. + -} +shouldSync :: UTCTime -> [Commit] -> [FailedSync] -> Bool +shouldSync _now commits _failedremotes + | not (null commits) = True + | otherwise = False -syncToRemotes :: IO () -syncToRemotes = return () -- TOOD +{- Updates the local sync branch, then pushes it to all remotes, in + - parallel. + - + - Avoids running possibly long-duration commands in the Annex monad, so + - as not to block other threads. -} +syncToRemotes :: UTCTime -> ThreadState -> [Remote] -> IO [FailedSync] +syncToRemotes now st remotes = do + (g, branch) <- runThreadState st $ + (,) <$> fromRepo id <*> Command.Sync.currentBranch + Command.Sync.updateBranch (Command.Sync.syncBranch branch) g + map (`FailedSync` now) <$> inParallel (go g branch) remotes + where + go g branch remote = + ifM (Command.Sync.pushBranch remote branch g) + ( exitSuccess, exitFailure) diff --git a/Command/Sync.hs b/Command/Sync.hs index 5fb49d30c5..110cf2a6c7 100644 --- a/Command/Sync.hs +++ b/Command/Sync.hs @@ -31,7 +31,7 @@ def = [command "sync" (paramOptional (paramRepeating paramRemote)) -- syncing involves several operations, any of which can independently fail seek :: CommandSeek seek rs = do - !branch <- fromMaybe nobranch <$> inRepo Git.Branch.current + branch <- currentBranch remotes <- syncRemotes rs return $ concat [ [ commit ] @@ -41,6 +41,11 @@ seek rs = do , [ pushLocal branch ] , [ pushRemote remote branch | remote <- remotes ] ] + +currentBranch :: Annex Git.Ref +currentBranch = do + !branch <- fromMaybe nobranch <$> inRepo Git.Branch.current + return branch where nobranch = error "no branch is checked out" @@ -90,7 +95,7 @@ mergeLocal branch = go =<< needmerge syncbranch = syncBranch branch needmerge = do unlessM (inRepo $ Git.Ref.exists syncbranch) $ - updateBranch syncbranch + inRepo $ updateBranch syncbranch inRepo $ Git.Branch.changed branch syncbranch go False = stop go True = do @@ -99,17 +104,17 @@ mergeLocal branch = go =<< needmerge pushLocal :: Git.Ref -> CommandStart pushLocal branch = do - updateBranch $ syncBranch branch + inRepo $ updateBranch $ syncBranch branch stop -updateBranch :: Git.Ref -> Annex () -updateBranch syncbranch = +updateBranch :: Git.Ref -> Git.Repo -> IO () +updateBranch syncbranch g = unlessM go $ error $ "failed to update " ++ show syncbranch where - go = inRepo $ Git.Command.runBool "branch" + go = Git.Command.runBool "branch" [ Param "-f" , Param $ show $ Git.Ref.base syncbranch - ] + ] g pullRemote :: Remote -> Git.Ref -> CommandStart pullRemote remote branch = do @@ -135,19 +140,27 @@ mergeRemote remote branch = all id <$> (mapM merge =<< tomerge) pushRemote :: Remote -> Git.Ref -> CommandStart pushRemote remote branch = go =<< needpush where - needpush = anyM (newer remote) [syncbranch, Annex.Branch.name] + needpush = anyM (newer remote) [syncBranch branch, Annex.Branch.name] go False = stop go True = do showStart "push" (Remote.name remote) next $ next $ do showOutput - inRepo $ Git.Command.runBool "push" - [ Param (Remote.name remote) - , Param (show Annex.Branch.name) - , Param refspec - ] - refspec = show (Git.Ref.base branch) ++ ":" ++ show (Git.Ref.base syncbranch) - syncbranch = syncBranch branch + inRepo $ pushBranch remote branch + +pushBranch :: Remote -> Git.Ref -> Git.Repo -> IO Bool +pushBranch remote branch g = + Git.Command.runBool "push" + [ Param (Remote.name remote) + , Param (show Annex.Branch.name) + , Param refspec + ] g + where + refspec = concat + [ show $ Git.Ref.base branch + , ":" + , show $ Git.Ref.base $ syncBranch branch + ] mergeAnnex :: CommandStart mergeAnnex = do diff --git a/Utility/Parallel.hs b/Utility/Parallel.hs new file mode 100644 index 0000000000..a512a6d306 --- /dev/null +++ b/Utility/Parallel.hs @@ -0,0 +1,20 @@ +{- parallel processes + - + - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Utility.Parallel where + +import Common + +{- Runs an action in parallel with a set of values. + - Returns values that caused the action to fail. -} +inParallel :: (v -> IO ()) -> [v] -> IO [v] +inParallel a v = do + pids <- mapM (forkProcess . a) v + statuses <- mapM (getProcessStatus True False) pids + return $ map fst $ filter failed $ zip v statuses + where + failed (_, status) = status /= Just (Exited ExitSuccess) diff --git a/Utility/ThreadScheduler.hs b/Utility/ThreadScheduler.hs index 6557398fd7..07a7401600 100644 --- a/Utility/ThreadScheduler.hs +++ b/Utility/ThreadScheduler.hs @@ -24,6 +24,12 @@ runEvery n a = forever $ do threadDelaySeconds n a +runEveryWith :: Seconds -> a -> (a -> IO a) -> IO () +runEveryWith n val a = do + threadDelaySeconds n + val' <- a val + runEveryWith n val' a + threadDelaySeconds :: Seconds -> IO () threadDelaySeconds (Seconds n) = unboundDelay (fromIntegral n * oneSecond) where From e699ce18417729abbb9606f6a011628ad6616a64 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 22 Jun 2012 17:01:08 -0400 Subject: [PATCH 004/331] added a merger thread Wow! I can create a file in repo a, and it instantly* shows up in repo b! * under 1 second anyway --- Assistant.hs | 23 +++++++--- Assistant/Merger.hs | 72 ++++++++++++++++++++++++++++++ Assistant/{Syncer.hs => Pusher.hs} | 40 ++++++++--------- Utility/Types/DirWatcher.hs | 3 ++ 4 files changed, 112 insertions(+), 26 deletions(-) create mode 100644 Assistant/Merger.hs rename Assistant/{Syncer.hs => Pusher.hs} (58%) diff --git a/Assistant.hs b/Assistant.hs index 5a3fa5a9d4..ce230533cf 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -22,11 +22,17 @@ - Thread 5: committer - Waits for changes to occur, and runs the git queue to update its - index, then commits. - - Thread 6: syncer - - Waits for commits to be made, and syncs the git repo to remotes. - - Thread 7: status logger + - Thread 6: pusher + - Waits for commits to be made, and pushes updated branches to remotes, + - in parallel. (Forks a process for each git push.) + - Thread 7: merger + - Waits for pushes to be received from remotes, and merges the + - updated branches into the current branch. This uses inotify + - on .git/refs/heads, so there are additional inotify threads + - associated with it, too. + - Thread 8: status logger - Wakes up periodically and records the daemon's status to disk. - - Thread 8: sanity checker + - Thread 9: sanity checker - Wakes up periodically (rarely) and does sanity checks. - - ThreadState: (MVar) @@ -41,6 +47,9 @@ - ChangeChan: (STM TChan) - Changes are indicated by writing to this channel. The committer - reads from it. + - CommitChan: (STM TChan) + - Commits are indicated by writing to this channel. The pusher reads + - from it. -} module Assistant where @@ -52,7 +61,8 @@ import Assistant.Changes import Assistant.Commits import Assistant.Watcher import Assistant.Committer -import Assistant.Syncer +import Assistant.Pusher +import Assistant.Merger import Assistant.SanityChecker import qualified Utility.Daemon import Utility.LogFile @@ -76,7 +86,8 @@ startDaemon assistant foreground changechan <- newChangeChan commitchan <- newCommitChan _ <- forkIO $ commitThread st changechan commitchan - _ <- forkIO $ syncThread st commitchan + _ <- forkIO $ pushThread st commitchan + _ <- forkIO $ mergeThread st _ <- forkIO $ daemonStatusThread st dstatus _ <- forkIO $ sanityCheckerThread st dstatus changechan -- Does not return. diff --git a/Assistant/Merger.hs b/Assistant/Merger.hs new file mode 100644 index 0000000000..660636842b --- /dev/null +++ b/Assistant/Merger.hs @@ -0,0 +1,72 @@ +{- git-annex assistant git merge thread + - + - Copyright 2012 Joey Hess + -} + +module Assistant.Merger where + +import Common.Annex +import Assistant.ThreadedMonad +import Utility.DirWatcher +import Utility.Types.DirWatcher +import qualified Git +import qualified Git.Command +import qualified Git.Branch +import qualified Command.Sync + +{- This thread watches for changes to .git/refs/heads/synced/*, + - which indicate incoming pushes. It merges those pushes into the + - currently checked out branch. -} +mergeThread :: ThreadState -> IO () +mergeThread st = do + g <- runThreadState st $ fromRepo id + let dir = Git.localGitDir g "refs" "heads" "synced" + createDirectoryIfMissing True dir + let hook a = Just $ runHandler g a + let hooks = mkWatchHooks + { addHook = hook onAdd + , errHook = hook onErr + } + watchDir dir (const False) hooks id + where + +type Handler = Git.Repo -> FilePath -> Maybe FileStatus -> IO () + +{- Runs an action handler. + - + - Exceptions are ignored, otherwise a whole thread could be crashed. + -} +runHandler :: Git.Repo -> Handler -> FilePath -> Maybe FileStatus -> IO () +runHandler g handler file filestatus = void $ do + either print (const noop) =<< tryIO go + where + go = handler g file filestatus + +{- Called when there's an error with inotify. -} +onErr :: Handler +onErr _ msg _ = error msg + +{- Called when a new branch ref is written. + - + - This relies on git's atomic method of updating branch ref files, + - which is to first write the new file to .lock, and then rename it + - over the old file. So, ignore .lock files, and the rename ensures + - the watcher sees a new file being added on each update. + - + - At startup, synthetic add events fire, causing this to run, but that's + - ok; it ensures that any changes pushed since the last time the assistant + - ran are merged in. + -} +onAdd :: Handler +onAdd g file _ + | ".lock" `isSuffixOf` file = noop + | otherwise = do + let branch = Git.Ref $ "refs" "heads" takeFileName file + current <- Git.Branch.current g + print (branch, current) + when (Just branch == current) $ + void $ mergeBranch branch g + +mergeBranch :: Git.Ref -> Git.Repo -> IO Bool +mergeBranch branch = Git.Command.runBool "merge" + [Param $ show $ Command.Sync.syncBranch branch] diff --git a/Assistant/Syncer.hs b/Assistant/Pusher.hs similarity index 58% rename from Assistant/Syncer.hs rename to Assistant/Pusher.hs index c579c1c280..119575b92a 100644 --- a/Assistant/Syncer.hs +++ b/Assistant/Pusher.hs @@ -1,9 +1,9 @@ -{- git-annex assistant git syncing thread +{- git-annex assistant git pushing thread - - Copyright 2012 Joey Hess -} -module Assistant.Syncer where +module Assistant.Pusher where import Common.Annex import Assistant.Commits @@ -14,39 +14,39 @@ import Utility.Parallel import Data.Time.Clock -data FailedSync = FailedSync +data FailedPush = FailedPush { failedRemote :: Remote , failedTimeStamp :: UTCTime } -{- This thread syncs git commits out to remotes. -} -syncThread :: ThreadState -> CommitChan -> IO () -syncThread st commitchan = do +{- This thread pushes git commits out to remotes. -} +pushThread :: ThreadState -> CommitChan -> IO () +pushThread st commitchan = do remotes <- runThreadState st $ Command.Sync.syncRemotes [] - runEveryWith (Seconds 2) [] $ \failedsyncs -> do + runEveryWith (Seconds 2) [] $ \failedpushes -> do -- We already waited two seconds as a simple rate limiter. -- Next, wait until at least one commit has been made commits <- getCommits commitchan - -- Now see if now's a good time to sync. + -- Now see if now's a good time to push. time <- getCurrentTime - if shouldSync time commits failedsyncs - then syncToRemotes time st remotes + if shouldPush time commits failedpushes + then pushToRemotes time st remotes else do refillCommits commitchan commits - return failedsyncs + return failedpushes -{- Decide if now is a good time to sync to remotes. +{- Decide if now is a good time to push to remotes. - - - Current strategy: Immediately sync all commits. The commit machinery + - Current strategy: Immediately push all commits. The commit machinery - already determines batches of changes, so we can't easily determine - batches better. - - - TODO: FailedSyncs are only retried the next time there's a commit. + - TODO: FailedPushs are only retried the next time there's a commit. - Should retry them periodically, or when a remote that was not available - becomes available. -} -shouldSync :: UTCTime -> [Commit] -> [FailedSync] -> Bool -shouldSync _now commits _failedremotes +shouldPush :: UTCTime -> [Commit] -> [FailedPush] -> Bool +shouldPush _now commits _failedremotes | not (null commits) = True | otherwise = False @@ -55,13 +55,13 @@ shouldSync _now commits _failedremotes - - Avoids running possibly long-duration commands in the Annex monad, so - as not to block other threads. -} -syncToRemotes :: UTCTime -> ThreadState -> [Remote] -> IO [FailedSync] -syncToRemotes now st remotes = do +pushToRemotes :: UTCTime -> ThreadState -> [Remote] -> IO [FailedPush] +pushToRemotes now st remotes = do (g, branch) <- runThreadState st $ (,) <$> fromRepo id <*> Command.Sync.currentBranch Command.Sync.updateBranch (Command.Sync.syncBranch branch) g - map (`FailedSync` now) <$> inParallel (go g branch) remotes + map (`FailedPush` now) <$> inParallel (push g branch) remotes where - go g branch remote = + push g branch remote = ifM (Command.Sync.pushBranch remote branch g) ( exitSuccess, exitFailure) diff --git a/Utility/Types/DirWatcher.hs b/Utility/Types/DirWatcher.hs index c828a05938..ba7eae6a16 100644 --- a/Utility/Types/DirWatcher.hs +++ b/Utility/Types/DirWatcher.hs @@ -20,3 +20,6 @@ data WatchHooks = WatchHooks , delDirHook :: Hook FilePath , errHook :: Hook String -- error message } + +mkWatchHooks :: WatchHooks +mkWatchHooks = WatchHooks Nothing Nothing Nothing Nothing Nothing From 38df4ed44f8deaba50b509a36814e59cf0388425 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sat, 23 Jun 2012 01:20:40 -0400 Subject: [PATCH 005/331] license --- Assistant/Changes.hs | 2 ++ Assistant/Commits.hs | 2 ++ Assistant/Committer.hs | 2 ++ Assistant/DaemonStatus.hs | 2 ++ Assistant/Merger.hs | 2 ++ Assistant/Pusher.hs | 2 ++ Assistant/SanityChecker.hs | 2 ++ Assistant/ThreadedMonad.hs | 2 ++ 8 files changed, 16 insertions(+) diff --git a/Assistant/Changes.hs b/Assistant/Changes.hs index 47eae83ef6..eca922109d 100644 --- a/Assistant/Changes.hs +++ b/Assistant/Changes.hs @@ -1,6 +1,8 @@ {- git-annex assistant change tracking - - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. -} module Assistant.Changes where diff --git a/Assistant/Commits.hs b/Assistant/Commits.hs index 152544e7ce..86fd7599fd 100644 --- a/Assistant/Commits.hs +++ b/Assistant/Commits.hs @@ -1,6 +1,8 @@ {- git-annex assistant commit tracking - - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. -} module Assistant.Commits where diff --git a/Assistant/Committer.hs b/Assistant/Committer.hs index acdee1408d..0c69995912 100644 --- a/Assistant/Committer.hs +++ b/Assistant/Committer.hs @@ -1,6 +1,8 @@ {- git-annex assistant commit thread - - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. -} module Assistant.Committer where diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs index e5ba3d1512..c7713e7d56 100644 --- a/Assistant/DaemonStatus.hs +++ b/Assistant/DaemonStatus.hs @@ -1,6 +1,8 @@ {- git-annex assistant daemon status - - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. -} module Assistant.DaemonStatus where diff --git a/Assistant/Merger.hs b/Assistant/Merger.hs index 660636842b..48cf02ae59 100644 --- a/Assistant/Merger.hs +++ b/Assistant/Merger.hs @@ -1,6 +1,8 @@ {- git-annex assistant git merge thread - - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. -} module Assistant.Merger where diff --git a/Assistant/Pusher.hs b/Assistant/Pusher.hs index 119575b92a..7504d44c20 100644 --- a/Assistant/Pusher.hs +++ b/Assistant/Pusher.hs @@ -1,6 +1,8 @@ {- git-annex assistant git pushing thread - - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. -} module Assistant.Pusher where diff --git a/Assistant/SanityChecker.hs b/Assistant/SanityChecker.hs index e2ca9da740..b74c9fe5d2 100644 --- a/Assistant/SanityChecker.hs +++ b/Assistant/SanityChecker.hs @@ -1,6 +1,8 @@ {- git-annex assistant sanity checker - - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. -} module Assistant.SanityChecker ( diff --git a/Assistant/ThreadedMonad.hs b/Assistant/ThreadedMonad.hs index 91a311deeb..6d3d25778e 100644 --- a/Assistant/ThreadedMonad.hs +++ b/Assistant/ThreadedMonad.hs @@ -1,6 +1,8 @@ {- making the Annex monad available across threads - - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. -} {-# LANGUAGE BangPatterns #-} From a71e7161fc4aad9ec5dfbce219d9d25703a9e3a6 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sat, 23 Jun 2012 01:33:10 -0400 Subject: [PATCH 006/331] golfing --- Utility/Parallel.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/Utility/Parallel.hs b/Utility/Parallel.hs index a512a6d306..6e4671c057 100644 --- a/Utility/Parallel.hs +++ b/Utility/Parallel.hs @@ -12,9 +12,9 @@ import Common {- Runs an action in parallel with a set of values. - Returns values that caused the action to fail. -} inParallel :: (v -> IO ()) -> [v] -> IO [v] -inParallel a v = do - pids <- mapM (forkProcess . a) v +inParallel a l = do + pids <- mapM (forkProcess . a) l statuses <- mapM (getProcessStatus True False) pids - return $ map fst $ filter failed $ zip v statuses + return $ map fst $ filter (failed . snd) $ zip l statuses where - failed (_, status) = status /= Just (Exited ExitSuccess) + failed v = v /= Just (Exited ExitSuccess) From d707f2dce5c3ed1a56c7bf3d65be7bef105f5dd1 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sat, 23 Jun 2012 01:35:40 -0400 Subject: [PATCH 007/331] cleanup --- Assistant/Merger.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/Assistant/Merger.hs b/Assistant/Merger.hs index 48cf02ae59..fbdf9ca015 100644 --- a/Assistant/Merger.hs +++ b/Assistant/Merger.hs @@ -65,7 +65,6 @@ onAdd g file _ | otherwise = do let branch = Git.Ref $ "refs" "heads" takeFileName file current <- Git.Branch.current g - print (branch, current) when (Just branch == current) $ void $ mergeBranch branch g From 19eee6a1df2a6c724e6d6dbe842b40dc1c17f65b Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sat, 23 Jun 2012 10:29:46 -0400 Subject: [PATCH 008/331] noninteractive merge --- Assistant/Merger.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/Assistant/Merger.hs b/Assistant/Merger.hs index fbdf9ca015..988cbd8a63 100644 --- a/Assistant/Merger.hs +++ b/Assistant/Merger.hs @@ -12,7 +12,7 @@ import Assistant.ThreadedMonad import Utility.DirWatcher import Utility.Types.DirWatcher import qualified Git -import qualified Git.Command +import qualified Git.Merge import qualified Git.Branch import qualified Command.Sync @@ -69,5 +69,4 @@ onAdd g file _ void $ mergeBranch branch g mergeBranch :: Git.Ref -> Git.Repo -> IO Bool -mergeBranch branch = Git.Command.runBool "merge" - [Param $ show $ Command.Sync.syncBranch branch] +mergeBranch = Git.Merge.mergeNonInteractive . Command.Sync.syncBranch From 0b146f9ecc36545478c4a2218981b376828c61db Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Mon, 25 Jun 2012 16:10:10 -0400 Subject: [PATCH 009/331] reorg threads --- Assistant.hs | 10 +++++----- Assistant/{ => Threads}/Committer.hs | 4 ++-- Assistant/{ => Threads}/Merger.hs | 2 +- Assistant/{ => Threads}/Pusher.hs | 2 +- Assistant/{ => Threads}/SanityChecker.hs | 8 ++++---- Assistant/{ => Threads}/Watcher.hs | 2 +- 6 files changed, 14 insertions(+), 14 deletions(-) rename Assistant/{ => Threads}/Committer.hs (98%) rename Assistant/{ => Threads}/Merger.hs (98%) rename Assistant/{ => Threads}/Pusher.hs (98%) rename Assistant/{ => Threads}/SanityChecker.hs (93%) rename Assistant/{ => Threads}/Watcher.hs (99%) diff --git a/Assistant.hs b/Assistant.hs index ce230533cf..ec46894a5b 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -59,11 +59,11 @@ import Assistant.ThreadedMonad import Assistant.DaemonStatus import Assistant.Changes import Assistant.Commits -import Assistant.Watcher -import Assistant.Committer -import Assistant.Pusher -import Assistant.Merger -import Assistant.SanityChecker +import Assistant.Threads.Watcher +import Assistant.Threads.Committer +import Assistant.Threads.Pusher +import Assistant.Threads.Merger +import Assistant.Threads.SanityChecker import qualified Utility.Daemon import Utility.LogFile diff --git a/Assistant/Committer.hs b/Assistant/Threads/Committer.hs similarity index 98% rename from Assistant/Committer.hs rename to Assistant/Threads/Committer.hs index 0c69995912..488056fa2b 100644 --- a/Assistant/Committer.hs +++ b/Assistant/Threads/Committer.hs @@ -5,13 +5,13 @@ - Licensed under the GNU GPL version 3 or higher. -} -module Assistant.Committer where +module Assistant.Threads.Committer where import Common.Annex import Assistant.Changes import Assistant.Commits import Assistant.ThreadedMonad -import Assistant.Watcher +import Assistant.Threads.Watcher import qualified Annex import qualified Annex.Queue import qualified Git.Command diff --git a/Assistant/Merger.hs b/Assistant/Threads/Merger.hs similarity index 98% rename from Assistant/Merger.hs rename to Assistant/Threads/Merger.hs index 988cbd8a63..d2c8b9b766 100644 --- a/Assistant/Merger.hs +++ b/Assistant/Threads/Merger.hs @@ -5,7 +5,7 @@ - Licensed under the GNU GPL version 3 or higher. -} -module Assistant.Merger where +module Assistant.Threads.Merger where import Common.Annex import Assistant.ThreadedMonad diff --git a/Assistant/Pusher.hs b/Assistant/Threads/Pusher.hs similarity index 98% rename from Assistant/Pusher.hs rename to Assistant/Threads/Pusher.hs index 7504d44c20..de90d4e64c 100644 --- a/Assistant/Pusher.hs +++ b/Assistant/Threads/Pusher.hs @@ -5,7 +5,7 @@ - Licensed under the GNU GPL version 3 or higher. -} -module Assistant.Pusher where +module Assistant.Threads.Pusher where import Common.Annex import Assistant.Commits diff --git a/Assistant/SanityChecker.hs b/Assistant/Threads/SanityChecker.hs similarity index 93% rename from Assistant/SanityChecker.hs rename to Assistant/Threads/SanityChecker.hs index b74c9fe5d2..4db2a61b22 100644 --- a/Assistant/SanityChecker.hs +++ b/Assistant/Threads/SanityChecker.hs @@ -5,7 +5,7 @@ - Licensed under the GNU GPL version 3 or higher. -} -module Assistant.SanityChecker ( +module Assistant.Threads.SanityChecker ( sanityCheckerThread ) where @@ -15,7 +15,7 @@ import Assistant.DaemonStatus import Assistant.ThreadedMonad import Assistant.Changes import Utility.ThreadScheduler -import qualified Assistant.Watcher +import qualified Assistant.Threads.Watcher as Watcher import Data.Time.Clock.POSIX @@ -79,5 +79,5 @@ check st status changechan = do insanity m = runThreadState st $ warning m addsymlink file s = do insanity $ "found unstaged symlink: " ++ file - Assistant.Watcher.runHandler st status changechan - Assistant.Watcher.onAddSymlink file s + Watcher.runHandler st status changechan + Watcher.onAddSymlink file s diff --git a/Assistant/Watcher.hs b/Assistant/Threads/Watcher.hs similarity index 99% rename from Assistant/Watcher.hs rename to Assistant/Threads/Watcher.hs index 78330c8d0a..1b6ec15f18 100644 --- a/Assistant/Watcher.hs +++ b/Assistant/Threads/Watcher.hs @@ -7,7 +7,7 @@ {-# LANGUAGE CPP #-} -module Assistant.Watcher where +module Assistant.Threads.Watcher where import Common.Annex import Assistant.ThreadedMonad From 5cfe91f06d5eaab217f1b289810d96fee0144c31 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Mon, 25 Jun 2012 16:38:12 -0400 Subject: [PATCH 010/331] add a push retry thread --- Assistant.hs | 14 +++++--- Assistant/Pushes.hs | 36 +++++++++++++++++++ Assistant/Threads/Pusher.hs | 57 ++++++++++++++++++------------- Utility/ThreadScheduler.hs | 6 ---- doc/design/assistant/syncing.mdwn | 5 +-- 5 files changed, 82 insertions(+), 36 deletions(-) create mode 100644 Assistant/Pushes.hs diff --git a/Assistant.hs b/Assistant.hs index ec46894a5b..c054dafd3d 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -25,14 +25,17 @@ - Thread 6: pusher - Waits for commits to be made, and pushes updated branches to remotes, - in parallel. (Forks a process for each git push.) - - Thread 7: merger + - Thread 7: push retryer + - Runs every 30 minutes when there are failed pushes, and retries + - them. + - Thread 8: merger - Waits for pushes to be received from remotes, and merges the - updated branches into the current branch. This uses inotify - on .git/refs/heads, so there are additional inotify threads - associated with it, too. - - Thread 8: status logger + - Thread 9: status logger - Wakes up periodically and records the daemon's status to disk. - - Thread 9: sanity checker + - Thread 10: sanity checker - Wakes up periodically (rarely) and does sanity checks. - - ThreadState: (MVar) @@ -59,6 +62,7 @@ import Assistant.ThreadedMonad import Assistant.DaemonStatus import Assistant.Changes import Assistant.Commits +import Assistant.Pushes import Assistant.Threads.Watcher import Assistant.Threads.Committer import Assistant.Threads.Pusher @@ -85,8 +89,10 @@ startDaemon assistant foreground liftIO $ a $ do changechan <- newChangeChan commitchan <- newCommitChan + pushchan <- newFailedPushChan _ <- forkIO $ commitThread st changechan commitchan - _ <- forkIO $ pushThread st commitchan + _ <- forkIO $ pushThread st commitchan pushchan + _ <- forkIO $ pushRetryThread st pushchan _ <- forkIO $ mergeThread st _ <- forkIO $ daemonStatusThread st dstatus _ <- forkIO $ sanityCheckerThread st dstatus changechan diff --git a/Assistant/Pushes.hs b/Assistant/Pushes.hs new file mode 100644 index 0000000000..f3bffbf792 --- /dev/null +++ b/Assistant/Pushes.hs @@ -0,0 +1,36 @@ +{- git-annex assistant push tracking + - + - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Assistant.Pushes where + +import Common.Annex +import Utility.TSet + +import Data.Time.Clock + +type FailedPushChan = TSet FailedPush + +data FailedPush = FailedPush + { failedRemote :: Remote + , failedTimeStamp :: UTCTime + } + +newFailedPushChan :: IO FailedPushChan +newFailedPushChan = newTSet + +{- Gets all failed pushes. Blocks until there is at least one failed push. -} +getFailedPushes :: FailedPushChan -> IO [FailedPush] +getFailedPushes = getTSet + +{- Puts failed pushes back into the channel. + - Note: Original order is not preserved. -} +refillFailedPushes :: FailedPushChan -> [FailedPush] -> IO () +refillFailedPushes = putTSet + +{- Records a failed push in the channel. -} +recordFailedPush :: FailedPushChan -> FailedPush -> IO () +recordFailedPush = putTSet1 diff --git a/Assistant/Threads/Pusher.hs b/Assistant/Threads/Pusher.hs index de90d4e64c..6a4ae7838d 100644 --- a/Assistant/Threads/Pusher.hs +++ b/Assistant/Threads/Pusher.hs @@ -1,4 +1,4 @@ -{- git-annex assistant git pushing thread +{- git-annex assistant git pushing threads - - Copyright 2012 Joey Hess - @@ -9,6 +9,7 @@ module Assistant.Threads.Pusher where import Common.Annex import Assistant.Commits +import Assistant.Pushes import Assistant.ThreadedMonad import qualified Command.Sync import Utility.ThreadScheduler @@ -16,39 +17,45 @@ import Utility.Parallel import Data.Time.Clock -data FailedPush = FailedPush - { failedRemote :: Remote - , failedTimeStamp :: UTCTime - } +{- This thread retries pushes that failed before. -} +pushRetryThread :: ThreadState -> FailedPushChan -> IO () +pushRetryThread st pushchan = runEvery (Seconds halfhour) $ do + -- We already waited half an hour, now wait until there are failed + -- pushes to retry. + pushes <- getFailedPushes pushchan + -- Check times, to avoid repushing a push that's too new. + now <- getCurrentTime + let (newpushes, oldpushes) = partition (toorecent now . failedTimeStamp) pushes + unless (null newpushes) $ + refillFailedPushes pushchan newpushes + unless (null oldpushes) $ + pushToRemotes now st pushchan $ map failedRemote oldpushes + where + halfhour = 1800 + toorecent now time = now `diffUTCTime` time < fromIntegral halfhour -{- This thread pushes git commits out to remotes. -} -pushThread :: ThreadState -> CommitChan -> IO () -pushThread st commitchan = do +{- This thread pushes git commits out to remotes soon after they are made. -} +pushThread :: ThreadState -> CommitChan -> FailedPushChan -> IO () +pushThread st commitchan pushchan = do remotes <- runThreadState st $ Command.Sync.syncRemotes [] - runEveryWith (Seconds 2) [] $ \failedpushes -> do + runEvery (Seconds 2) $ do -- We already waited two seconds as a simple rate limiter. -- Next, wait until at least one commit has been made commits <- getCommits commitchan -- Now see if now's a good time to push. - time <- getCurrentTime - if shouldPush time commits failedpushes - then pushToRemotes time st remotes - else do - refillCommits commitchan commits - return failedpushes + now <- getCurrentTime + if shouldPush now commits + then pushToRemotes now st pushchan remotes + else refillCommits commitchan commits {- Decide if now is a good time to push to remotes. - - Current strategy: Immediately push all commits. The commit machinery - already determines batches of changes, so we can't easily determine - batches better. - - - - TODO: FailedPushs are only retried the next time there's a commit. - - Should retry them periodically, or when a remote that was not available - - becomes available. -} -shouldPush :: UTCTime -> [Commit] -> [FailedPush] -> Bool -shouldPush _now commits _failedremotes +shouldPush :: UTCTime -> [Commit] -> Bool +shouldPush _now commits | not (null commits) = True | otherwise = False @@ -57,12 +64,14 @@ shouldPush _now commits _failedremotes - - Avoids running possibly long-duration commands in the Annex monad, so - as not to block other threads. -} -pushToRemotes :: UTCTime -> ThreadState -> [Remote] -> IO [FailedPush] -pushToRemotes now st remotes = do +pushToRemotes :: UTCTime -> ThreadState -> FailedPushChan -> [Remote] -> IO () +pushToRemotes now st pushchan remotes = do (g, branch) <- runThreadState st $ (,) <$> fromRepo id <*> Command.Sync.currentBranch Command.Sync.updateBranch (Command.Sync.syncBranch branch) g - map (`FailedPush` now) <$> inParallel (push g branch) remotes + failed <- map (`FailedPush` now) <$> inParallel (push g branch) remotes + unless (null failed) $ + refillFailedPushes pushchan failed where push g branch remote = ifM (Command.Sync.pushBranch remote branch g) diff --git a/Utility/ThreadScheduler.hs b/Utility/ThreadScheduler.hs index 07a7401600..6557398fd7 100644 --- a/Utility/ThreadScheduler.hs +++ b/Utility/ThreadScheduler.hs @@ -24,12 +24,6 @@ runEvery n a = forever $ do threadDelaySeconds n a -runEveryWith :: Seconds -> a -> (a -> IO a) -> IO () -runEveryWith n val a = do - threadDelaySeconds n - val' <- a val - runEveryWith n val' a - threadDelaySeconds :: Seconds -> IO () threadDelaySeconds (Seconds n) = unboundDelay (fromIntegral n * oneSecond) where diff --git a/doc/design/assistant/syncing.mdwn b/doc/design/assistant/syncing.mdwn index 8173457c55..a2b80eebc4 100644 --- a/doc/design/assistant/syncing.mdwn +++ b/doc/design/assistant/syncing.mdwn @@ -13,8 +13,9 @@ all the other git clones, at both the git level and the key/value level. [The watching can be done with the existing inotify code! This avoids needing any special mechanism to notify a remote that it's been synced to.] **done** -1. Periodically retry pushes that failed. Also, detect if a push failed - due to not being up-to-date, pull, and repush. +1. Periodically retry pushes that failed. **done** (every half an hour) +1. Also, detect if a push failed due to not being up-to-date, pull, + and repush. 2. Use a git merge driver that adds both conflicting files, so conflicts never break a sync. 3. Investigate the XMPP approach like dvcs-autosync does, or other ways of From 05c4dfb9411e54c21aa4c0d49e3662117ac2f549 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Mon, 25 Jun 2012 20:16:30 -0400 Subject: [PATCH 011/331] fixup merges now done when needed --- Assistant/Threads/Merger.hs | 8 ++++++++ Assistant/Threads/Pusher.hs | 17 +++++++++++++---- doc/design/assistant/syncing.mdwn | 2 +- 3 files changed, 22 insertions(+), 5 deletions(-) diff --git a/Assistant/Threads/Merger.hs b/Assistant/Threads/Merger.hs index d2c8b9b766..77bf9f416e 100644 --- a/Assistant/Threads/Merger.hs +++ b/Assistant/Threads/Merger.hs @@ -70,3 +70,11 @@ onAdd g file _ mergeBranch :: Git.Ref -> Git.Repo -> IO Bool mergeBranch = Git.Merge.mergeNonInteractive . Command.Sync.syncBranch + +{- Manually pull from remotes and merge their branches. Called by the pusher + - when a push fails, which can happen due to a remote not having pushed + - changes to us. That could be because it doesn't have us as a remote, or + - because the assistant is not running there, or other reasons. -} +manualPull :: Git.Ref -> [Remote] -> Annex () +manualPull currentbranch remotes = forM_ remotes $ \r -> + Command.Sync.mergeRemote r currentbranch diff --git a/Assistant/Threads/Pusher.hs b/Assistant/Threads/Pusher.hs index 6a4ae7838d..82c37de5f8 100644 --- a/Assistant/Threads/Pusher.hs +++ b/Assistant/Threads/Pusher.hs @@ -11,6 +11,7 @@ import Common.Annex import Assistant.Commits import Assistant.Pushes import Assistant.ThreadedMonad +import Assistant.Threads.Merger import qualified Command.Sync import Utility.ThreadScheduler import Utility.Parallel @@ -68,11 +69,19 @@ pushToRemotes :: UTCTime -> ThreadState -> FailedPushChan -> [Remote] -> IO () pushToRemotes now st pushchan remotes = do (g, branch) <- runThreadState st $ (,) <$> fromRepo id <*> Command.Sync.currentBranch - Command.Sync.updateBranch (Command.Sync.syncBranch branch) g - failed <- map (`FailedPush` now) <$> inParallel (push g branch) remotes - unless (null failed) $ - refillFailedPushes pushchan failed + go True branch g remotes where + go shouldretry branch g rs = do + Command.Sync.updateBranch (Command.Sync.syncBranch branch) g + failed <- inParallel (push g branch) rs + unless (null failed) $ + if shouldretry + then retry branch g rs + else refillFailedPushes pushchan $ + map (`FailedPush` now) failed push g branch remote = ifM (Command.Sync.pushBranch remote branch g) ( exitSuccess, exitFailure) + retry branch g rs = do + runThreadState st $ manualPull branch rs + go False branch g rs diff --git a/doc/design/assistant/syncing.mdwn b/doc/design/assistant/syncing.mdwn index a2b80eebc4..3ece69638c 100644 --- a/doc/design/assistant/syncing.mdwn +++ b/doc/design/assistant/syncing.mdwn @@ -15,7 +15,7 @@ all the other git clones, at both the git level and the key/value level. **done** 1. Periodically retry pushes that failed. **done** (every half an hour) 1. Also, detect if a push failed due to not being up-to-date, pull, - and repush. + and repush. **done** 2. Use a git merge driver that adds both conflicting files, so conflicts never break a sync. 3. Investigate the XMPP approach like dvcs-autosync does, or other ways of From f2bce89055da1a453d420a7f46b5f86ab0c4c1ff Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Tue, 26 Jun 2012 12:36:42 -0400 Subject: [PATCH 012/331] better data type for push records Not yet plumbed thru --- Assistant/Pushes.hs | 37 +++++++++++++++++++------------------ 1 file changed, 19 insertions(+), 18 deletions(-) diff --git a/Assistant/Pushes.hs b/Assistant/Pushes.hs index f3bffbf792..61d2b798b3 100644 --- a/Assistant/Pushes.hs +++ b/Assistant/Pushes.hs @@ -8,29 +8,30 @@ module Assistant.Pushes where import Common.Annex -import Utility.TSet +import Control.Concurrent.SampleVar import Data.Time.Clock +import qualified Data.Map as M -type FailedPushChan = TSet FailedPush - -data FailedPush = FailedPush - { failedRemote :: Remote - , failedTimeStamp :: UTCTime - } +{- Track the most recent push failure for each remote. -} +type PushMap = M.Map Remote UTCTime +type FailedPushes = SampleVar PushMap newFailedPushChan :: IO FailedPushChan -newFailedPushChan = newTSet +newFailedPushChan = newEmptySampleVar -{- Gets all failed pushes. Blocks until there is at least one failed push. -} -getFailedPushes :: FailedPushChan -> IO [FailedPush] -getFailedPushes = getTSet +{- Gets all failed pushes. Blocks until set. -} +getFailedPushes :: FailedPushChan -> IO PushMap +getFailedPushes = readSampleVar -{- Puts failed pushes back into the channel. - - Note: Original order is not preserved. -} -refillFailedPushes :: FailedPushChan -> [FailedPush] -> IO () -refillFailedPushes = putTSet +{- Sets all failed pushes to passed PushMap -} +setFailedPushes :: FailedPushChan -> PushMap -> IO () +setFailedPushes = writeSampleVar -{- Records a failed push in the channel. -} -recordFailedPush :: FailedPushChan -> FailedPush -> IO () -recordFailedPush = putTSet1 +{- Indicates a failure to push to a single remote. -} +failedPush :: FailedPushChan -> Remote -> IO () +failedPush c r = + +{- Indicates that a remote was pushed to successfully. -} +successfulPush :: FailedPushChan -> Remote -> IO () +successfulPush c r = From 67c8ef7de25ad6f433db2fa5d5fc764dd515a5b2 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Tue, 26 Jun 2012 17:33:34 -0400 Subject: [PATCH 013/331] use a TMVar SampleMVar won't work; between getting the current value and changing it, another thread could made a change, which would get lost. TMVar works well; this update situation is handled by atomic transactions. --- Assistant.hs | 9 +++++--- Assistant/Pushes.hs | 45 ++++++++++++++++++++++--------------- Assistant/Threads/Pusher.hs | 44 ++++++++++++++++++------------------ Utility/Parallel.hs | 10 +++++---- 4 files changed, 61 insertions(+), 47 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index c054dafd3d..4f8a868f4f 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -53,6 +53,9 @@ - CommitChan: (STM TChan) - Commits are indicated by writing to this channel. The pusher reads - from it. + - FailedPushMap (STM TMVar) + - Failed pushes are indicated by writing to this TMVar. The push + - retrier blocks until they're available. -} module Assistant where @@ -89,10 +92,10 @@ startDaemon assistant foreground liftIO $ a $ do changechan <- newChangeChan commitchan <- newCommitChan - pushchan <- newFailedPushChan + pushmap <- newFailedPushMap _ <- forkIO $ commitThread st changechan commitchan - _ <- forkIO $ pushThread st commitchan pushchan - _ <- forkIO $ pushRetryThread st pushchan + _ <- forkIO $ pushThread st commitchan pushmap + _ <- forkIO $ pushRetryThread st pushmap _ <- forkIO $ mergeThread st _ <- forkIO $ daemonStatusThread st dstatus _ <- forkIO $ sanityCheckerThread st dstatus changechan diff --git a/Assistant/Pushes.hs b/Assistant/Pushes.hs index 61d2b798b3..f411dda07d 100644 --- a/Assistant/Pushes.hs +++ b/Assistant/Pushes.hs @@ -8,30 +8,39 @@ module Assistant.Pushes where import Common.Annex -import Control.Concurrent.SampleVar +import Control.Concurrent.STM import Data.Time.Clock import qualified Data.Map as M {- Track the most recent push failure for each remote. -} type PushMap = M.Map Remote UTCTime -type FailedPushes = SampleVar PushMap +type FailedPushMap = TMVar PushMap -newFailedPushChan :: IO FailedPushChan -newFailedPushChan = newEmptySampleVar +{- The TMVar starts empty, and is left empty when there are no + - failed pushes. This way we can block until there are some failed pushes. + -} +newFailedPushMap :: IO FailedPushMap +newFailedPushMap = atomically newEmptyTMVar -{- Gets all failed pushes. Blocks until set. -} -getFailedPushes :: FailedPushChan -> IO PushMap -getFailedPushes = readSampleVar +{- Blocks until there are failed pushes. + - Returns Remotes whose pushes failed a given time duration or more ago. + - (This may be an empty list.) -} +getFailedPushesBefore :: FailedPushMap -> NominalDiffTime -> IO [Remote] +getFailedPushesBefore v duration = do + m <- atomically $ readTMVar v + now <- getCurrentTime + return $ M.keys $ M.filter (not . toorecent now) m + where + toorecent now time = now `diffUTCTime` time < duration -{- Sets all failed pushes to passed PushMap -} -setFailedPushes :: FailedPushChan -> PushMap -> IO () -setFailedPushes = writeSampleVar - -{- Indicates a failure to push to a single remote. -} -failedPush :: FailedPushChan -> Remote -> IO () -failedPush c r = - -{- Indicates that a remote was pushed to successfully. -} -successfulPush :: FailedPushChan -> Remote -> IO () -successfulPush c r = +{- Modifies the map. -} +changeFailedPushMap :: FailedPushMap -> (PushMap -> PushMap) -> IO () +changeFailedPushMap v a = atomically $ + store . a . fromMaybe M.empty =<< tryTakeTMVar v + where + {- tryTakeTMVar empties the TMVar; refill it only if + - the modified map is not itself empty -} + store m + | m == M.empty = noop + | otherwise = putTMVar v $! m diff --git a/Assistant/Threads/Pusher.hs b/Assistant/Threads/Pusher.hs index 82c37de5f8..04d3435287 100644 --- a/Assistant/Threads/Pusher.hs +++ b/Assistant/Threads/Pusher.hs @@ -17,27 +17,23 @@ import Utility.ThreadScheduler import Utility.Parallel import Data.Time.Clock +import qualified Data.Map as M {- This thread retries pushes that failed before. -} -pushRetryThread :: ThreadState -> FailedPushChan -> IO () -pushRetryThread st pushchan = runEvery (Seconds halfhour) $ do +pushRetryThread :: ThreadState -> FailedPushMap -> IO () +pushRetryThread st pushmap = runEvery (Seconds halfhour) $ do -- We already waited half an hour, now wait until there are failed -- pushes to retry. - pushes <- getFailedPushes pushchan - -- Check times, to avoid repushing a push that's too new. - now <- getCurrentTime - let (newpushes, oldpushes) = partition (toorecent now . failedTimeStamp) pushes - unless (null newpushes) $ - refillFailedPushes pushchan newpushes - unless (null oldpushes) $ - pushToRemotes now st pushchan $ map failedRemote oldpushes + topush <- getFailedPushesBefore pushmap (fromIntegral halfhour) + unless (null topush) $ do + now <- getCurrentTime + pushToRemotes now st pushmap topush where halfhour = 1800 - toorecent now time = now `diffUTCTime` time < fromIntegral halfhour {- This thread pushes git commits out to remotes soon after they are made. -} -pushThread :: ThreadState -> CommitChan -> FailedPushChan -> IO () -pushThread st commitchan pushchan = do +pushThread :: ThreadState -> CommitChan -> FailedPushMap -> IO () +pushThread st commitchan pushmap = do remotes <- runThreadState st $ Command.Sync.syncRemotes [] runEvery (Seconds 2) $ do -- We already waited two seconds as a simple rate limiter. @@ -46,7 +42,7 @@ pushThread st commitchan pushchan = do -- Now see if now's a good time to push. now <- getCurrentTime if shouldPush now commits - then pushToRemotes now st pushchan remotes + then pushToRemotes now st pushmap remotes else refillCommits commitchan commits {- Decide if now is a good time to push to remotes. @@ -65,23 +61,27 @@ shouldPush _now commits - - Avoids running possibly long-duration commands in the Annex monad, so - as not to block other threads. -} -pushToRemotes :: UTCTime -> ThreadState -> FailedPushChan -> [Remote] -> IO () -pushToRemotes now st pushchan remotes = do +pushToRemotes :: UTCTime -> ThreadState -> FailedPushMap -> [Remote] -> IO () +pushToRemotes now st pushmap remotes = do (g, branch) <- runThreadState st $ (,) <$> fromRepo id <*> Command.Sync.currentBranch go True branch g remotes where go shouldretry branch g rs = do Command.Sync.updateBranch (Command.Sync.syncBranch branch) g - failed <- inParallel (push g branch) rs - unless (null failed) $ - if shouldretry - then retry branch g rs - else refillFailedPushes pushchan $ - map (`FailedPush` now) failed + (succeeded, failed) <- inParallel (push g branch) rs + changeFailedPushMap pushmap $ \m -> + M.union (makemap failed) $ + M.difference m (makemap succeeded) + unless (null failed || not shouldretry) $ + retry branch g failed + + makemap l = M.fromList $ zip l (repeat now) + push g branch remote = ifM (Command.Sync.pushBranch remote branch g) ( exitSuccess, exitFailure) + retry branch g rs = do runThreadState st $ manualPull branch rs go False branch g rs diff --git a/Utility/Parallel.hs b/Utility/Parallel.hs index 6e4671c057..9df95ab2b0 100644 --- a/Utility/Parallel.hs +++ b/Utility/Parallel.hs @@ -10,11 +10,13 @@ module Utility.Parallel where import Common {- Runs an action in parallel with a set of values. - - Returns values that caused the action to fail. -} -inParallel :: (v -> IO ()) -> [v] -> IO [v] + - Returns the values partitioned into ones with which the action succeeded, + - and ones with which it failed. -} +inParallel :: (v -> IO ()) -> [v] -> IO ([v], [v]) inParallel a l = do pids <- mapM (forkProcess . a) l statuses <- mapM (getProcessStatus True False) pids - return $ map fst $ filter (failed . snd) $ zip l statuses + return $ reduce $ partition (succeeded . snd) $ zip l statuses where - failed v = v /= Just (Exited ExitSuccess) + succeeded v = v == Just (Exited ExitSuccess) + reduce (x,y) = (map fst x, map fst y) From 783bee285fd357b887de818918b181ea4628783a Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 27 Jun 2012 20:06:21 -0400 Subject: [PATCH 014/331] automatic conflict resolution for assistant --- Assistant/Threads/Merger.hs | 29 +++++++++++++++++------------ 1 file changed, 17 insertions(+), 12 deletions(-) diff --git a/Assistant/Threads/Merger.hs b/Assistant/Threads/Merger.hs index 77bf9f416e..3659588fcd 100644 --- a/Assistant/Threads/Merger.hs +++ b/Assistant/Threads/Merger.hs @@ -24,7 +24,7 @@ mergeThread st = do g <- runThreadState st $ fromRepo id let dir = Git.localGitDir g "refs" "heads" "synced" createDirectoryIfMissing True dir - let hook a = Just $ runHandler g a + let hook a = Just $ runHandler st g a let hooks = mkWatchHooks { addHook = hook onAdd , errHook = hook onErr @@ -32,21 +32,21 @@ mergeThread st = do watchDir dir (const False) hooks id where -type Handler = Git.Repo -> FilePath -> Maybe FileStatus -> IO () +type Handler = ThreadState -> Git.Repo -> FilePath -> Maybe FileStatus -> IO () {- Runs an action handler. - - Exceptions are ignored, otherwise a whole thread could be crashed. -} -runHandler :: Git.Repo -> Handler -> FilePath -> Maybe FileStatus -> IO () -runHandler g handler file filestatus = void $ do +runHandler :: ThreadState -> Git.Repo -> Handler -> FilePath -> Maybe FileStatus -> IO () +runHandler st g handler file filestatus = void $ do either print (const noop) =<< tryIO go where - go = handler g file filestatus + go = handler st g file filestatus {- Called when there's an error with inotify. -} onErr :: Handler -onErr _ msg _ = error msg +onErr _ _ msg _ = error msg {- Called when a new branch ref is written. - @@ -60,16 +60,21 @@ onErr _ msg _ = error msg - ran are merged in. -} onAdd :: Handler -onAdd g file _ +onAdd st g file _ | ".lock" `isSuffixOf` file = noop | otherwise = do - let branch = Git.Ref $ "refs" "heads" takeFileName file + let changedbranch = Git.Ref $ + "refs" "heads" takeFileName file current <- Git.Branch.current g - when (Just branch == current) $ - void $ mergeBranch branch g + when (Just changedbranch == current) $ + void $ mergeBranch st changedbranch g -mergeBranch :: Git.Ref -> Git.Repo -> IO Bool -mergeBranch = Git.Merge.mergeNonInteractive . Command.Sync.syncBranch +mergeBranch :: ThreadState -> Git.Ref -> Git.Repo -> IO Bool +mergeBranch st branch repo = do + ok <- Git.Merge.mergeNonInteractive (Command.Sync.syncBranch branch) repo + if ok + then return ok + else runThreadState st Command.Sync.resolveMerge {- Manually pull from remotes and merge their branches. Called by the pusher - when a push fails, which can happen due to a remote not having pushed From 59b5266ad13efe465b67b31aba3b750c31fb83cd Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 27 Jun 2012 20:30:04 -0400 Subject: [PATCH 015/331] actually fetch from remote when doing a manual pull forgot to do this --- Assistant/Threads/Merger.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/Assistant/Threads/Merger.hs b/Assistant/Threads/Merger.hs index 3659588fcd..602bebb5b0 100644 --- a/Assistant/Threads/Merger.hs +++ b/Assistant/Threads/Merger.hs @@ -12,9 +12,11 @@ import Assistant.ThreadedMonad import Utility.DirWatcher import Utility.Types.DirWatcher import qualified Git +import qualified Git.Command import qualified Git.Merge import qualified Git.Branch import qualified Command.Sync +import qualified Remote {- This thread watches for changes to .git/refs/heads/synced/*, - which indicate incoming pushes. It merges those pushes into the @@ -81,5 +83,6 @@ mergeBranch st branch repo = do - changes to us. That could be because it doesn't have us as a remote, or - because the assistant is not running there, or other reasons. -} manualPull :: Git.Ref -> [Remote] -> Annex () -manualPull currentbranch remotes = forM_ remotes $ \r -> +manualPull currentbranch remotes = forM_ remotes $ \r -> do + void $ inRepo $ Git.Command.runBool "fetch" [Param $ Remote.name r] Command.Sync.mergeRemote r currentbranch From fb51d9995193b2e15f3e5174783347ec14dbaa28 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 27 Jun 2012 20:50:50 -0400 Subject: [PATCH 016/331] merge conflict resolution now working Avoid MVar deadlock issue, which I don't understand. Have not taken the time to debug it fully, because it turns out I don't need to resolve merge conflicts when a new branch ref is written... I think. Ensure the git-annex branch is merged when doing a manual pull. Otherwise it can get out of sync, since git-annex normally only merges it once per run. --- Assistant/Threads/Merger.hs | 37 ++++++++++++++++++++----------------- 1 file changed, 20 insertions(+), 17 deletions(-) diff --git a/Assistant/Threads/Merger.hs b/Assistant/Threads/Merger.hs index 602bebb5b0..d643f16943 100644 --- a/Assistant/Threads/Merger.hs +++ b/Assistant/Threads/Merger.hs @@ -11,6 +11,7 @@ import Common.Annex import Assistant.ThreadedMonad import Utility.DirWatcher import Utility.Types.DirWatcher +import qualified Annex.Branch import qualified Git import qualified Git.Command import qualified Git.Merge @@ -26,7 +27,10 @@ mergeThread st = do g <- runThreadState st $ fromRepo id let dir = Git.localGitDir g "refs" "heads" "synced" createDirectoryIfMissing True dir - let hook a = Just $ runHandler st g a + let hook a = Just $ runHandler g a + -- XXX: For reasons currently unknown, using the ThreadState + -- inside the watch hooks leads to a MVar deadlock. + -- Luckily, we don't currently need to do that. let hooks = mkWatchHooks { addHook = hook onAdd , errHook = hook onErr @@ -34,21 +38,21 @@ mergeThread st = do watchDir dir (const False) hooks id where -type Handler = ThreadState -> Git.Repo -> FilePath -> Maybe FileStatus -> IO () +type Handler = Git.Repo -> FilePath -> Maybe FileStatus -> IO () {- Runs an action handler. - - Exceptions are ignored, otherwise a whole thread could be crashed. -} -runHandler :: ThreadState -> Git.Repo -> Handler -> FilePath -> Maybe FileStatus -> IO () -runHandler st g handler file filestatus = void $ do +runHandler :: Git.Repo -> Handler -> FilePath -> Maybe FileStatus -> IO () +runHandler g handler file filestatus = void $ do either print (const noop) =<< tryIO go where - go = handler st g file filestatus + go = handler g file filestatus {- Called when there's an error with inotify. -} onErr :: Handler -onErr _ _ msg _ = error msg +onErr _ msg _ = error msg {- Called when a new branch ref is written. - @@ -62,27 +66,26 @@ onErr _ _ msg _ = error msg - ran are merged in. -} onAdd :: Handler -onAdd st g file _ +onAdd g file _ | ".lock" `isSuffixOf` file = noop | otherwise = do let changedbranch = Git.Ref $ "refs" "heads" takeFileName file current <- Git.Branch.current g when (Just changedbranch == current) $ - void $ mergeBranch st changedbranch g + void $ mergeBranch changedbranch g -mergeBranch :: ThreadState -> Git.Ref -> Git.Repo -> IO Bool -mergeBranch st branch repo = do - ok <- Git.Merge.mergeNonInteractive (Command.Sync.syncBranch branch) repo - if ok - then return ok - else runThreadState st Command.Sync.resolveMerge +mergeBranch :: Git.Ref -> Git.Repo -> IO Bool +mergeBranch = Git.Merge.mergeNonInteractive . Command.Sync.syncBranch {- Manually pull from remotes and merge their branches. Called by the pusher - when a push fails, which can happen due to a remote not having pushed - changes to us. That could be because it doesn't have us as a remote, or - because the assistant is not running there, or other reasons. -} manualPull :: Git.Ref -> [Remote] -> Annex () -manualPull currentbranch remotes = forM_ remotes $ \r -> do - void $ inRepo $ Git.Command.runBool "fetch" [Param $ Remote.name r] - Command.Sync.mergeRemote r currentbranch +manualPull currentbranch remotes = do + forM_ remotes $ \r -> + inRepo $ Git.Command.runBool "fetch" [Param $ Remote.name r] + Annex.Branch.forceUpdate + forM_ remotes $ \r -> + Command.Sync.mergeRemote r currentbranch From 40f357fdcf07a9b9844e675fe478ab08f5c1bae8 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 28 Jun 2012 13:04:02 -0400 Subject: [PATCH 017/331] tweak --- Assistant.hs | 2 +- Assistant/Threads/Merger.hs | 1 - 2 files changed, 1 insertion(+), 2 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index 4f8a868f4f..b61270613c 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -40,7 +40,7 @@ - - ThreadState: (MVar) - The Annex state is stored here, which allows resuscitating the - - Annex monad in IO actions run by the inotify and committer + - Annex monad in IO actions run by the watcher and committer - threads. Thus, a single state is shared amoung the threads, and - only one at a time can access it. - DaemonStatusHandle: (MVar) diff --git a/Assistant/Threads/Merger.hs b/Assistant/Threads/Merger.hs index d643f16943..de172e8da0 100644 --- a/Assistant/Threads/Merger.hs +++ b/Assistant/Threads/Merger.hs @@ -36,7 +36,6 @@ mergeThread st = do , errHook = hook onErr } watchDir dir (const False) hooks id - where type Handler = Git.Repo -> FilePath -> Maybe FileStatus -> IO () From 4888c5b0422c8006b4c178503b24bced733931fa Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 28 Jun 2012 13:37:03 -0400 Subject: [PATCH 018/331] improve thread termination handling The reason the DirWatcher had to wait for program termination was because it used withINotify, so when it finished, its watcher threads were killed. But since I have two DirWatcher threads now, that was not good, and could perhaps explain the MVar problem I saw yesterday. In any case, fixed this part of the code by making the DirWatcher return a handle that can be used to stop it, and now the main Assistant thread is the only one calling waitForTermination. --- Assistant.hs | 5 +++-- Assistant/Threads/Merger.hs | 2 +- Assistant/Threads/Watcher.hs | 2 +- Utility/DirWatcher.hs | 35 ++++++++++++++++++++++++++++------- 4 files changed, 33 insertions(+), 11 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index b61270613c..2a11741b4d 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -73,6 +73,7 @@ import Assistant.Threads.Merger import Assistant.Threads.SanityChecker import qualified Utility.Daemon import Utility.LogFile +import Utility.ThreadScheduler import Control.Concurrent @@ -99,8 +100,8 @@ startDaemon assistant foreground _ <- forkIO $ mergeThread st _ <- forkIO $ daemonStatusThread st dstatus _ <- forkIO $ sanityCheckerThread st dstatus changechan - -- Does not return. - watchThread st dstatus changechan + _ <- forkIO $ watchThread st dstatus changechan + waitForTermination stopDaemon :: Annex () stopDaemon = liftIO . Utility.Daemon.stopDaemon =<< fromRepo gitAnnexPidFile diff --git a/Assistant/Threads/Merger.hs b/Assistant/Threads/Merger.hs index de172e8da0..5d24d1862b 100644 --- a/Assistant/Threads/Merger.hs +++ b/Assistant/Threads/Merger.hs @@ -35,7 +35,7 @@ mergeThread st = do { addHook = hook onAdd , errHook = hook onErr } - watchDir dir (const False) hooks id + void $ watchDir dir (const False) hooks id type Handler = Git.Repo -> FilePath -> Maybe FileStatus -> IO () diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs index 1b6ec15f18..e250f4b4a6 100644 --- a/Assistant/Threads/Watcher.hs +++ b/Assistant/Threads/Watcher.hs @@ -46,7 +46,7 @@ needLsof = error $ unlines ] watchThread :: ThreadState -> DaemonStatusHandle -> ChangeChan -> IO () -watchThread st dstatus changechan = watchDir "." ignored hooks startup +watchThread st dstatus changechan = void $ watchDir "." ignored hooks startup where startup = statupScan st dstatus hook a = Just $ runHandler st dstatus changechan a diff --git a/Utility/DirWatcher.hs b/Utility/DirWatcher.hs index 11ce7baef1..93c3ecb026 100644 --- a/Utility/DirWatcher.hs +++ b/Utility/DirWatcher.hs @@ -17,7 +17,6 @@ import Utility.Types.DirWatcher #if WITH_INOTIFY import qualified Utility.INotify as INotify import qualified System.INotify as INotify -import Utility.ThreadScheduler #endif #if WITH_KQUEUE import qualified Utility.Kqueue as Kqueue @@ -72,19 +71,41 @@ closingTracked = undefined #endif #endif +/* Starts a watcher thread. The runStartup action is passed a scanner action + * to run, that will return once the initial directory scan is complete. + * Once runStartup returns, the watcher thread continues running, + * and processing events. Returns a DirWatcherHandle that can be used + * to shutdown later. */ #if WITH_INOTIFY -watchDir :: FilePath -> Pruner -> WatchHooks -> (IO () -> IO ()) -> IO () -watchDir dir prune hooks runstartup = INotify.withINotify $ \i -> do +type DirWatcherHandle = INotify.INotify +watchDir :: FilePath -> Pruner -> WatchHooks -> (IO () -> IO ()) -> IO DirWatcherHandle +watchDir dir prune hooks runstartup = do + i <- INotify.initINotify runstartup $ INotify.watchDir i dir prune hooks - waitForTermination -- Let the inotify thread run. + return i #else #if WITH_KQUEUE -watchDir :: FilePath -> Pruner -> WatchHooks -> (IO Kqueue.Kqueue -> IO Kqueue.Kqueue) -> IO () +type DirWatcherHandle = ThreadID +watchDir :: FilePath -> Pruner -> WatchHooks -> (IO Kqueue.Kqueue -> IO Kqueue.Kqueue) -> IO DirWatcherHandle watchDir dir ignored hooks runstartup = do kq <- runstartup $ Kqueue.initKqueue dir ignored - Kqueue.runHooks kq hooks + forkIO $ Kqueue.runHooks kq hooks #else -watchDir :: FilePath -> Pruner -> WatchHooks -> (IO () -> IO ()) -> IO () +type DirWatcherHandle = () +watchDir :: FilePath -> Pruner -> WatchHooks -> (IO () -> IO ()) -> IO DirWatcherHandle watchDir = undefined #endif #endif + +#if WITH_INOTIFY +stopWatchDir :: DirWatcherHandle -> IO () +stopWatchDir = INotify.killINotify +#else +#if WITH_KQUEUE +stopWatchDir :: DirWatcherHandle -> IO () +stopWatchDir = killThread +#else +stopWatchDir :: DirWatcherHandle -> IO () +stopWatchDir = undefined +#endif +#endif From a3636602ab5b33bf25cef760d4780794841bc8e6 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 28 Jun 2012 13:47:15 -0400 Subject: [PATCH 019/331] MVar deadlock problem seems to be fixed by previous commit --- Assistant/Threads/Merger.hs | 3 --- 1 file changed, 3 deletions(-) diff --git a/Assistant/Threads/Merger.hs b/Assistant/Threads/Merger.hs index 5d24d1862b..c7da86a8d3 100644 --- a/Assistant/Threads/Merger.hs +++ b/Assistant/Threads/Merger.hs @@ -28,9 +28,6 @@ mergeThread st = do let dir = Git.localGitDir g "refs" "heads" "synced" createDirectoryIfMissing True dir let hook a = Just $ runHandler g a - -- XXX: For reasons currently unknown, using the ThreadState - -- inside the watch hooks leads to a MVar deadlock. - -- Luckily, we don't currently need to do that. let hooks = mkWatchHooks { addHook = hook onAdd , errHook = hook onErr From 421f9ce0e26936e384700c9cb5e202191cc92d1c Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 28 Jun 2012 14:13:15 -0400 Subject: [PATCH 020/331] fix kqueue build --- Utility/DirWatcher.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/Utility/DirWatcher.hs b/Utility/DirWatcher.hs index 93c3ecb026..5e76e780c8 100644 --- a/Utility/DirWatcher.hs +++ b/Utility/DirWatcher.hs @@ -20,6 +20,7 @@ import qualified System.INotify as INotify #endif #if WITH_KQUEUE import qualified Utility.Kqueue as Kqueue +import Control.Concurrent #endif type Pruner = FilePath -> Bool From 638a321ca504e24809c85e24583ae06cd5f7de8f Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 28 Jun 2012 14:15:49 -0400 Subject: [PATCH 021/331] typo --- Utility/DirWatcher.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Utility/DirWatcher.hs b/Utility/DirWatcher.hs index 5e76e780c8..213aeb50a7 100644 --- a/Utility/DirWatcher.hs +++ b/Utility/DirWatcher.hs @@ -86,7 +86,7 @@ watchDir dir prune hooks runstartup = do return i #else #if WITH_KQUEUE -type DirWatcherHandle = ThreadID +type DirWatcherHandle = ThreadId watchDir :: FilePath -> Pruner -> WatchHooks -> (IO Kqueue.Kqueue -> IO Kqueue.Kqueue) -> IO DirWatcherHandle watchDir dir ignored hooks runstartup = do kq <- runstartup $ Kqueue.initKqueue dir ignored From c7328556a3d3aa504c68c612f2c19a1dd49a4e25 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 28 Jun 2012 14:48:46 -0400 Subject: [PATCH 022/331] update --- doc/design/assistant/syncing.mdwn | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/doc/design/assistant/syncing.mdwn b/doc/design/assistant/syncing.mdwn index 3e90e6b105..50e6fb4f18 100644 --- a/doc/design/assistant/syncing.mdwn +++ b/doc/design/assistant/syncing.mdwn @@ -17,12 +17,18 @@ all the other git clones, at both the git level and the key/value level. 1. Also, detect if a push failed due to not being up-to-date, pull, and repush. **done** 2. Use a git merge driver that adds both conflicting files, - so conflicts never break a sync. + so conflicts never break a sync. **done** 3. Investigate the XMPP approach like dvcs-autosync does, or other ways of signaling a change out of band. 4. Add a hook, so when there's a change to sync, a program can be run and do its own signaling. +## misc todo + +* --debug will show often unnecessary work being done. Optimise. +* It would be nice if, when a USB drive is connected, + syncing starts automatically. Use dbus on Linux? + ## data syncing There are two parts to data syncing. First, map the network and second, @@ -41,8 +47,5 @@ This probably will need lots of refinements to get working well. ## other considerations -It would be nice if, when a USB drive is connected, -syncing starts automatically. Use dbus on Linux? - This assumes the network is connected. It's often not, so the [[cloud]] needs to be used to bridge between LANs. From 39569e889a5cdef913cd3927ee0383eafac77190 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 28 Jun 2012 18:22:43 -0400 Subject: [PATCH 023/331] blog for the day --- .../blog/day_19__random_improvements.mdwn | 50 +++++++++++++++++++ 1 file changed, 50 insertions(+) create mode 100644 doc/design/assistant/blog/day_19__random_improvements.mdwn diff --git a/doc/design/assistant/blog/day_19__random_improvements.mdwn b/doc/design/assistant/blog/day_19__random_improvements.mdwn new file mode 100644 index 0000000000..93c1296bab --- /dev/null +++ b/doc/design/assistant/blog/day_19__random_improvements.mdwn @@ -0,0 +1,50 @@ +Random improvements day.. + +Got the merge conflict resolution code working in `git annex assistant`. + +Did some more fixes to the pushing and pulling code, covering some cases +I missed earlier. + +Git syncing seems to work well for me now; I've seen it recover +from a variety of error conditions, including merge conflicts and repos +that were temporarily unavailable. + +---- + +There is definitely a MVar deadlock if the merger thread's inotify event +handler tries to run code in the Annex monad. Luckily, it doesn't +currently seem to need to do that, so I have put off debugging what's going +on there. + +Reworked how the inotify thread runs, to avoid the two inotify threads +in the assistant now from both needing to wait for program termination, +in a possibly conflicting manner. + +Hmm, that *seems* to have fixed the MVar deadlock problem. + +---- + +Been thinking about how to fix [[bugs/watcher_commits_unlocked_files]]. +Posted some thoughts there. + +It's about time to move on to data [[syncing]]. While eventually that will +need to build a map of the repo network to efficiently sync data over the +fastest paths, I'm thinking that I'll first write a dumb version. So, two +more threads: + +1. Uploads new data to every configured remote. Triggered by the watcher + thread when it adds content. Easy; just use a `TSet` of Keys to send. + +2. Downloads new data from the cheapest remote that has it. COuld be + triggered by the + merger thread, after it merges in a git sync. Rather hard; how does it + work out what new keys are in the tree without scanning it all? Scan + through the git history to find newly created files? Maybe the watcher + triggers this thread instead, when it sees a new symlink, without data, + appear. + +Both threads will need to be able to be stopped, and restarted, as needed +to control the data transfer. And a lot of other control smarts will +eventually be needed, but my first pass will be to do a straightforward +implementation. Once it's done, the git annex assistant will be basically +usable. From 247099f6282262cb72027aeeadce2e7bb8073eef Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 28 Jun 2012 20:01:03 -0400 Subject: [PATCH 024/331] refactor --- Assistant.hs | 29 ++++++++++++++++------------- 1 file changed, 16 insertions(+), 13 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index 2a11741b4d..a077cf10f6 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -87,21 +87,24 @@ startDaemon assistant foreground pidfile <- fromRepo gitAnnexPidFile go $ Utility.Daemon.daemonize logfd (Just pidfile) False where - go a = withThreadState $ \st -> do + go daemonize = withThreadState $ \st -> do checkCanWatch dstatus <- startDaemonStatus - liftIO $ a $ do - changechan <- newChangeChan - commitchan <- newCommitChan - pushmap <- newFailedPushMap - _ <- forkIO $ commitThread st changechan commitchan - _ <- forkIO $ pushThread st commitchan pushmap - _ <- forkIO $ pushRetryThread st pushmap - _ <- forkIO $ mergeThread st - _ <- forkIO $ daemonStatusThread st dstatus - _ <- forkIO $ sanityCheckerThread st dstatus changechan - _ <- forkIO $ watchThread st dstatus changechan - waitForTermination + liftIO $ daemonize $ run dstatus st + run dstatus st = do + changechan <- newChangeChan + commitchan <- newCommitChan + pushmap <- newFailedPushMap + mapM_ (void . forkIO) + [ commitThread st changechan commitchan + , pushThread st commitchan pushmap + , pushRetryThread st pushmap + , mergeThread st + , daemonStatusThread st dstatus + , sanityCheckerThread st dstatus changechan + , watchThread st dstatus changechan + ] + waitForTermination stopDaemon :: Annex () stopDaemon = liftIO . Utility.Daemon.stopDaemon =<< fromRepo gitAnnexPidFile From 397117429c8824bad7e994454a1d9b8e6f4b3b96 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 28 Jun 2012 23:40:16 -0400 Subject: [PATCH 025/331] simplify modifyMVar_ catches exceptions, so no need to roll my own --- Assistant/ThreadedMonad.hs | 13 ++----------- 1 file changed, 2 insertions(+), 11 deletions(-) diff --git a/Assistant/ThreadedMonad.hs b/Assistant/ThreadedMonad.hs index 6d3d25778e..7b915e12c8 100644 --- a/Assistant/ThreadedMonad.hs +++ b/Assistant/ThreadedMonad.hs @@ -5,15 +5,13 @@ - Licensed under the GNU GPL version 3 or higher. -} -{-# LANGUAGE BangPatterns #-} - module Assistant.ThreadedMonad where import Common.Annex import qualified Annex import Control.Concurrent -import Control.Exception (throw) +import Data.Tuple {- The Annex state is stored in a MVar, so that threaded actions can access - it. -} @@ -37,11 +35,4 @@ withThreadState a = do - This serializes calls by threads; only one thread can run in Annex at a - time. -} runThreadState :: ThreadState -> Annex a -> IO a -runThreadState mvar a = do - startstate <- takeMVar mvar - -- catch IO errors and rethrow after restoring the MVar - !(r, newstate) <- catchIO (Annex.run startstate a) $ \e -> do - putMVar mvar startstate - throw e - putMVar mvar newstate - return r +runThreadState mvar a = modifyMVar mvar $ \state -> swap <$> Annex.run state a From c9d7e9f6bd5adac8a5ff0e925bbac549f962cdb0 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Mon, 2 Jul 2012 16:06:52 -0400 Subject: [PATCH 026/331] startedTime needs to be a Maybe to handle transfers that have not started yet This changes the file format. --- Logs/Transfer.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Logs/Transfer.hs b/Logs/Transfer.hs index dc92833069..f808cb6a44 100644 --- a/Logs/Transfer.hs +++ b/Logs/Transfer.hs @@ -34,7 +34,7 @@ data Transfer = Transfer - of some repository, that was acted on to initiate the transfer. -} data TransferInfo = TransferInfo - { startedTime :: UTCTime + { startedTime :: Maybe UTCTime , transferPid :: Maybe ProcessID , transferThread :: Maybe ThreadId , bytesComplete :: Maybe Integer @@ -76,7 +76,7 @@ transfer t file a = do createAnnexDirectory $ takeDirectory tfile mode <- annexFileMode info <- liftIO $ TransferInfo - <$> getCurrentTime + <$> (Just <$> getCurrentTime) <*> pure Nothing -- pid not stored in file, so omitted for speed <*> pure Nothing -- threadid not stored in file, so omitted for speed <*> pure Nothing -- not 0; transfer may be resuming From ad0b82795742228d3ed9eab7e50f4000f6d78734 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Mon, 2 Jul 2012 16:07:39 -0400 Subject: [PATCH 027/331] added --- Assistant/TransferQueue.hs | 43 ++++++++++++++++++++++++++++++++++++++ 1 file changed, 43 insertions(+) create mode 100644 Assistant/TransferQueue.hs diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs new file mode 100644 index 0000000000..979cbb80f5 --- /dev/null +++ b/Assistant/TransferQueue.hs @@ -0,0 +1,43 @@ +{- git-annex assistant pending transfer queue + - + - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Assistant.TransferQueue where + +import Common.Annex +import Utility.TSet +import Logs.Transfer +import Types.Remote + +import Control.Concurrent.STM + +type TransferQueue = TChan (Transfer, TransferInfo) + +newTransferQueue :: IO TransferQueue +newTransferQueue = atomically newTChan + +stubInfo :: AssociatedFile -> TransferInfo +stubInfo f = TransferInfo + { startedTime = Nothing + , transferPid = Nothing + , transferThread = Nothing + , bytesComplete = Nothing + , associatedFile = f + } + +{- Adds a pending transfer to the end of the queue. -} +queueTransfer :: TransferQueue -> Transfer -> AssociatedFile -> IO () +queueTransfer q transfer f = void $ atomically $ + writeTChan q (transfer, stubInfo f) + +{- Adds a pending transfer to the start of the queue, to be processed next. -} +queueNextTransfer :: TransferQueue -> Transfer -> AssociatedFile -> IO () +queueNextTransfer q transfer f = void $ atomically $ + unGetTChan q (transfer, stubInfo f) + +{- Blocks until a pending transfer is available in the queue. -} +getNextTransfer :: TransferQueue -> IO (Transfer, TransferInfo) +getNextTransfer = atomically . readTChan From 32e5e02e431338a7b04990ab91feaea7b32d6d0e Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Mon, 2 Jul 2012 16:11:04 -0400 Subject: [PATCH 028/331] added currentTransfers --- Assistant/DaemonStatus.hs | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs index c7713e7d56..10161a96cb 100644 --- a/Assistant/DaemonStatus.hs +++ b/Assistant/DaemonStatus.hs @@ -17,6 +17,8 @@ import System.Posix.Types import Data.Time.Clock.POSIX import Data.Time import System.Locale +import Logs.Transfer +import qualified Data.Map as M data DaemonStatus = DaemonStatus -- False when the daemon is performing its startup scan @@ -27,6 +29,8 @@ data DaemonStatus = DaemonStatus , sanityCheckRunning :: Bool -- Last time the sanity checker ran , lastSanityCheck :: Maybe POSIXTime + -- Currently running file content transfers + , currentTransfers :: M.Map Transfer TransferInfo } deriving (Show) @@ -38,6 +42,7 @@ newDaemonStatus = DaemonStatus , lastRunning = Nothing , sanityCheckRunning = False , lastSanityCheck = Nothing + , currentTransfers = M.empty } getDaemonStatus :: DaemonStatusHandle -> Annex DaemonStatus @@ -47,15 +52,17 @@ modifyDaemonStatus :: DaemonStatusHandle -> (DaemonStatus -> DaemonStatus) -> An modifyDaemonStatus handle a = liftIO $ modifyMVar_ handle (return . a) {- Load any previous daemon status file, and store it in the MVar for this - - process to use as its DaemonStatus. -} + - process to use as its DaemonStatus. Also gets current transfer status. -} startDaemonStatus :: Annex DaemonStatusHandle startDaemonStatus = do file <- fromRepo gitAnnexDaemonStatusFile status <- liftIO $ catchDefaultIO (readDaemonStatusFile file) newDaemonStatus + transfers <- M.fromList <$> getTransfers liftIO $ newMVar status { scanComplete = False , sanityCheckRunning = False + , currentTransfers = transfers } {- This thread wakes up periodically and writes the daemon status to disk. -} From b4917bd18fa9e2eacb5fbd916828d30e2ac297b4 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Tue, 3 Jul 2012 10:58:40 -0400 Subject: [PATCH 029/331] add transfer watching thread Worked the 1st try! --- Assistant.hs | 13 ++++- Assistant/Threads/TransferWatcher.hs | 78 ++++++++++++++++++++++++++++ 2 files changed, 89 insertions(+), 2 deletions(-) create mode 100644 Assistant/Threads/TransferWatcher.hs diff --git a/Assistant.hs b/Assistant.hs index a077cf10f6..40f53d55ee 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -33,9 +33,14 @@ - updated branches into the current branch. This uses inotify - on .git/refs/heads, so there are additional inotify threads - associated with it, too. - - Thread 9: status logger + - Thread 9: transfer watcher + - Watches for transfer information files being created and removed, + - and maintains the DaemonStatus currentTransfers map. This uses + - inotify on .git/annex/transfer/, so there are additional inotify + - threads associated with it, too. + - Thread 10: status logger - Wakes up periodically and records the daemon's status to disk. - - Thread 10: sanity checker + - Thread 11: sanity checker - Wakes up periodically (rarely) and does sanity checks. - - ThreadState: (MVar) @@ -56,6 +61,8 @@ - FailedPushMap (STM TMVar) - Failed pushes are indicated by writing to this TMVar. The push - retrier blocks until they're available. + - TransferQueue (STM TChan) + - Transfers to make are indicated by writing to this channel. -} module Assistant where @@ -70,6 +77,7 @@ import Assistant.Threads.Watcher import Assistant.Threads.Committer import Assistant.Threads.Pusher import Assistant.Threads.Merger +import Assistant.Threads.TransferWatcher import Assistant.Threads.SanityChecker import qualified Utility.Daemon import Utility.LogFile @@ -100,6 +108,7 @@ startDaemon assistant foreground , pushThread st commitchan pushmap , pushRetryThread st pushmap , mergeThread st + , transferWatcherThread st dstatus , daemonStatusThread st dstatus , sanityCheckerThread st dstatus changechan , watchThread st dstatus changechan diff --git a/Assistant/Threads/TransferWatcher.hs b/Assistant/Threads/TransferWatcher.hs new file mode 100644 index 0000000000..811b045a82 --- /dev/null +++ b/Assistant/Threads/TransferWatcher.hs @@ -0,0 +1,78 @@ +{- git-annex assistant transfer watching thread + - + - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Assistant.Threads.TransferWatcher where + +import Common.Annex +import Assistant.ThreadedMonad +import Assistant.DaemonStatus +import Logs.Transfer +import Utility.DirWatcher +import Utility.Types.DirWatcher + +import Data.Map as M + +{- This thread watches for changes to the gitAnnexTransferDir, + - and updates the DaemonStatus's map of ongoing transfers. -} +transferWatcherThread :: ThreadState -> DaemonStatusHandle -> IO () +transferWatcherThread st dstatus = do + g <- runThreadState st $ fromRepo id + let dir = gitAnnexTransferDir g + createDirectoryIfMissing True dir + let hook a = Just $ runHandler st dstatus a + let hooks = mkWatchHooks + { addHook = hook onAdd + , delHook = hook onDel + , errHook = hook onErr + } + void $ watchDir dir (const False) hooks id + +type Handler = ThreadState -> DaemonStatusHandle -> FilePath -> Maybe FileStatus -> IO () + +{- Runs an action handler. + - + - Exceptions are ignored, otherwise a whole thread could be crashed. + -} +runHandler :: ThreadState -> DaemonStatusHandle -> Handler -> FilePath -> Maybe FileStatus -> IO () +runHandler st dstatus handler file filestatus = void $ do + either print (const noop) =<< tryIO go + where + go = handler st dstatus file filestatus + +{- Called when there's an error with inotify. -} +onErr :: Handler +onErr _ _ msg _ = error msg + +{- Called when a new transfer information file is written. + - + - When another thread of the assistant writes a transfer info file, + - this will notice that too, but should skip it, because the thread + - will be managing the transfer itself, and will have stored a more + - complete TransferInfo than is stored in the file. + -} +onAdd :: Handler +onAdd st dstatus file _ = case parseTransferFile file of + Nothing -> noop + Just t -> do + minfo <- runThreadState st $ checkTransfer t + pid <- getProcessID + case minfo of + Nothing -> noop -- transfer already finished + Just info + | transferPid info == Just pid -> noop + | otherwise -> adjustTransfers st dstatus + (M.insertWith' const t info) + +{- Called when a transfer information file is removed. -} +onDel :: Handler +onDel st dstatus file _ = case parseTransferFile file of + Nothing -> noop + Just t -> adjustTransfers st dstatus (M.delete t) + +adjustTransfers :: ThreadState -> DaemonStatusHandle -> (M.Map Transfer TransferInfo -> M.Map Transfer TransferInfo) -> IO () +adjustTransfers st dstatus a = runThreadState st $ modifyDaemonStatus dstatus $ + \s -> s { currentTransfers = a (currentTransfers s) } From 83c66ccaf88a10e8f4b16fc2162cbed2656b95e0 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 5 Jul 2012 10:21:22 -0600 Subject: [PATCH 030/331] queue Uploads of newly added files to remotes Added knownRemotes to DaemonStatus. This list is not entirely trivial to calculate, and having it here should make it easier to add/remove remotes on the fly later on. It did require plumbing the daemonstatus through to some more threads. --- Assistant.hs | 9 ++++++--- Assistant/DaemonStatus.hs | 8 +++++++- Assistant/Threads/Committer.hs | 28 ++++++++++++++++------------ Assistant/Threads/Pusher.hs | 11 +++++++---- Assistant/TransferQueue.hs | 29 ++++++++++++++++++++++------- 5 files changed, 58 insertions(+), 27 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index 40f53d55ee..548850e92d 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -21,7 +21,8 @@ - until this is complete. - Thread 5: committer - Waits for changes to occur, and runs the git queue to update its - - index, then commits. + - index, then commits. Also queues Transfer events to send added + - files to other remotes. - Thread 6: pusher - Waits for commits to be made, and pushes updated branches to remotes, - in parallel. (Forks a process for each git push.) @@ -73,6 +74,7 @@ import Assistant.DaemonStatus import Assistant.Changes import Assistant.Commits import Assistant.Pushes +import Assistant.TransferQueue import Assistant.Threads.Watcher import Assistant.Threads.Committer import Assistant.Threads.Pusher @@ -103,9 +105,10 @@ startDaemon assistant foreground changechan <- newChangeChan commitchan <- newCommitChan pushmap <- newFailedPushMap + transferqueue <- newTransferQueue mapM_ (void . forkIO) - [ commitThread st changechan commitchan - , pushThread st commitchan pushmap + [ commitThread st changechan commitchan transferqueue dstatus + , pushThread st dstatus commitchan pushmap , pushRetryThread st pushmap , mergeThread st , transferWatcherThread st dstatus diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs index 10161a96cb..a3e909904f 100644 --- a/Assistant/DaemonStatus.hs +++ b/Assistant/DaemonStatus.hs @@ -11,13 +11,14 @@ import Common.Annex import Assistant.ThreadedMonad import Utility.ThreadScheduler import Utility.TempFile +import Logs.Transfer +import qualified Command.Sync import Control.Concurrent import System.Posix.Types import Data.Time.Clock.POSIX import Data.Time import System.Locale -import Logs.Transfer import qualified Data.Map as M data DaemonStatus = DaemonStatus @@ -31,6 +32,8 @@ data DaemonStatus = DaemonStatus , lastSanityCheck :: Maybe POSIXTime -- Currently running file content transfers , currentTransfers :: M.Map Transfer TransferInfo + -- Ordered list of remotes to talk to. + , knownRemotes :: [Remote] } deriving (Show) @@ -43,6 +46,7 @@ newDaemonStatus = DaemonStatus , sanityCheckRunning = False , lastSanityCheck = Nothing , currentTransfers = M.empty + , knownRemotes = [] } getDaemonStatus :: DaemonStatusHandle -> Annex DaemonStatus @@ -59,10 +63,12 @@ startDaemonStatus = do status <- liftIO $ catchDefaultIO (readDaemonStatusFile file) newDaemonStatus transfers <- M.fromList <$> getTransfers + remotes <- Command.Sync.syncRemotes [] liftIO $ newMVar status { scanComplete = False , sanityCheckRunning = False , currentTransfers = transfers + , knownRemotes = remotes } {- This thread wakes up periodically and writes the daemon status to disk. -} diff --git a/Assistant/Threads/Committer.hs b/Assistant/Threads/Committer.hs index 488056fa2b..ff5cc9eabc 100644 --- a/Assistant/Threads/Committer.hs +++ b/Assistant/Threads/Committer.hs @@ -12,6 +12,9 @@ import Assistant.Changes import Assistant.Commits import Assistant.ThreadedMonad import Assistant.Threads.Watcher +import Assistant.TransferQueue +import Assistant.DaemonStatus +import Logs.Transfer import qualified Annex import qualified Annex.Queue import qualified Git.Command @@ -29,8 +32,8 @@ import qualified Data.Set as S import Data.Either {- This thread makes git commits at appropriate times. -} -commitThread :: ThreadState -> ChangeChan -> CommitChan -> IO () -commitThread st changechan commitchan = runEvery (Seconds 1) $ do +commitThread :: ThreadState -> ChangeChan -> CommitChan -> TransferQueue -> DaemonStatusHandle -> IO () +commitThread st changechan commitchan transferqueue dstatus = runEvery (Seconds 1) $ do -- We already waited one second as a simple rate limiter. -- Next, wait until at least one change is available for -- processing. @@ -39,7 +42,7 @@ commitThread st changechan commitchan = runEvery (Seconds 1) $ do time <- getCurrentTime if shouldCommit time changes then do - readychanges <- handleAdds st changechan changes + readychanges <- handleAdds st changechan transferqueue dstatus changes if shouldCommit time readychanges then do void $ tryIO $ runThreadState st commitStaged @@ -97,8 +100,8 @@ shouldCommit now changes - Any pending adds that are not ready yet are put back into the ChangeChan, - where they will be retried later. -} -handleAdds :: ThreadState -> ChangeChan -> [Change] -> IO [Change] -handleAdds st changechan cs = returnWhen (null pendingadds) $ do +handleAdds :: ThreadState -> ChangeChan -> TransferQueue -> DaemonStatusHandle -> [Change] -> IO [Change] +handleAdds st changechan transferqueue dstatus cs = returnWhen (null pendingadds) $ do (postponed, toadd) <- partitionEithers <$> safeToAdd st pendingadds @@ -110,7 +113,7 @@ handleAdds st changechan cs = returnWhen (null pendingadds) $ do if (DirWatcher.eventsCoalesce || null added) then return $ added ++ otherchanges else do - r <- handleAdds st changechan + r <- handleAdds st changechan transferqueue dstatus =<< getChanges changechan return $ r ++ added ++ otherchanges where @@ -121,12 +124,12 @@ handleAdds st changechan cs = returnWhen (null pendingadds) $ do | otherwise = a add :: Change -> IO (Maybe Change) - add change@(PendingAddChange { keySource = ks }) = do - r <- catchMaybeIO $ sanitycheck ks $ runThreadState st $ do - showStart "add" $ keyFilename ks - handle (finishedChange change) (keyFilename ks) - =<< Command.Add.ingest ks - return $ maybeMaybe r + add change@(PendingAddChange { keySource = ks }) = + liftM maybeMaybe $ catchMaybeIO $ + sanitycheck ks $ runThreadState st $ do + showStart "add" $ keyFilename ks + key <- Command.Add.ingest ks + handle (finishedChange change) (keyFilename ks) key add _ = return Nothing maybeMaybe (Just j@(Just _)) = j @@ -141,6 +144,7 @@ handleAdds st changechan cs = returnWhen (null pendingadds) $ do sha <- inRepo $ Git.HashObject.hashObject BlobObject link stageSymlink file sha + queueTransfers transferqueue dstatus key (Just file) Upload showEndOk return $ Just change diff --git a/Assistant/Threads/Pusher.hs b/Assistant/Threads/Pusher.hs index 04d3435287..6d6836120e 100644 --- a/Assistant/Threads/Pusher.hs +++ b/Assistant/Threads/Pusher.hs @@ -10,6 +10,7 @@ module Assistant.Threads.Pusher where import Common.Annex import Assistant.Commits import Assistant.Pushes +import Assistant.DaemonStatus import Assistant.ThreadedMonad import Assistant.Threads.Merger import qualified Command.Sync @@ -32,9 +33,8 @@ pushRetryThread st pushmap = runEvery (Seconds halfhour) $ do halfhour = 1800 {- This thread pushes git commits out to remotes soon after they are made. -} -pushThread :: ThreadState -> CommitChan -> FailedPushMap -> IO () -pushThread st commitchan pushmap = do - remotes <- runThreadState st $ Command.Sync.syncRemotes [] +pushThread :: ThreadState -> DaemonStatusHandle -> CommitChan -> FailedPushMap -> IO () +pushThread st daemonstatus commitchan pushmap = do runEvery (Seconds 2) $ do -- We already waited two seconds as a simple rate limiter. -- Next, wait until at least one commit has been made @@ -42,7 +42,10 @@ pushThread st commitchan pushmap = do -- Now see if now's a good time to push. now <- getCurrentTime if shouldPush now commits - then pushToRemotes now st pushmap remotes + then do + remotes <- runThreadState st $ + knownRemotes <$> getDaemonStatus daemonstatus + pushToRemotes now st pushmap remotes else refillCommits commitchan commits {- Decide if now is a good time to push to remotes. diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs index 979cbb80f5..fc25b057d3 100644 --- a/Assistant/TransferQueue.hs +++ b/Assistant/TransferQueue.hs @@ -8,9 +8,10 @@ module Assistant.TransferQueue where import Common.Annex -import Utility.TSet +import Assistant.DaemonStatus import Logs.Transfer import Types.Remote +import qualified Remote import Control.Concurrent.STM @@ -28,15 +29,29 @@ stubInfo f = TransferInfo , associatedFile = f } +{- Adds pending transfers to the end of the queue for some of the known + - remotes. (TBD: a smaller set of remotes that are sufficient to transfer to, + - rather than transferring to all.) -} +queueTransfers :: TransferQueue -> DaemonStatusHandle -> Key -> AssociatedFile -> Direction -> Annex () +queueTransfers q daemonstatus k f direction = + mapM_ (liftIO . queueTransfer q f . gentransfer) + =<< knownRemotes <$> getDaemonStatus daemonstatus + where + gentransfer r = Transfer + { transferDirection = direction + , transferKey = k + , transferRemote = Remote.uuid r + } + {- Adds a pending transfer to the end of the queue. -} -queueTransfer :: TransferQueue -> Transfer -> AssociatedFile -> IO () -queueTransfer q transfer f = void $ atomically $ - writeTChan q (transfer, stubInfo f) +queueTransfer :: TransferQueue -> AssociatedFile -> Transfer -> IO () +queueTransfer q f t = void $ atomically $ + writeTChan q (t, stubInfo f) {- Adds a pending transfer to the start of the queue, to be processed next. -} -queueNextTransfer :: TransferQueue -> Transfer -> AssociatedFile -> IO () -queueNextTransfer q transfer f = void $ atomically $ - unGetTChan q (transfer, stubInfo f) +queueNextTransfer :: TransferQueue -> AssociatedFile -> Transfer -> IO () +queueNextTransfer q f t = void $ atomically $ + unGetTChan q (t, stubInfo f) {- Blocks until a pending transfer is available in the queue. -} getNextTransfer :: TransferQueue -> IO (Transfer, TransferInfo) From c1728849a9b5d1e7803cf6a36f826a7bafdc667a Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 5 Jul 2012 10:34:47 -0600 Subject: [PATCH 031/331] update --- doc/design/assistant/syncing.mdwn | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) diff --git a/doc/design/assistant/syncing.mdwn b/doc/design/assistant/syncing.mdwn index d2248279f7..caae60a32e 100644 --- a/doc/design/assistant/syncing.mdwn +++ b/doc/design/assistant/syncing.mdwn @@ -16,7 +16,7 @@ all the other git clones, at both the git level and the key/value level. * Poll transfer in progress info files for changes (use inotify again! wow! hammer, meet nail..), and update the TransferInfo Map **done** * enqueue Transfers (Uploads) as new files are added to the annex by - Watcher. + Watcher. **done** * enqueue Tranferrs (Downloads) as new dangling symlinks are noticed by Watcher. * Write basic Transfer handling thread. Multiple such threads need to be @@ -82,11 +82,8 @@ anyway. ### transfer tracking -* Upload added to queue by the watcher thread when it adds content. -* Download added to queue by the watcher thread when it seens new symlinks - that lack content. -* Transfer threads started/stopped as necessary to move data. - (May sometimes want multiple threads downloading, or uploading, or even both.) +Transfer threads started/stopped as necessary to move data. +(May sometimes want multiple threads downloading, or uploading, or even both.) startTransfer :: TransferQueue -> Transfer -> Annex () startTransfer q transfer = error "TODO" From c8135ea0a8aa2b374e45a8bb8c447c5287862838 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 5 Jul 2012 10:44:03 -0600 Subject: [PATCH 032/331] split logic for uploads and downloads --- Assistant/TransferQueue.hs | 19 ++++++++++++++++--- 1 file changed, 16 insertions(+), 3 deletions(-) diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs index fc25b057d3..f1f4882bef 100644 --- a/Assistant/TransferQueue.hs +++ b/Assistant/TransferQueue.hs @@ -30,13 +30,26 @@ stubInfo f = TransferInfo } {- Adds pending transfers to the end of the queue for some of the known - - remotes. (TBD: a smaller set of remotes that are sufficient to transfer to, - - rather than transferring to all.) -} + - remotes. -} queueTransfers :: TransferQueue -> DaemonStatusHandle -> Key -> AssociatedFile -> Direction -> Annex () queueTransfers q daemonstatus k f direction = mapM_ (liftIO . queueTransfer q f . gentransfer) - =<< knownRemotes <$> getDaemonStatus daemonstatus + =<< sufficientremotes . knownRemotes + <$> getDaemonStatus daemonstatus where + sufficientremotes l + -- Queue downloads from all remotes, with the + -- cheapest ones first. More expensive ones will + -- only be tried if downloading from a cheap one + -- fails. + -- TODO: avoid downloading from remotes that don't + -- have the key. + | direction == Download = l + -- TODO: Determine a smaller set of remotes that + -- can be uploaded to, in order to ensure all + -- remotes can access the content. Currently, + -- send to every remote we can. + | otherwise = l gentransfer r = Transfer { transferDirection = direction , transferKey = k From 6af319d8cdefb4589d9cd354dbc49006bb7d68ea Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 5 Jul 2012 10:58:49 -0600 Subject: [PATCH 033/331] enqueue Downloads when new symlinks appear to content we don't have --- Assistant.hs | 4 +-- Assistant/Threads/SanityChecker.hs | 13 +++++----- Assistant/Threads/Watcher.hs | 39 ++++++++++++++++++++---------- 3 files changed, 35 insertions(+), 21 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index 548850e92d..82ac2037e3 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -113,8 +113,8 @@ startDaemon assistant foreground , mergeThread st , transferWatcherThread st dstatus , daemonStatusThread st dstatus - , sanityCheckerThread st dstatus changechan - , watchThread st dstatus changechan + , sanityCheckerThread st dstatus transferqueue changechan + , watchThread st dstatus transferqueue changechan ] waitForTermination diff --git a/Assistant/Threads/SanityChecker.hs b/Assistant/Threads/SanityChecker.hs index 4db2a61b22..d7b117cd02 100644 --- a/Assistant/Threads/SanityChecker.hs +++ b/Assistant/Threads/SanityChecker.hs @@ -14,14 +14,15 @@ import qualified Git.LsFiles import Assistant.DaemonStatus import Assistant.ThreadedMonad import Assistant.Changes +import Assistant.TransferQueue import Utility.ThreadScheduler import qualified Assistant.Threads.Watcher as Watcher import Data.Time.Clock.POSIX {- This thread wakes up occasionally to make sure the tree is in good shape. -} -sanityCheckerThread :: ThreadState -> DaemonStatusHandle -> ChangeChan -> IO () -sanityCheckerThread st status changechan = forever $ do +sanityCheckerThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> ChangeChan -> IO () +sanityCheckerThread st status transferqueue changechan = forever $ do waitForNextCheck st status runThreadState st $ @@ -29,7 +30,7 @@ sanityCheckerThread st status changechan = forever $ do { sanityCheckRunning = True } now <- getPOSIXTime -- before check started - catchIO (check st status changechan) + catchIO (check st status transferqueue changechan) (runThreadState st . warning . show) runThreadState st $ do @@ -58,8 +59,8 @@ oneDay = 24 * 60 * 60 {- It's important to stay out of the Annex monad as much as possible while - running potentially expensive parts of this check, since remaining in it - will block the watcher. -} -check :: ThreadState -> DaemonStatusHandle -> ChangeChan -> IO () -check st status changechan = do +check :: ThreadState -> DaemonStatusHandle -> TransferQueue -> ChangeChan -> IO () +check st status transferqueue changechan = do g <- runThreadState st $ do showSideAction "Running daily check" fromRepo id @@ -79,5 +80,5 @@ check st status changechan = do insanity m = runThreadState st $ warning m addsymlink file s = do insanity $ "found unstaged symlink: " ++ file - Watcher.runHandler st status changechan + Watcher.runHandler st status transferqueue changechan Watcher.onAddSymlink file s diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs index e250f4b4a6..882aab3a78 100644 --- a/Assistant/Threads/Watcher.hs +++ b/Assistant/Threads/Watcher.hs @@ -13,6 +13,8 @@ import Common.Annex import Assistant.ThreadedMonad import Assistant.DaemonStatus import Assistant.Changes +import Assistant.TransferQueue +import Logs.Transfer import Utility.DirWatcher import Utility.Types.DirWatcher import qualified Annex @@ -45,11 +47,11 @@ needLsof = error $ unlines , "Be warned: This can corrupt data in the annex, and make fsck complain." ] -watchThread :: ThreadState -> DaemonStatusHandle -> ChangeChan -> IO () -watchThread st dstatus changechan = void $ watchDir "." ignored hooks startup +watchThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> ChangeChan -> IO () +watchThread st dstatus transferqueue changechan = void $ watchDir "." ignored hooks startup where startup = statupScan st dstatus - hook a = Just $ runHandler st dstatus changechan a + hook a = Just $ runHandler st dstatus transferqueue changechan a hooks = WatchHooks { addHook = hook onAdd , delHook = hook onDel @@ -82,22 +84,22 @@ ignored = ig . takeFileName ig ".gitattributes" = True ig _ = False -type Handler = FilePath -> Maybe FileStatus -> DaemonStatusHandle -> Annex (Maybe Change) +type Handler = FilePath -> Maybe FileStatus -> DaemonStatusHandle -> TransferQueue -> Annex (Maybe Change) {- Runs an action handler, inside the Annex monad, and if there was a - change, adds it to the ChangeChan. - - Exceptions are ignored, otherwise a whole watcher thread could be crashed. -} -runHandler :: ThreadState -> DaemonStatusHandle -> ChangeChan -> Handler -> FilePath -> Maybe FileStatus -> IO () -runHandler st dstatus changechan handler file filestatus = void $ do +runHandler :: ThreadState -> DaemonStatusHandle -> TransferQueue -> ChangeChan -> Handler -> FilePath -> Maybe FileStatus -> IO () +runHandler st dstatus transferqueue changechan handler file filestatus = void $ do r <- tryIO go case r of Left e -> print e Right Nothing -> noop Right (Just change) -> recordChange changechan change where - go = runThreadState st $ handler file filestatus dstatus + go = runThreadState st $ handler file filestatus dstatus transferqueue {- During initial directory scan, this will be run for any regular files - that are already checked into git. We don't want to turn those into @@ -118,7 +120,7 @@ runHandler st dstatus changechan handler file filestatus = void $ do - the add. -} onAdd :: Handler -onAdd file filestatus dstatus +onAdd file filestatus dstatus _ | maybe False isRegularFile filestatus = do ifM (scanComplete <$> getDaemonStatus dstatus) ( go @@ -136,12 +138,15 @@ onAdd file filestatus dstatus - before adding it. -} onAddSymlink :: Handler -onAddSymlink file filestatus dstatus = go =<< Backend.lookupFile file +onAddSymlink file filestatus dstatus transferqueue = go =<< Backend.lookupFile file where go (Just (key, _)) = do link <- calcGitLink file key ifM ((==) link <$> liftIO (readSymbolicLink file)) - ( ensurestaged link =<< getDaemonStatus dstatus + ( do + s <- getDaemonStatus dstatus + checkcontent key s + ensurestaged link s , do liftIO $ removeFile file liftIO $ createSymbolicLink link file @@ -183,8 +188,16 @@ onAddSymlink file filestatus dstatus = go =<< Backend.lookupFile file stageSymlink file sha madeChange file LinkChange + {- When a new link appears, after the startup scan, + - try to get the key's content. -} + checkcontent key daemonstatus + | scanComplete daemonstatus = unlessM (inAnnex key) $ + queueTransfers transferqueue dstatus + key (Just file) Download + | otherwise = noop + onDel :: Handler -onDel file _ _dstatus = do +onDel file _ _dstatus _ = do Annex.Queue.addUpdateIndex =<< inRepo (Git.UpdateIndex.unstageFile file) madeChange file RmChange @@ -197,14 +210,14 @@ onDel file _ _dstatus = do - command to get the recursive list of files in the directory, so rm is - just as good. -} onDelDir :: Handler -onDelDir dir _ _dstatus = do +onDelDir dir _ _dstatus _ = do Annex.Queue.addCommand "rm" [Params "--quiet -r --cached --ignore-unmatch --"] [dir] madeChange dir RmDirChange {- Called when there's an error with inotify. -} onErr :: Handler -onErr msg _ _dstatus = do +onErr msg _ _dstatus _ = do warning msg return Nothing From 71b5ad8398c4d86d5e9b993e175b48f2c5f0861d Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 5 Jul 2012 14:34:20 -0600 Subject: [PATCH 034/331] wrote transfer thread finally! --- Assistant.hs | 8 ++- Assistant/DaemonStatus.hs | 9 ++- Assistant/Threads/TransferWatcher.hs | 20 +++--- Assistant/Threads/Transferrer.hs | 102 +++++++++++++++++++++++++++ Assistant/TransferQueue.hs | 8 ++- Command/Status.hs | 4 +- Logs/Transfer.hs | 5 +- 7 files changed, 136 insertions(+), 20 deletions(-) create mode 100644 Assistant/Threads/Transferrer.hs diff --git a/Assistant.hs b/Assistant.hs index 82ac2037e3..e751b4ae8c 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -39,9 +39,11 @@ - and maintains the DaemonStatus currentTransfers map. This uses - inotify on .git/annex/transfer/, so there are additional inotify - threads associated with it, too. - - Thread 10: status logger + - Thread 10: transferrer + - Waits for Transfers to be queued and does them. + - Thread 11: status logger - Wakes up periodically and records the daemon's status to disk. - - Thread 11: sanity checker + - Thread 12: sanity checker - Wakes up periodically (rarely) and does sanity checks. - - ThreadState: (MVar) @@ -80,6 +82,7 @@ import Assistant.Threads.Committer import Assistant.Threads.Pusher import Assistant.Threads.Merger import Assistant.Threads.TransferWatcher +import Assistant.Threads.Transferrer import Assistant.Threads.SanityChecker import qualified Utility.Daemon import Utility.LogFile @@ -114,6 +117,7 @@ startDaemon assistant foreground , transferWatcherThread st dstatus , daemonStatusThread st dstatus , sanityCheckerThread st dstatus transferqueue changechan + , transfererThread st dstatus transferqueue , watchThread st dstatus transferqueue changechan ] waitForTermination diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs index a3e909904f..40816bb1a7 100644 --- a/Assistant/DaemonStatus.hs +++ b/Assistant/DaemonStatus.hs @@ -31,12 +31,14 @@ data DaemonStatus = DaemonStatus -- Last time the sanity checker ran , lastSanityCheck :: Maybe POSIXTime -- Currently running file content transfers - , currentTransfers :: M.Map Transfer TransferInfo + , currentTransfers :: TransferMap -- Ordered list of remotes to talk to. , knownRemotes :: [Remote] } deriving (Show) +type TransferMap = M.Map Transfer TransferInfo + type DaemonStatusHandle = MVar DaemonStatus newDaemonStatus :: DaemonStatus @@ -132,3 +134,8 @@ afterLastDaemonRun timestamp status = maybe False (< t) (lastRunning status) tenMinutes :: Int tenMinutes = 10 * 60 + +{- Mutates the transfer map. -} +adjustTransfers :: DaemonStatusHandle -> (TransferMap -> TransferMap) -> Annex () +adjustTransfers dstatus a = modifyDaemonStatus dstatus $ + \s -> s { currentTransfers = a (currentTransfers s) } diff --git a/Assistant/Threads/TransferWatcher.hs b/Assistant/Threads/TransferWatcher.hs index 811b045a82..f18d4e3f86 100644 --- a/Assistant/Threads/TransferWatcher.hs +++ b/Assistant/Threads/TransferWatcher.hs @@ -58,21 +58,17 @@ onAdd :: Handler onAdd st dstatus file _ = case parseTransferFile file of Nothing -> noop Just t -> do - minfo <- runThreadState st $ checkTransfer t pid <- getProcessID - case minfo of - Nothing -> noop -- transfer already finished - Just info - | transferPid info == Just pid -> noop - | otherwise -> adjustTransfers st dstatus - (M.insertWith' const t info) + runThreadState st $ go t pid =<< checkTransfer t + where + go _ _ Nothing = noop -- transfer already finished + go t pid (Just info) + | transferPid info == Just pid = noop + | otherwise = adjustTransfers dstatus $ + M.insertWith' const t info {- Called when a transfer information file is removed. -} onDel :: Handler onDel st dstatus file _ = case parseTransferFile file of Nothing -> noop - Just t -> adjustTransfers st dstatus (M.delete t) - -adjustTransfers :: ThreadState -> DaemonStatusHandle -> (M.Map Transfer TransferInfo -> M.Map Transfer TransferInfo) -> IO () -adjustTransfers st dstatus a = runThreadState st $ modifyDaemonStatus dstatus $ - \s -> s { currentTransfers = a (currentTransfers s) } + Just t -> runThreadState st $ adjustTransfers dstatus $ M.delete t diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs new file mode 100644 index 0000000000..0562a607ce --- /dev/null +++ b/Assistant/Threads/Transferrer.hs @@ -0,0 +1,102 @@ +{- git-annex assistant data transferrer thread + - + - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Assistant.Threads.Transferrer where + +import Common.Annex +import Assistant.ThreadedMonad +import Assistant.DaemonStatus +import Assistant.TransferQueue +import Logs.Transfer +import Annex.Content +import Annex.BranchState +import Command +import qualified Command.Move + +import Control.Exception as E +import Control.Concurrent +import Data.Time.Clock +import qualified Data.Map as M + +{- Dispatches transfers from the queue. + - + - This is currently very simplistic, and runs only one transfer at a time. + -} +transfererThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> IO () +transfererThread st dstatus transferqueue = do + mypid <- getProcessID + mytid <- myThreadId + go mypid mytid + where + go mypid mytid = do + (t, info) <- getNextTransfer transferqueue + + now <- getCurrentTime + let info' = info + { startedTime = Just now + , transferPid = Just mypid + , transferThread = Just mytid + } + + ifM (runThreadState st $ shouldtransfer t info') + ( runTransfer st t info' + , noop + ) + go mypid mytid + + -- Check if the transfer is already running, + -- and if not, add it to the TransferMap. + shouldtransfer t info = do + current <- currentTransfers <$> getDaemonStatus dstatus + if M.member t current + then ifM (validtransfer t) + ( do + adjustTransfers dstatus $ + M.insertWith' const t info + return True + , return False + ) + else return False + + validtransfer t + | transferDirection t == Download = + not <$> inAnnex (transferKey t) + | otherwise = return True + +{- A transfer is run in a separate thread, with a *copy* of the Annex + - state. This is necessary to avoid blocking the rest of the assistant + - on the transfer completing, and also to allow multiple transfers to run + - at once. + - + - However, it means that the transfer threads are responsible + - for doing any necessary shutdown cleanups, and that the parent + - thread's cache must be invalidated, as changes may have been made to the + - git-annex branch. + - + - Currently a minimal shutdown is done; the transfer threads are + - effectively running in oneshot mode, without committing changes to the + - git-annex branch, and transfers should never queue git commands to run. + - + - Note: It is unsafe to call getDaemonStatus inside the transfer thread. + -} +runTransfer :: ThreadState -> Transfer -> TransferInfo -> IO () +runTransfer st t info + | transferDirection t == Download = go Command.Move.fromStart + | otherwise = go Command.Move.toStart + where + go cmd = case (transferRemote info, associatedFile info) of + (Nothing, _) -> noop + (_, Nothing) -> noop + (Just remote, Just file) -> + inthread $ void $ doCommand $ + cmd remote False file (transferKey t) + inthread a = do + mvar <- newEmptyMVar + void $ forkIO $ + runThreadState st a `E.finally` putMVar mvar () + void $ takeMVar mvar -- wait for transfer thread + runThreadState st invalidateCache diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs index f1f4882bef..a35815ca16 100644 --- a/Assistant/TransferQueue.hs +++ b/Assistant/TransferQueue.hs @@ -25,6 +25,7 @@ stubInfo f = TransferInfo { startedTime = Nothing , transferPid = Nothing , transferThread = Nothing + , transferRemote = Nothing , bytesComplete = Nothing , associatedFile = f } @@ -33,7 +34,7 @@ stubInfo f = TransferInfo - remotes. -} queueTransfers :: TransferQueue -> DaemonStatusHandle -> Key -> AssociatedFile -> Direction -> Annex () queueTransfers q daemonstatus k f direction = - mapM_ (liftIO . queueTransfer q f . gentransfer) + mapM_ (\r -> queue r $ gentransfer r) =<< sufficientremotes . knownRemotes <$> getDaemonStatus daemonstatus where @@ -53,8 +54,11 @@ queueTransfers q daemonstatus k f direction = gentransfer r = Transfer { transferDirection = direction , transferKey = k - , transferRemote = Remote.uuid r + , transferUUID = Remote.uuid r } + queue r t = liftIO $ void $ atomically $ do + let info = (stubInfo f) { transferRemote = Just r } + writeTChan q (t, info) {- Adds a pending transfer to the end of the queue. -} queueTransfer :: TransferQueue -> AssociatedFile -> Transfer -> IO () diff --git a/Command/Status.hs b/Command/Status.hs index eff21bb509..2d63c525c3 100644 --- a/Command/Status.hs +++ b/Command/Status.hs @@ -186,8 +186,8 @@ transfer_list = stat "transfers in progress" $ nojson $ lift $ do [ show (transferDirection t) ++ "ing" , fromMaybe (show $ transferKey t) (associatedFile i) , if transferDirection t == Upload then "to" else "from" - , maybe (fromUUID $ transferRemote t) Remote.name $ - M.lookup (transferRemote t) uuidmap + , maybe (fromUUID $ transferUUID t) Remote.name $ + M.lookup (transferUUID t) uuidmap ] disk_size :: Stat diff --git a/Logs/Transfer.hs b/Logs/Transfer.hs index f808cb6a44..12ab8ff113 100644 --- a/Logs/Transfer.hs +++ b/Logs/Transfer.hs @@ -22,7 +22,7 @@ import Data.Time.Clock - of the transfer information file. -} data Transfer = Transfer { transferDirection :: Direction - , transferRemote :: UUID + , transferUUID :: UUID , transferKey :: Key } deriving (Show, Eq, Ord) @@ -37,6 +37,7 @@ data TransferInfo = TransferInfo { startedTime :: Maybe UTCTime , transferPid :: Maybe ProcessID , transferThread :: Maybe ThreadId + , transferRemote :: Maybe Remote , bytesComplete :: Maybe Integer , associatedFile :: Maybe FilePath } @@ -80,6 +81,7 @@ transfer t file a = do <*> pure Nothing -- pid not stored in file, so omitted for speed <*> pure Nothing -- threadid not stored in file, so omitted for speed <*> pure Nothing -- not 0; transfer may be resuming + <*> pure Nothing <*> pure file bracketIO (prep tfile mode info) (cleanup tfile) a where @@ -170,6 +172,7 @@ readTransferInfo pid s = <*> pure (Just pid) <*> pure Nothing <*> pure Nothing + <*> pure Nothing <*> pure (if null filename then Nothing else Just filename) _ -> Nothing where From 2136ee4adbeba262dcf184e653e1e07acb02a2bd Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 5 Jul 2012 14:45:21 -0600 Subject: [PATCH 035/331] logic error --- Assistant/Threads/Transferrer.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs index 0562a607ce..29cc393f23 100644 --- a/Assistant/Threads/Transferrer.hs +++ b/Assistant/Threads/Transferrer.hs @@ -53,14 +53,14 @@ transfererThread st dstatus transferqueue = do shouldtransfer t info = do current <- currentTransfers <$> getDaemonStatus dstatus if M.member t current - then ifM (validtransfer t) + then return False + else ifM (validtransfer t) ( do adjustTransfers dstatus $ M.insertWith' const t info return True , return False ) - else return False validtransfer t | transferDirection t == Download = From 9eaba58dd9706fde7e0fb84364a16576db63a7e0 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 5 Jul 2012 16:07:49 -0600 Subject: [PATCH 036/331] run transfer with copy of annex state This should have made it run concurrently with other annex actions, but I'm still seeing it serialize. Perhaps I need to forkProcess? --- Assistant/ThreadedMonad.hs | 12 ++++++++++++ Assistant/Threads/Transferrer.hs | 2 +- 2 files changed, 13 insertions(+), 1 deletion(-) diff --git a/Assistant/ThreadedMonad.hs b/Assistant/ThreadedMonad.hs index 7b915e12c8..4e871ab676 100644 --- a/Assistant/ThreadedMonad.hs +++ b/Assistant/ThreadedMonad.hs @@ -36,3 +36,15 @@ withThreadState a = do - time. -} runThreadState :: ThreadState -> Annex a -> IO a runThreadState mvar a = modifyMVar mvar $ \state -> swap <$> Annex.run state a + +{- Runs an Annex action, using a copy of the state from the MVar. + - + - The state modified by the action is thrown away, so it's up to the + - action to perform any necessary shutdown tasks in order for state to not + - be lost. And it's up to the caller to resynchronise with any changes + - the action makes to eg, the git-annex branch. + -} +unsafeRunThreadState :: ThreadState -> Annex a -> IO a +unsafeRunThreadState mvar a = do + state <- readMVar mvar + Annex.eval state a diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs index 29cc393f23..0b47e97812 100644 --- a/Assistant/Threads/Transferrer.hs +++ b/Assistant/Threads/Transferrer.hs @@ -97,6 +97,6 @@ runTransfer st t info inthread a = do mvar <- newEmptyMVar void $ forkIO $ - runThreadState st a `E.finally` putMVar mvar () + unsafeRunThreadState st a `E.finally` putMVar mvar () void $ takeMVar mvar -- wait for transfer thread runThreadState st invalidateCache From a92f5589fcf5549832914fdee34596818bfdc583 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 5 Jul 2012 18:57:06 -0600 Subject: [PATCH 037/331] unfinished (and unbuildable) work toward separate transfer processes --- Assistant.hs | 24 ++++--- Assistant/Threads/Transferrer.hs | 103 ++++++++++++++----------------- Logs/Transfer.hs | 5 -- 3 files changed, 63 insertions(+), 69 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index e751b4ae8c..38ed539a1f 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -31,14 +31,15 @@ - them. - Thread 8: merger - Waits for pushes to be received from remotes, and merges the - - updated branches into the current branch. This uses inotify - - on .git/refs/heads, so there are additional inotify threads - - associated with it, too. + - updated branches into the current branch. + - (This uses inotify on .git/refs/heads, so there are additional + - inotify threads associated with it, too.) - Thread 9: transfer watcher - Watches for transfer information files being created and removed, - - and maintains the DaemonStatus currentTransfers map. This uses - - inotify on .git/annex/transfer/, so there are additional inotify - - threads associated with it, too. + - and maintains the DaemonStatus currentTransfers map and the + - TransferSlots QSemN. + - (This uses inotify on .git/annex/transfer/, so there are + - additional inotify threads associated with it, too.) - Thread 10: transferrer - Waits for Transfers to be queued and does them. - Thread 11: status logger @@ -66,6 +67,12 @@ - retrier blocks until they're available. - TransferQueue (STM TChan) - Transfers to make are indicated by writing to this channel. + - TransferSlots (QSemN) + - Count of the number of currently available transfer slots. + - Updated by the transfer watcher, this allows other threads + - to block until a slot is available. + - This MVar should only be manipulated from inside the Annex monad, + - which ensures it's accessed only after the ThreadState MVar. -} module Assistant where @@ -109,15 +116,16 @@ startDaemon assistant foreground commitchan <- newCommitChan pushmap <- newFailedPushMap transferqueue <- newTransferQueue + transferslots <- newTransferSlots mapM_ (void . forkIO) [ commitThread st changechan commitchan transferqueue dstatus , pushThread st dstatus commitchan pushmap , pushRetryThread st pushmap , mergeThread st - , transferWatcherThread st dstatus + , transferWatcherThread st dstatus transferslots + , transfererThread st dstatus transferqueue transferslots , daemonStatusThread st dstatus , sanityCheckerThread st dstatus transferqueue changechan - , transfererThread st dstatus transferqueue , watchThread st dstatus transferqueue changechan ] waitForTermination diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs index 0b47e97812..249e15cf26 100644 --- a/Assistant/Threads/Transferrer.hs +++ b/Assistant/Threads/Transferrer.hs @@ -14,6 +14,7 @@ import Assistant.TransferQueue import Logs.Transfer import Annex.Content import Annex.BranchState +import Utility.ThreadScheduler import Command import qualified Command.Move @@ -22,68 +23,58 @@ import Control.Concurrent import Data.Time.Clock import qualified Data.Map as M -{- Dispatches transfers from the queue. - - - - This is currently very simplistic, and runs only one transfer at a time. - -} +{- For now only one transfer is run at a time. -} +maxTransfers :: Int +maxTransfers = 1 + +{- Dispatches transfers from the queue. -} transfererThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> IO () -transfererThread st dstatus transferqueue = do - mypid <- getProcessID - mytid <- myThreadId - go mypid mytid +transfererThread st dstatus transferqueue = runEvery (Seconds 1) $ do + (t, info) <- getNextTransfer transferqueue + go =<< runThreadState st $ shouldTransfer t where - go mypid mytid = do - (t, info) <- getNextTransfer transferqueue + go Yes = runTransfer st t + go No = noop + go TooMany = waitTransfer >> go Yes - now <- getCurrentTime - let info' = info - { startedTime = Just now - , transferPid = Just mypid - , transferThread = Just mytid - } +data ShouldTransfer = Yes | Skip | TooMany - ifM (runThreadState st $ shouldtransfer t info') - ( runTransfer st t info' - , noop - ) - go mypid mytid - - -- Check if the transfer is already running, - -- and if not, add it to the TransferMap. - shouldtransfer t info = do - current <- currentTransfers <$> getDaemonStatus dstatus - if M.member t current - then return False - else ifM (validtransfer t) - ( do - adjustTransfers dstatus $ - M.insertWith' const t info - return True - , return False - ) - - validtransfer t +{- Checks if the requested transfer is already running, or + - the file to download is already present. + - + - There also may be too many transfers already running to service this + - transfer yet. -} +shouldTransfer :: DaemonStatusHandle -> Transfer -> Annex ShouldTransfer +shouldTransfer dstatus t = go =<< currentTransfers <$> getDaemonStatus dstatus + where + go m + | M.member t m = return Skip + | M.size m > maxTransfers = return TooMany | transferDirection t == Download = - not <$> inAnnex (transferKey t) - | otherwise = return True + ifM (inAnnex $ transferKey t) (No, Yes) + | otherwise = return Yes -{- A transfer is run in a separate thread, with a *copy* of the Annex +{- Waits for any of the transfers in the map to complete. -} +waitTransfer :: IO () +waitTransfer = error "TODO" +-- getProcessStatus True False pid +-- runThreadState st invalidateCache + +{- A transfer is run in a separate process, with a *copy* of the Annex - state. This is necessary to avoid blocking the rest of the assistant - on the transfer completing, and also to allow multiple transfers to run - at once. - - - However, it means that the transfer threads are responsible + - However, it means that the transfer processes are responsible - for doing any necessary shutdown cleanups, and that the parent - - thread's cache must be invalidated, as changes may have been made to the - - git-annex branch. + - thread's cache must be invalidated once a transfer completes, as + - changes may have been made to the git-annex branch. - - - Currently a minimal shutdown is done; the transfer threads are + - Currently a minimal shutdown is done; the transfer processes are - effectively running in oneshot mode, without committing changes to the - git-annex branch, and transfers should never queue git commands to run. - - - - Note: It is unsafe to call getDaemonStatus inside the transfer thread. -} -runTransfer :: ThreadState -> Transfer -> TransferInfo -> IO () +runTransfer :: ThreadState -> Transfer -> TransferInfo -> IO ProcessID runTransfer st t info | transferDirection t == Download = go Command.Move.fromStart | otherwise = go Command.Move.toStart @@ -91,12 +82,12 @@ runTransfer st t info go cmd = case (transferRemote info, associatedFile info) of (Nothing, _) -> noop (_, Nothing) -> noop - (Just remote, Just file) -> - inthread $ void $ doCommand $ - cmd remote False file (transferKey t) - inthread a = do - mvar <- newEmptyMVar - void $ forkIO $ - unsafeRunThreadState st a `E.finally` putMVar mvar () - void $ takeMVar mvar -- wait for transfer thread - runThreadState st invalidateCache + (Just remote, Just file) -> do + now <- getCurrentTime + pid <- forkProcess $ unsafeRunThreadState st $ + doCommand $ cmd remote False file (transferKey t) + adjustTransfers dstatus $ + M.insertWith' const t info + { startedTime = Just now + , transferPid = Just pid + } diff --git a/Logs/Transfer.hs b/Logs/Transfer.hs index 12ab8ff113..54f98da5cb 100644 --- a/Logs/Transfer.hs +++ b/Logs/Transfer.hs @@ -14,7 +14,6 @@ import qualified Git import Types.Remote import qualified Fields -import Control.Concurrent import System.Posix.Types import Data.Time.Clock @@ -36,7 +35,6 @@ data Transfer = Transfer data TransferInfo = TransferInfo { startedTime :: Maybe UTCTime , transferPid :: Maybe ProcessID - , transferThread :: Maybe ThreadId , transferRemote :: Maybe Remote , bytesComplete :: Maybe Integer , associatedFile :: Maybe FilePath @@ -79,7 +77,6 @@ transfer t file a = do info <- liftIO $ TransferInfo <$> (Just <$> getCurrentTime) <*> pure Nothing -- pid not stored in file, so omitted for speed - <*> pure Nothing -- threadid not stored in file, so omitted for speed <*> pure Nothing -- not 0; transfer may be resuming <*> pure Nothing <*> pure file @@ -158,7 +155,6 @@ writeTransferInfo :: TransferInfo -> String writeTransferInfo info = unlines -- transferPid is not included; instead obtained by looking at -- the process that locks the file. - -- transferThread is not included; not relevant for other processes [ show $ startedTime info -- bytesComplete is not included; changes too fast , fromMaybe "" $ associatedFile info -- comes last; arbitrary content @@ -172,7 +168,6 @@ readTransferInfo pid s = <*> pure (Just pid) <*> pure Nothing <*> pure Nothing - <*> pure Nothing <*> pure (if null filename then Nothing else Just filename) _ -> Nothing where From 721748135b80a20e78ddc780ffedb2c54b74c307 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 6 Jul 2012 14:42:45 -0400 Subject: [PATCH 038/331] fix build (almost) --- Assistant/Threads/Transferrer.hs | 33 ++++++++++++++++---------------- Assistant/TransferQueue.hs | 1 - 2 files changed, 16 insertions(+), 18 deletions(-) diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs index 249e15cf26..0d0bc6f6d3 100644 --- a/Assistant/Threads/Transferrer.hs +++ b/Assistant/Threads/Transferrer.hs @@ -13,13 +13,10 @@ import Assistant.DaemonStatus import Assistant.TransferQueue import Logs.Transfer import Annex.Content -import Annex.BranchState import Utility.ThreadScheduler import Command import qualified Command.Move -import Control.Exception as E -import Control.Concurrent import Data.Time.Clock import qualified Data.Map as M @@ -31,11 +28,11 @@ maxTransfers = 1 transfererThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> IO () transfererThread st dstatus transferqueue = runEvery (Seconds 1) $ do (t, info) <- getNextTransfer transferqueue - go =<< runThreadState st $ shouldTransfer t - where - go Yes = runTransfer st t - go No = noop - go TooMany = waitTransfer >> go Yes + c <- runThreadState st $ shouldTransfer dstatus t + case c of + Yes -> void $ runTransfer st dstatus t info + Skip -> noop + TooMany -> void $ waitTransfer >> runTransfer st dstatus t info data ShouldTransfer = Yes | Skip | TooMany @@ -51,7 +48,8 @@ shouldTransfer dstatus t = go =<< currentTransfers <$> getDaemonStatus dstatus | M.member t m = return Skip | M.size m > maxTransfers = return TooMany | transferDirection t == Download = - ifM (inAnnex $ transferKey t) (No, Yes) + ifM (inAnnex $ transferKey t) + (return Skip, return Yes) | otherwise = return Yes {- Waits for any of the transfers in the map to complete. -} @@ -74,8 +72,8 @@ waitTransfer = error "TODO" - effectively running in oneshot mode, without committing changes to the - git-annex branch, and transfers should never queue git commands to run. -} -runTransfer :: ThreadState -> Transfer -> TransferInfo -> IO ProcessID -runTransfer st t info +runTransfer :: ThreadState -> DaemonStatusHandle -> Transfer -> TransferInfo -> IO () +runTransfer st dstatus t info | transferDirection t == Download = go Command.Move.fromStart | otherwise = go Command.Move.toStart where @@ -84,10 +82,11 @@ runTransfer st t info (_, Nothing) -> noop (Just remote, Just file) -> do now <- getCurrentTime - pid <- forkProcess $ unsafeRunThreadState st $ + pid <- forkProcess $ unsafeRunThreadState st $ void $ doCommand $ cmd remote False file (transferKey t) - adjustTransfers dstatus $ - M.insertWith' const t info - { startedTime = Just now - , transferPid = Just pid - } + runThreadState st $ + adjustTransfers dstatus $ + M.insertWith' const t info + { startedTime = Just now + , transferPid = Just pid + } diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs index a35815ca16..bb65dbae5a 100644 --- a/Assistant/TransferQueue.hs +++ b/Assistant/TransferQueue.hs @@ -24,7 +24,6 @@ stubInfo :: AssociatedFile -> TransferInfo stubInfo f = TransferInfo { startedTime = Nothing , transferPid = Nothing - , transferThread = Nothing , transferRemote = Nothing , bytesComplete = Nothing , associatedFile = f From 8795a392c3f283d8e372cac3d82d29ca52c9cfb5 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 6 Jul 2012 16:30:55 -0400 Subject: [PATCH 039/331] fix --- Assistant/Threads/TransferWatcher.hs | 14 +++----------- 1 file changed, 3 insertions(+), 11 deletions(-) diff --git a/Assistant/Threads/TransferWatcher.hs b/Assistant/Threads/TransferWatcher.hs index f18d4e3f86..48c0c79ae5 100644 --- a/Assistant/Threads/TransferWatcher.hs +++ b/Assistant/Threads/TransferWatcher.hs @@ -47,13 +47,7 @@ runHandler st dstatus handler file filestatus = void $ do onErr :: Handler onErr _ _ msg _ = error msg -{- Called when a new transfer information file is written. - - - - When another thread of the assistant writes a transfer info file, - - this will notice that too, but should skip it, because the thread - - will be managing the transfer itself, and will have stored a more - - complete TransferInfo than is stored in the file. - -} +{- Called when a new transfer information file is written. -} onAdd :: Handler onAdd st dstatus file _ = case parseTransferFile file of Nothing -> noop @@ -62,10 +56,8 @@ onAdd st dstatus file _ = case parseTransferFile file of runThreadState st $ go t pid =<< checkTransfer t where go _ _ Nothing = noop -- transfer already finished - go t pid (Just info) - | transferPid info == Just pid = noop - | otherwise = adjustTransfers dstatus $ - M.insertWith' const t info + go t pid (Just info) = adjustTransfers dstatus $ + M.insertWith' const t info {- Called when a transfer information file is removed. -} onDel :: Handler From 430ad8ce85835e002a326b68813c51f85c91141e Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 6 Jul 2012 16:39:07 -0400 Subject: [PATCH 040/331] it builds again Currently nothing waits on transfer processes. (Second drive of the day fried. Not concentrating very well.) --- Assistant.hs | 3 ++- Assistant/Threads/Transferrer.hs | 11 +++++++---- Assistant/TransferSlots.hs | 30 ++++++++++++++++++++++++++++++ 3 files changed, 39 insertions(+), 5 deletions(-) create mode 100644 Assistant/TransferSlots.hs diff --git a/Assistant.hs b/Assistant.hs index 38ed539a1f..06484b0862 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -84,6 +84,7 @@ import Assistant.Changes import Assistant.Commits import Assistant.Pushes import Assistant.TransferQueue +import Assistant.TransferSlots import Assistant.Threads.Watcher import Assistant.Threads.Committer import Assistant.Threads.Pusher @@ -122,7 +123,7 @@ startDaemon assistant foreground , pushThread st dstatus commitchan pushmap , pushRetryThread st pushmap , mergeThread st - , transferWatcherThread st dstatus transferslots + , transferWatcherThread st dstatus , transfererThread st dstatus transferqueue transferslots , daemonStatusThread st dstatus , sanityCheckerThread st dstatus transferqueue changechan diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs index 0d0bc6f6d3..3e417e7ff5 100644 --- a/Assistant/Threads/Transferrer.hs +++ b/Assistant/Threads/Transferrer.hs @@ -11,6 +11,7 @@ import Common.Annex import Assistant.ThreadedMonad import Assistant.DaemonStatus import Assistant.TransferQueue +import Assistant.TransferSlots import Logs.Transfer import Annex.Content import Utility.ThreadScheduler @@ -25,14 +26,16 @@ maxTransfers :: Int maxTransfers = 1 {- Dispatches transfers from the queue. -} -transfererThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> IO () -transfererThread st dstatus transferqueue = runEvery (Seconds 1) $ do +transfererThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> TransferSlots -> IO () +transfererThread st dstatus transferqueue slots = runEvery (Seconds 1) $ do (t, info) <- getNextTransfer transferqueue c <- runThreadState st $ shouldTransfer dstatus t + let run = void $ inTransferSlot slots $ + runTransfer st dstatus t info case c of - Yes -> void $ runTransfer st dstatus t info + Yes -> run Skip -> noop - TooMany -> void $ waitTransfer >> runTransfer st dstatus t info + TooMany -> waitTransfer >> run data ShouldTransfer = Yes | Skip | TooMany diff --git a/Assistant/TransferSlots.hs b/Assistant/TransferSlots.hs new file mode 100644 index 0000000000..0e2bb98b0c --- /dev/null +++ b/Assistant/TransferSlots.hs @@ -0,0 +1,30 @@ +{- git-annex assistant transfer slots + - + - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Assistant.TransferSlots where + +import Control.Exception +import Control.Concurrent + +type TransferSlots = QSemN + +{- Number of concurrent transfers allowed to be run from the assistant. + - + - Transfers launched by other means, including by remote assistants, + - do not currently take up slots. + -} +numSlots :: Int +numSlots = 1 + +newTransferSlots :: IO TransferSlots +newTransferSlots = newQSemN numSlots + +{- Waits until a transfer slot becomes available, and runs a transfer + - action in the slot. + -} +inTransferSlot :: TransferSlots -> IO a -> IO a +inTransferSlot s = bracket_ (waitQSemN s 1) (signalQSemN s 1) From 3d30a45e72418927d55a31a4d3d7aa5cf0c5c365 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 6 Jul 2012 14:54:07 -0600 Subject: [PATCH 041/331] simplified background transferrs seem to work now --- Assistant/Threads/Transferrer.hs | 27 ++++++++------------------- 1 file changed, 8 insertions(+), 19 deletions(-) diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs index 3e417e7ff5..2d01855b4c 100644 --- a/Assistant/Threads/Transferrer.hs +++ b/Assistant/Threads/Transferrer.hs @@ -29,31 +29,20 @@ maxTransfers = 1 transfererThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> TransferSlots -> IO () transfererThread st dstatus transferqueue slots = runEvery (Seconds 1) $ do (t, info) <- getNextTransfer transferqueue - c <- runThreadState st $ shouldTransfer dstatus t - let run = void $ inTransferSlot slots $ - runTransfer st dstatus t info - case c of - Yes -> run - Skip -> noop - TooMany -> waitTransfer >> run - -data ShouldTransfer = Yes | Skip | TooMany + whenM (runThreadState st $ shouldTransfer dstatus t) $ + void $ inTransferSlot slots $ + runTransfer st dstatus t info {- Checks if the requested transfer is already running, or - - the file to download is already present. - - - - There also may be too many transfers already running to service this - - transfer yet. -} -shouldTransfer :: DaemonStatusHandle -> Transfer -> Annex ShouldTransfer + - the file to download is already present. -} +shouldTransfer :: DaemonStatusHandle -> Transfer -> Annex Bool shouldTransfer dstatus t = go =<< currentTransfers <$> getDaemonStatus dstatus where go m - | M.member t m = return Skip - | M.size m > maxTransfers = return TooMany + | M.member t m = return False | transferDirection t == Download = - ifM (inAnnex $ transferKey t) - (return Skip, return Yes) - | otherwise = return Yes + inAnnex $ transferKey t + | otherwise = return True {- Waits for any of the transfers in the map to complete. -} waitTransfer :: IO () From 4a107951442f30354fa90b0b31200a9fdc86ffca Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 6 Jul 2012 15:07:42 -0600 Subject: [PATCH 042/331] logic error --- Assistant/Threads/Transferrer.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs index 2d01855b4c..5bc47cfa67 100644 --- a/Assistant/Threads/Transferrer.hs +++ b/Assistant/Threads/Transferrer.hs @@ -41,7 +41,7 @@ shouldTransfer dstatus t = go =<< currentTransfers <$> getDaemonStatus dstatus go m | M.member t m = return False | transferDirection t == Download = - inAnnex $ transferKey t + not <$> inAnnex (transferKey t) | otherwise = return True {- Waits for any of the transfers in the map to complete. -} From 62876502c55958cd8f716d6676eb97825456d9b7 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 6 Jul 2012 16:44:13 -0600 Subject: [PATCH 043/331] wait on child transfer processes, and invalidate cache There's still a bug; if the child updates its transfer info file, then the data from it will superscede the TransferInfo, losing the info that we should wait on this child. --- Assistant/DaemonStatus.hs | 19 ++++++++++++++++--- Assistant/Threads/SanityChecker.hs | 4 ++-- Assistant/Threads/TransferWatcher.hs | 26 +++++++++++++++++++------- Assistant/Threads/Transferrer.hs | 7 +------ Assistant/Threads/Watcher.hs | 2 +- Assistant/TransferQueue.hs | 1 + Logs/Transfer.hs | 3 +++ 7 files changed, 43 insertions(+), 19 deletions(-) diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs index 40816bb1a7..64c441ceee 100644 --- a/Assistant/DaemonStatus.hs +++ b/Assistant/DaemonStatus.hs @@ -54,8 +54,11 @@ newDaemonStatus = DaemonStatus getDaemonStatus :: DaemonStatusHandle -> Annex DaemonStatus getDaemonStatus = liftIO . readMVar -modifyDaemonStatus :: DaemonStatusHandle -> (DaemonStatus -> DaemonStatus) -> Annex () -modifyDaemonStatus handle a = liftIO $ modifyMVar_ handle (return . a) +modifyDaemonStatus_ :: DaemonStatusHandle -> (DaemonStatus -> DaemonStatus) -> Annex () +modifyDaemonStatus_ handle a = liftIO $ modifyMVar_ handle (return . a) + +modifyDaemonStatus :: DaemonStatusHandle -> (DaemonStatus -> (DaemonStatus, b)) -> Annex b +modifyDaemonStatus handle a = liftIO $ modifyMVar handle (return . a) {- Load any previous daemon status file, and store it in the MVar for this - process to use as its DaemonStatus. Also gets current transfer status. -} @@ -137,5 +140,15 @@ tenMinutes = 10 * 60 {- Mutates the transfer map. -} adjustTransfers :: DaemonStatusHandle -> (TransferMap -> TransferMap) -> Annex () -adjustTransfers dstatus a = modifyDaemonStatus dstatus $ +adjustTransfers dstatus a = modifyDaemonStatus_ dstatus $ \s -> s { currentTransfers = a (currentTransfers s) } + +{- Removes a transfer from the map, and returns its info. -} +removeTransfer :: DaemonStatusHandle -> Transfer -> Annex (Maybe TransferInfo) +removeTransfer dstatus t = modifyDaemonStatus dstatus go + where + go s = + let (info, ts) = M.updateLookupWithKey + (\_k _v -> Nothing) + t (currentTransfers s) + in (s { currentTransfers = ts }, info) diff --git a/Assistant/Threads/SanityChecker.hs b/Assistant/Threads/SanityChecker.hs index d7b117cd02..c5b99863e3 100644 --- a/Assistant/Threads/SanityChecker.hs +++ b/Assistant/Threads/SanityChecker.hs @@ -26,7 +26,7 @@ sanityCheckerThread st status transferqueue changechan = forever $ do waitForNextCheck st status runThreadState st $ - modifyDaemonStatus status $ \s -> s + modifyDaemonStatus_ status $ \s -> s { sanityCheckRunning = True } now <- getPOSIXTime -- before check started @@ -34,7 +34,7 @@ sanityCheckerThread st status transferqueue changechan = forever $ do (runThreadState st . warning . show) runThreadState st $ do - modifyDaemonStatus status $ \s -> s + modifyDaemonStatus_ status $ \s -> s { sanityCheckRunning = False , lastSanityCheck = Just now } diff --git a/Assistant/Threads/TransferWatcher.hs b/Assistant/Threads/TransferWatcher.hs index 48c0c79ae5..4e468a4165 100644 --- a/Assistant/Threads/TransferWatcher.hs +++ b/Assistant/Threads/TransferWatcher.hs @@ -13,6 +13,7 @@ import Assistant.DaemonStatus import Logs.Transfer import Utility.DirWatcher import Utility.Types.DirWatcher +import Annex.BranchState import Data.Map as M @@ -51,16 +52,27 @@ onErr _ _ msg _ = error msg onAdd :: Handler onAdd st dstatus file _ = case parseTransferFile file of Nothing -> noop - Just t -> do - pid <- getProcessID - runThreadState st $ go t pid =<< checkTransfer t + Just t -> runThreadState st $ go t =<< checkTransfer t where - go _ _ Nothing = noop -- transfer already finished - go t pid (Just info) = adjustTransfers dstatus $ + go _ Nothing = noop -- transfer already finished + go t (Just info) = adjustTransfers dstatus $ M.insertWith' const t info -{- Called when a transfer information file is removed. -} +{- Called when a transfer information file is removed. + - + - When the transfer process is a child of this process, wait on it + - to avoid zombies. + -} onDel :: Handler onDel st dstatus file _ = case parseTransferFile file of Nothing -> noop - Just t -> runThreadState st $ adjustTransfers dstatus $ M.delete t + Just t -> maybe noop waitchild + =<< runThreadState st (removeTransfer dstatus t) + where + waitchild info + | shouldWait info = case transferPid info of + Nothing -> noop + Just pid -> do + void $ getProcessStatus True False pid + runThreadState st invalidateCache + | otherwise = noop diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs index 5bc47cfa67..09c0aa0369 100644 --- a/Assistant/Threads/Transferrer.hs +++ b/Assistant/Threads/Transferrer.hs @@ -44,12 +44,6 @@ shouldTransfer dstatus t = go =<< currentTransfers <$> getDaemonStatus dstatus not <$> inAnnex (transferKey t) | otherwise = return True -{- Waits for any of the transfers in the map to complete. -} -waitTransfer :: IO () -waitTransfer = error "TODO" --- getProcessStatus True False pid --- runThreadState st invalidateCache - {- A transfer is run in a separate process, with a *copy* of the Annex - state. This is necessary to avoid blocking the rest of the assistant - on the transfer completing, and also to allow multiple transfers to run @@ -81,4 +75,5 @@ runTransfer st dstatus t info M.insertWith' const t info { startedTime = Just now , transferPid = Just pid + , shouldWait = True } diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs index 882aab3a78..9f0eba74e9 100644 --- a/Assistant/Threads/Watcher.hs +++ b/Assistant/Threads/Watcher.hs @@ -67,7 +67,7 @@ statupScan st dstatus scanner = do showAction "scanning" r <- scanner runThreadState st $ - modifyDaemonStatus dstatus $ \s -> s { scanComplete = True } + modifyDaemonStatus_ dstatus $ \s -> s { scanComplete = True } -- Notice any files that were deleted before watching was started. runThreadState st $ do diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs index bb65dbae5a..5e1fad4560 100644 --- a/Assistant/TransferQueue.hs +++ b/Assistant/TransferQueue.hs @@ -27,6 +27,7 @@ stubInfo f = TransferInfo , transferRemote = Nothing , bytesComplete = Nothing , associatedFile = f + , shouldWait = False } {- Adds pending transfers to the end of the queue for some of the known diff --git a/Logs/Transfer.hs b/Logs/Transfer.hs index 54f98da5cb..494a44c51b 100644 --- a/Logs/Transfer.hs +++ b/Logs/Transfer.hs @@ -38,6 +38,7 @@ data TransferInfo = TransferInfo , transferRemote :: Maybe Remote , bytesComplete :: Maybe Integer , associatedFile :: Maybe FilePath + , shouldWait :: Bool } deriving (Show, Eq, Ord) @@ -80,6 +81,7 @@ transfer t file a = do <*> pure Nothing -- not 0; transfer may be resuming <*> pure Nothing <*> pure file + <*> pure False bracketIO (prep tfile mode info) (cleanup tfile) a where prep tfile mode info = do @@ -169,6 +171,7 @@ readTransferInfo pid s = <*> pure Nothing <*> pure Nothing <*> pure (if null filename then Nothing else Just filename) + <*> pure False _ -> Nothing where (bits, filebits) = splitAt 1 $ lines s From d954a0ce5934a877f8df0c683eaccaf8c2b1938e Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 6 Jul 2012 18:48:51 -0600 Subject: [PATCH 044/331] fixed close-together transfer race The issue involved forking and they trying to read from a MVar. Reading the MVar 1st fixed it. --- Assistant/ThreadedMonad.hs | 17 +++++++++-------- Assistant/Threads/Transferrer.hs | 16 +++++++++------- 2 files changed, 18 insertions(+), 15 deletions(-) diff --git a/Assistant/ThreadedMonad.hs b/Assistant/ThreadedMonad.hs index 4e871ab676..16f3a9dd9f 100644 --- a/Assistant/ThreadedMonad.hs +++ b/Assistant/ThreadedMonad.hs @@ -12,6 +12,7 @@ import qualified Annex import Control.Concurrent import Data.Tuple +import System.Posix.Types {- The Annex state is stored in a MVar, so that threaded actions can access - it. -} @@ -37,14 +38,14 @@ withThreadState a = do runThreadState :: ThreadState -> Annex a -> IO a runThreadState mvar a = modifyMVar mvar $ \state -> swap <$> Annex.run state a -{- Runs an Annex action, using a copy of the state from the MVar. +{- Runs an Annex action in a separate process, using a copy of the state + - from the MVar. - - - The state modified by the action is thrown away, so it's up to the - - action to perform any necessary shutdown tasks in order for state to not - - be lost. And it's up to the caller to resynchronise with any changes - - the action makes to eg, the git-annex branch. + - It's up to the action to perform any necessary shutdown tasks in order + - for state to not be lost. And it's up to the caller to resynchronise + - with any changes the action makes to eg, the git-annex branch. -} -unsafeRunThreadState :: ThreadState -> Annex a -> IO a -unsafeRunThreadState mvar a = do +unsafeForkProcessThreadState :: ThreadState -> Annex a -> IO ProcessID +unsafeForkProcessThreadState mvar a = do state <- readMVar mvar - Annex.eval state a + forkProcess $ void $ Annex.eval state a diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs index 09c0aa0369..f40218c08d 100644 --- a/Assistant/Threads/Transferrer.hs +++ b/Assistant/Threads/Transferrer.hs @@ -14,7 +14,6 @@ import Assistant.TransferQueue import Assistant.TransferSlots import Logs.Transfer import Annex.Content -import Utility.ThreadScheduler import Command import qualified Command.Move @@ -27,11 +26,14 @@ maxTransfers = 1 {- Dispatches transfers from the queue. -} transfererThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> TransferSlots -> IO () -transfererThread st dstatus transferqueue slots = runEvery (Seconds 1) $ do - (t, info) <- getNextTransfer transferqueue - whenM (runThreadState st $ shouldTransfer dstatus t) $ - void $ inTransferSlot slots $ - runTransfer st dstatus t info +transfererThread st dstatus transferqueue slots = go + where + go = do + (t, info) <- getNextTransfer transferqueue + whenM (runThreadState st $ shouldTransfer dstatus t) $ + void $ inTransferSlot slots $ + runTransfer st dstatus t info + go {- Checks if the requested transfer is already running, or - the file to download is already present. -} @@ -68,7 +70,7 @@ runTransfer st dstatus t info (_, Nothing) -> noop (Just remote, Just file) -> do now <- getCurrentTime - pid <- forkProcess $ unsafeRunThreadState st $ void $ + pid <- unsafeForkProcessThreadState st $ doCommand $ cmd remote False file (transferKey t) runThreadState st $ adjustTransfers dstatus $ From 94b06deb64c7152aef718cb26ed804266902a6a9 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 6 Jul 2012 21:45:08 -0600 Subject: [PATCH 045/331] fix transfer slots blocking and refilling when transfers are stopped --- Assistant.hs | 2 +- Assistant/Threads/TransferWatcher.hs | 25 ++++++++++++++----------- Assistant/TransferSlots.hs | 13 +++++++++++-- 3 files changed, 26 insertions(+), 14 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index 06484b0862..91ebf2d2e0 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -123,7 +123,7 @@ startDaemon assistant foreground , pushThread st dstatus commitchan pushmap , pushRetryThread st pushmap , mergeThread st - , transferWatcherThread st dstatus + , transferWatcherThread st dstatus transferslots , transfererThread st dstatus transferqueue transferslots , daemonStatusThread st dstatus , sanityCheckerThread st dstatus transferqueue changechan diff --git a/Assistant/Threads/TransferWatcher.hs b/Assistant/Threads/TransferWatcher.hs index 4e468a4165..aa8b3f6e68 100644 --- a/Assistant/Threads/TransferWatcher.hs +++ b/Assistant/Threads/TransferWatcher.hs @@ -10,6 +10,7 @@ module Assistant.Threads.TransferWatcher where import Common.Annex import Assistant.ThreadedMonad import Assistant.DaemonStatus +import Assistant.TransferSlots import Logs.Transfer import Utility.DirWatcher import Utility.Types.DirWatcher @@ -19,12 +20,12 @@ import Data.Map as M {- This thread watches for changes to the gitAnnexTransferDir, - and updates the DaemonStatus's map of ongoing transfers. -} -transferWatcherThread :: ThreadState -> DaemonStatusHandle -> IO () -transferWatcherThread st dstatus = do +transferWatcherThread :: ThreadState -> DaemonStatusHandle -> TransferSlots -> IO () +transferWatcherThread st dstatus transferslots = do g <- runThreadState st $ fromRepo id let dir = gitAnnexTransferDir g createDirectoryIfMissing True dir - let hook a = Just $ runHandler st dstatus a + let hook a = Just $ runHandler st dstatus transferslots a let hooks = mkWatchHooks { addHook = hook onAdd , delHook = hook onDel @@ -32,25 +33,25 @@ transferWatcherThread st dstatus = do } void $ watchDir dir (const False) hooks id -type Handler = ThreadState -> DaemonStatusHandle -> FilePath -> Maybe FileStatus -> IO () +type Handler = ThreadState -> DaemonStatusHandle -> TransferSlots -> FilePath -> Maybe FileStatus -> IO () {- Runs an action handler. - - Exceptions are ignored, otherwise a whole thread could be crashed. -} -runHandler :: ThreadState -> DaemonStatusHandle -> Handler -> FilePath -> Maybe FileStatus -> IO () -runHandler st dstatus handler file filestatus = void $ do +runHandler :: ThreadState -> DaemonStatusHandle -> TransferSlots -> Handler -> FilePath -> Maybe FileStatus -> IO () +runHandler st dstatus transferslots handler file filestatus = void $ do either print (const noop) =<< tryIO go where - go = handler st dstatus file filestatus + go = handler st dstatus transferslots file filestatus {- Called when there's an error with inotify. -} onErr :: Handler -onErr _ _ msg _ = error msg +onErr _ _ _ msg _ = error msg {- Called when a new transfer information file is written. -} onAdd :: Handler -onAdd st dstatus file _ = case parseTransferFile file of +onAdd st dstatus _ file _ = case parseTransferFile file of Nothing -> noop Just t -> runThreadState st $ go t =<< checkTransfer t where @@ -64,7 +65,7 @@ onAdd st dstatus file _ = case parseTransferFile file of - to avoid zombies. -} onDel :: Handler -onDel st dstatus file _ = case parseTransferFile file of +onDel st dstatus transferslots file _ = case parseTransferFile file of Nothing -> noop Just t -> maybe noop waitchild =<< runThreadState st (removeTransfer dstatus t) @@ -73,6 +74,8 @@ onDel st dstatus file _ = case parseTransferFile file of | shouldWait info = case transferPid info of Nothing -> noop Just pid -> do - void $ getProcessStatus True False pid + void $ tryIO $ + getProcessStatus True False pid runThreadState st invalidateCache + transferComplete transferslots | otherwise = noop diff --git a/Assistant/TransferSlots.hs b/Assistant/TransferSlots.hs index 0e2bb98b0c..3dc7917e42 100644 --- a/Assistant/TransferSlots.hs +++ b/Assistant/TransferSlots.hs @@ -24,7 +24,16 @@ newTransferSlots :: IO TransferSlots newTransferSlots = newQSemN numSlots {- Waits until a transfer slot becomes available, and runs a transfer - - action in the slot. + - action in the slot. If the action throws an exception, its slot is + - freed here, otherwise it should be freed by the TransferWatcher when + - the transfer is complete. -} inTransferSlot :: TransferSlots -> IO a -> IO a -inTransferSlot s = bracket_ (waitQSemN s 1) (signalQSemN s 1) +inTransferSlot s a = bracketOnError + (waitQSemN s 1) + (const $ signalQSemN s 1) + (const a) + +{- Call when a transfer is complete. -} +transferComplete :: TransferSlots -> IO () +transferComplete s = signalQSemN s 1 From cc6f660752d4eef1e667f1ac859c6140f4da87ca Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 6 Jul 2012 21:45:08 -0600 Subject: [PATCH 046/331] fix transfer slots blocking and refilling when transfers are stopped There's a bug, if a transfer process notices it needs to do nothing, it never starts the transfer, so the slot is never freed. --- Assistant.hs | 2 +- Assistant/Threads/TransferWatcher.hs | 25 ++++++++++++++----------- Assistant/TransferSlots.hs | 14 ++++++++++++-- 3 files changed, 27 insertions(+), 14 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index 06484b0862..91ebf2d2e0 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -123,7 +123,7 @@ startDaemon assistant foreground , pushThread st dstatus commitchan pushmap , pushRetryThread st pushmap , mergeThread st - , transferWatcherThread st dstatus + , transferWatcherThread st dstatus transferslots , transfererThread st dstatus transferqueue transferslots , daemonStatusThread st dstatus , sanityCheckerThread st dstatus transferqueue changechan diff --git a/Assistant/Threads/TransferWatcher.hs b/Assistant/Threads/TransferWatcher.hs index 4e468a4165..aa8b3f6e68 100644 --- a/Assistant/Threads/TransferWatcher.hs +++ b/Assistant/Threads/TransferWatcher.hs @@ -10,6 +10,7 @@ module Assistant.Threads.TransferWatcher where import Common.Annex import Assistant.ThreadedMonad import Assistant.DaemonStatus +import Assistant.TransferSlots import Logs.Transfer import Utility.DirWatcher import Utility.Types.DirWatcher @@ -19,12 +20,12 @@ import Data.Map as M {- This thread watches for changes to the gitAnnexTransferDir, - and updates the DaemonStatus's map of ongoing transfers. -} -transferWatcherThread :: ThreadState -> DaemonStatusHandle -> IO () -transferWatcherThread st dstatus = do +transferWatcherThread :: ThreadState -> DaemonStatusHandle -> TransferSlots -> IO () +transferWatcherThread st dstatus transferslots = do g <- runThreadState st $ fromRepo id let dir = gitAnnexTransferDir g createDirectoryIfMissing True dir - let hook a = Just $ runHandler st dstatus a + let hook a = Just $ runHandler st dstatus transferslots a let hooks = mkWatchHooks { addHook = hook onAdd , delHook = hook onDel @@ -32,25 +33,25 @@ transferWatcherThread st dstatus = do } void $ watchDir dir (const False) hooks id -type Handler = ThreadState -> DaemonStatusHandle -> FilePath -> Maybe FileStatus -> IO () +type Handler = ThreadState -> DaemonStatusHandle -> TransferSlots -> FilePath -> Maybe FileStatus -> IO () {- Runs an action handler. - - Exceptions are ignored, otherwise a whole thread could be crashed. -} -runHandler :: ThreadState -> DaemonStatusHandle -> Handler -> FilePath -> Maybe FileStatus -> IO () -runHandler st dstatus handler file filestatus = void $ do +runHandler :: ThreadState -> DaemonStatusHandle -> TransferSlots -> Handler -> FilePath -> Maybe FileStatus -> IO () +runHandler st dstatus transferslots handler file filestatus = void $ do either print (const noop) =<< tryIO go where - go = handler st dstatus file filestatus + go = handler st dstatus transferslots file filestatus {- Called when there's an error with inotify. -} onErr :: Handler -onErr _ _ msg _ = error msg +onErr _ _ _ msg _ = error msg {- Called when a new transfer information file is written. -} onAdd :: Handler -onAdd st dstatus file _ = case parseTransferFile file of +onAdd st dstatus _ file _ = case parseTransferFile file of Nothing -> noop Just t -> runThreadState st $ go t =<< checkTransfer t where @@ -64,7 +65,7 @@ onAdd st dstatus file _ = case parseTransferFile file of - to avoid zombies. -} onDel :: Handler -onDel st dstatus file _ = case parseTransferFile file of +onDel st dstatus transferslots file _ = case parseTransferFile file of Nothing -> noop Just t -> maybe noop waitchild =<< runThreadState st (removeTransfer dstatus t) @@ -73,6 +74,8 @@ onDel st dstatus file _ = case parseTransferFile file of | shouldWait info = case transferPid info of Nothing -> noop Just pid -> do - void $ getProcessStatus True False pid + void $ tryIO $ + getProcessStatus True False pid runThreadState st invalidateCache + transferComplete transferslots | otherwise = noop diff --git a/Assistant/TransferSlots.hs b/Assistant/TransferSlots.hs index 0e2bb98b0c..1859b281bb 100644 --- a/Assistant/TransferSlots.hs +++ b/Assistant/TransferSlots.hs @@ -24,7 +24,17 @@ newTransferSlots :: IO TransferSlots newTransferSlots = newQSemN numSlots {- Waits until a transfer slot becomes available, and runs a transfer - - action in the slot. + - action in the slot. If the action throws an exception, its slot is + - freed here, otherwise it should be freed by the TransferWatcher when + - the transfer is complete. -} inTransferSlot :: TransferSlots -> IO a -> IO a -inTransferSlot s = bracket_ (waitQSemN s 1) (signalQSemN s 1) +inTransferSlot s a = bracketOnError start abort run + where + start = waitQSemN s 1 + abort = const $ transferComplete s + run = const a + +{- Call when a transfer is complete. -} +transferComplete :: TransferSlots -> IO () +transferComplete s = signalQSemN s 1 From cd168c6cba2ce6d938a4533abf783286addb16b0 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sat, 7 Jul 2012 10:50:20 -0600 Subject: [PATCH 047/331] fix transferrer thread's use of transfer slots and transfer info files Check first if a transfer needs to be done, using the location log only (for speed), and avoid occupying a slot if not. Always write a transfer info file, and keep it open throughout the tranfer process. Now transfers to remotes seem reliable. --- Assistant/Threads/Transferrer.hs | 77 ++++++++++++++++++++------------ 1 file changed, 49 insertions(+), 28 deletions(-) diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs index f40218c08d..aaf654d34b 100644 --- a/Assistant/Threads/Transferrer.hs +++ b/Assistant/Threads/Transferrer.hs @@ -13,9 +13,10 @@ import Assistant.DaemonStatus import Assistant.TransferQueue import Assistant.TransferSlots import Logs.Transfer +import Logs.Presence +import Logs.Location import Annex.Content -import Command -import qualified Command.Move +import qualified Remote import Data.Time.Clock import qualified Data.Map as M @@ -31,8 +32,7 @@ transfererThread st dstatus transferqueue slots = go go = do (t, info) <- getNextTransfer transferqueue whenM (runThreadState st $ shouldTransfer dstatus t) $ - void $ inTransferSlot slots $ - runTransfer st dstatus t info + runTransfer st dstatus slots t info go {- Checks if the requested transfer is already running, or @@ -49,33 +49,54 @@ shouldTransfer dstatus t = go =<< currentTransfers <$> getDaemonStatus dstatus {- A transfer is run in a separate process, with a *copy* of the Annex - state. This is necessary to avoid blocking the rest of the assistant - on the transfer completing, and also to allow multiple transfers to run - - at once. + - at once. - - However, it means that the transfer processes are responsible - for doing any necessary shutdown cleanups, and that the parent - thread's cache must be invalidated once a transfer completes, as - - changes may have been made to the git-annex branch. - - - - Currently a minimal shutdown is done; the transfer processes are - - effectively running in oneshot mode, without committing changes to the - - git-annex branch, and transfers should never queue git commands to run. + - changes may have been made to the git-annex branch. -} -runTransfer :: ThreadState -> DaemonStatusHandle -> Transfer -> TransferInfo -> IO () -runTransfer st dstatus t info - | transferDirection t == Download = go Command.Move.fromStart - | otherwise = go Command.Move.toStart +runTransfer :: ThreadState -> DaemonStatusHandle -> TransferSlots -> Transfer -> TransferInfo -> IO () +runTransfer st dstatus slots t info = case (transferRemote info, associatedFile info) of + (Nothing, _) -> noop + (_, Nothing) -> noop + (Just remote, Just file) -> whenM (shouldtransfer remote) $ do + pid <- inTransferSlot slots $ + unsafeForkProcessThreadState st $ + transferprocess remote file + now <- getCurrentTime + runThreadState st $ adjustTransfers dstatus $ + M.insertWith' const t info + { startedTime = Just now + , transferPid = Just pid + , shouldWait = True + } where - go cmd = case (transferRemote info, associatedFile info) of - (Nothing, _) -> noop - (_, Nothing) -> noop - (Just remote, Just file) -> do - now <- getCurrentTime - pid <- unsafeForkProcessThreadState st $ - doCommand $ cmd remote False file (transferKey t) - runThreadState st $ - adjustTransfers dstatus $ - M.insertWith' const t info - { startedTime = Just now - , transferPid = Just pid - , shouldWait = True - } + isdownload = transferDirection t == Download + tofrom + | isdownload = "from" + | otherwise = "to" + key = transferKey t + + shouldtransfer remote + | isdownload = return True + | otherwise = runThreadState st $ + {- Trust the location log to check if the + - remote already has the key. This avoids + - a roundtrip to the remote. -} + notElem (Remote.uuid remote) + <$> loggedLocations key + + transferprocess remote file = do + showStart "copy" file + showAction $ tofrom ++ " " ++ Remote.name remote + ok <- transfer t (Just file) $ + if isdownload + then getViaTmp key $ + Remote.retrieveKeyFile remote key (Just file) + else do + ok <- Remote.storeKey remote key $ Just file + when ok $ + Remote.logStatus remote key InfoPresent + return ok + showEndResult ok From c8691d76aa9a438c17a1c15ac01495d782fa84db Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sat, 7 Jul 2012 11:17:20 -0600 Subject: [PATCH 048/331] bugfix --- Assistant/Threads/TransferWatcher.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/Assistant/Threads/TransferWatcher.hs b/Assistant/Threads/TransferWatcher.hs index aa8b3f6e68..5be63fce4f 100644 --- a/Assistant/Threads/TransferWatcher.hs +++ b/Assistant/Threads/TransferWatcher.hs @@ -57,7 +57,9 @@ onAdd st dstatus _ file _ = case parseTransferFile file of where go _ Nothing = noop -- transfer already finished go t (Just info) = adjustTransfers dstatus $ - M.insertWith' const t info + M.insertWith' merge t info + -- preseve shouldWait flag, which is not written to disk + merge new old = new { shouldWait = shouldWait old } {- Called when a transfer information file is removed. - From 9379c77fb304a878481ba1366e055dc726ad2954 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sat, 7 Jul 2012 11:47:36 -0600 Subject: [PATCH 049/331] split transfer info and lock files Since the lock file has to be kept open, this prevented the TransferWatcher from noticing when it appeared, since inotify (and more importantly kqueue) events happen when a new file is closed. Writing a separate info file fixes that problem. --- Logs/Transfer.hs | 42 +++++++++++++++++++++--------------------- 1 file changed, 21 insertions(+), 21 deletions(-) diff --git a/Logs/Transfer.hs b/Logs/Transfer.hs index 494a44c51b..8b88041273 100644 --- a/Logs/Transfer.hs +++ b/Logs/Transfer.hs @@ -1,4 +1,4 @@ -{- git-annex transfer information files +{- git-annex transfer information files and lock files - - Copyright 2012 Joey Hess - @@ -66,9 +66,9 @@ fieldTransfer direction key a = do maybe a (\u -> transfer (Transfer direction (toUUID u) key) afile a) =<< Fields.getField Fields.remoteUUID -{- Runs a transfer action. Creates and locks the transfer information file - - while the action is running. Will throw an error if the transfer is - - already in progress. +{- Runs a transfer action. Creates and locks the lock file while the + - action is running, and stores into in the transfer information + - file. Will throw an error if the transfer is already in progress. -} transfer :: Transfer -> Maybe FilePath -> Annex a -> Annex a transfer t file a = do @@ -85,19 +85,18 @@ transfer t file a = do bracketIO (prep tfile mode info) (cleanup tfile) a where prep tfile mode info = do - fd <- openFd tfile ReadWrite (Just mode) + fd <- openFd (transferLockFile tfile) ReadWrite (Just mode) defaultFileFlags { trunc = True } locked <- catchMaybeIO $ setLock fd (WriteLock, AbsoluteSeek, 0, 0) when (locked == Nothing) $ error $ "transfer already in progress" - h <- fdToHandle fd - hPutStr h $ writeTransferInfo info - hFlush h - return h - cleanup tfile h = do + writeFile tfile $ writeTransferInfo info + return fd + cleanup tfile fd = do removeFile tfile - hClose h + removeFile $ transferLockFile tfile + closeFd fd {- If a transfer is still running, returns its TransferInfo. -} checkTransfer :: Transfer -> Annex (Maybe TransferInfo) @@ -105,22 +104,19 @@ checkTransfer t = do mode <- annexFileMode tfile <- fromRepo $ transferFile t mfd <- liftIO $ catchMaybeIO $ - openFd tfile ReadOnly (Just mode) defaultFileFlags + openFd (transferLockFile tfile) ReadOnly (Just mode) defaultFileFlags case mfd of Nothing -> return Nothing -- failed to open file; not running Just fd -> do locked <- liftIO $ getLock fd (WriteLock, AbsoluteSeek, 0, 0) + liftIO $ closeFd fd case locked of - Nothing -> do - liftIO $ closeFd fd - return Nothing - Just (pid, _) -> liftIO $ do - h <- fdToHandle fd - info <- readTransferInfo pid - <$> hGetContentsStrict h - hClose h - return info + Nothing -> return Nothing + Just (pid, _) -> liftIO $ + flip catchDefaultIO Nothing $ + readTransferInfo pid + <$> readFile tfile {- Gets all currently running transfers. -} getTransfers :: Annex [(Transfer, TransferInfo)] @@ -141,6 +137,10 @@ transferFile (Transfer direction u key) r = gitAnnexTransferDir r fromUUID u keyFile key +{- The transfer lock file corresponding to a given transfer info file. -} +transferLockFile :: FilePath -> FilePath +transferLockFile infofile = infofile ++ ".lck" + {- Parses a transfer information filename to a Transfer. -} parseTransferFile :: FilePath -> Maybe Transfer parseTransferFile file = From b7d3cefde9a82a7a5bab90eb621690fc969da5ea Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Tue, 17 Jul 2012 12:06:35 -0400 Subject: [PATCH 050/331] merge two shouldTransfer checks --- Assistant/Threads/Transferrer.hs | 35 +++++++++++++++++--------------- 1 file changed, 19 insertions(+), 16 deletions(-) diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs index aaf654d34b..9d3358f546 100644 --- a/Assistant/Threads/Transferrer.hs +++ b/Assistant/Threads/Transferrer.hs @@ -31,20 +31,32 @@ transfererThread st dstatus transferqueue slots = go where go = do (t, info) <- getNextTransfer transferqueue - whenM (runThreadState st $ shouldTransfer dstatus t) $ + whenM (runThreadState st $ shouldTransfer dstatus t info) $ runTransfer st dstatus slots t info go {- Checks if the requested transfer is already running, or - - the file to download is already present. -} -shouldTransfer :: DaemonStatusHandle -> Transfer -> Annex Bool -shouldTransfer dstatus t = go =<< currentTransfers <$> getDaemonStatus dstatus + - the file to download is already present, or the remote + - being uploaded to isn't known to have the file. -} +shouldTransfer :: DaemonStatusHandle -> Transfer -> TransferInfo -> Annex Bool +shouldTransfer dstatus t info = + go =<< currentTransfers <$> getDaemonStatus dstatus where go m | M.member t m = return False | transferDirection t == Download = - not <$> inAnnex (transferKey t) - | otherwise = return True + not <$> inAnnex key + | transferDirection t == Upload = + {- Trust the location log to check if the + - remote already has the key. This avoids + - a roundtrip to the remote. -} + case transferRemote info of + Nothing -> return False + Just remote -> + notElem (Remote.uuid remote) + <$> loggedLocations key + | otherwise = return False + key = transferKey t {- A transfer is run in a separate process, with a *copy* of the Annex - state. This is necessary to avoid blocking the rest of the assistant @@ -60,7 +72,7 @@ runTransfer :: ThreadState -> DaemonStatusHandle -> TransferSlots -> Transfer -> runTransfer st dstatus slots t info = case (transferRemote info, associatedFile info) of (Nothing, _) -> noop (_, Nothing) -> noop - (Just remote, Just file) -> whenM (shouldtransfer remote) $ do + (Just remote, Just file) -> do pid <- inTransferSlot slots $ unsafeForkProcessThreadState st $ transferprocess remote file @@ -78,15 +90,6 @@ runTransfer st dstatus slots t info = case (transferRemote info, associatedFile | otherwise = "to" key = transferKey t - shouldtransfer remote - | isdownload = return True - | otherwise = runThreadState st $ - {- Trust the location log to check if the - - remote already has the key. This avoids - - a roundtrip to the remote. -} - notElem (Remote.uuid remote) - <$> loggedLocations key - transferprocess remote file = do showStart "copy" file showAction $ tofrom ++ " " ++ Remote.name remote From c34d8ae088e284b7585b7e32330945d1e9c922f2 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Tue, 17 Jul 2012 12:17:01 -0400 Subject: [PATCH 051/331] avoid enqueing downloads from remotes that don't have the key --- Assistant/TransferQueue.hs | 22 +++++++++++----------- 1 file changed, 11 insertions(+), 11 deletions(-) diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs index 5e1fad4560..73e73ca0af 100644 --- a/Assistant/TransferQueue.hs +++ b/Assistant/TransferQueue.hs @@ -33,24 +33,24 @@ stubInfo f = TransferInfo {- Adds pending transfers to the end of the queue for some of the known - remotes. -} queueTransfers :: TransferQueue -> DaemonStatusHandle -> Key -> AssociatedFile -> Direction -> Annex () -queueTransfers q daemonstatus k f direction = +queueTransfers q daemonstatus k f direction = do + rs <- knownRemotes <$> getDaemonStatus daemonstatus mapM_ (\r -> queue r $ gentransfer r) - =<< sufficientremotes . knownRemotes - <$> getDaemonStatus daemonstatus + =<< sufficientremotes rs where sufficientremotes l - -- Queue downloads from all remotes, with the - -- cheapest ones first. More expensive ones will - -- only be tried if downloading from a cheap one - -- fails. - -- TODO: avoid downloading from remotes that don't - -- have the key. - | direction == Download = l + -- Queue downloads from all remotes that + -- have the key, with the cheapest ones first. + -- More expensive ones will only be tried if + -- downloading from a cheap one fails. + | direction == Download = do + uuids <- Remote.keyLocations k + return $ filter (\r -> uuid r `elem` uuids) l -- TODO: Determine a smaller set of remotes that -- can be uploaded to, in order to ensure all -- remotes can access the content. Currently, -- send to every remote we can. - | otherwise = l + | otherwise = return l gentransfer r = Transfer { transferDirection = direction , transferKey = k From 1d5582091e9df550a8b42d0a69bada1d15a1825e Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Tue, 17 Jul 2012 13:37:55 -0400 Subject: [PATCH 052/331] attempt at building with -threaded Added a modified System.Cmd.Utils, working around bug #681621 Unfortunatly, the test suite still hangs partway through. Some of the hangs occur within pOpen3 still. Some of the hangs do not seem to occur within System.Cmd.Utils at all, but in some other code. --- Makefile | 2 +- System/Cmd/.Utils.hs.swp | Bin 0 -> 36864 bytes System/Cmd/Utils.hs | 568 +++++++++++++++++++++++++++++++++++++++ 3 files changed, 569 insertions(+), 1 deletion(-) create mode 100644 System/Cmd/.Utils.hs.swp create mode 100644 System/Cmd/Utils.hs diff --git a/Makefile b/Makefile index 4d56287468..0afb10a7bb 100644 --- a/Makefile +++ b/Makefile @@ -14,7 +14,7 @@ endif PREFIX=/usr IGNORE=-ignore-package monads-fd -ignore-package monads-tf -BASEFLAGS=-Wall $(IGNORE) -outputdir tmp -IUtility -DWITH_ASSISTANT -DWITH_S3 $(BASEFLAGS_OPTS) +BASEFLAGS=-threaded -Wall $(IGNORE) -outputdir tmp -IUtility -DWITH_ASSISTANT -DWITH_S3 $(BASEFLAGS_OPTS) GHCFLAGS=-O2 $(BASEFLAGS) CFLAGS=-Wall diff --git a/System/Cmd/.Utils.hs.swp b/System/Cmd/.Utils.hs.swp new file mode 100644 index 0000000000000000000000000000000000000000..65e9e77e4437e33e567a27e7f34f6b8301ca5f47 GIT binary patch literal 36864 zcmeI53zTFnT26r%!i0tpEy7@r{c2>Jf1y0>pX zW_A{3A=m@o_TyI7ty_=3>i_Gn>e;ntX11wQ(imGc8bJ`BaIp6md zgV%~hzI!I@f!jeoKMQukC?DkW)8SBful@Xoyq|$u0=*LGl|ZiqdL_^+fnEvpN}yK)y%Ok^K(7RPC2){Rz|A|(iQMad z(9320Uu*#1dA8%+1Yd-|g1>}Uz%Pz;oPU5T;B7Dke+;)Cfu0W^h8*<6orhy9fZO0( za2>o3rr}laLU7=7f8;nfz+Cyc-vNW>EdS+E9U-s%=Ud=A5lhY@0Dd$)BdL&l&)qLRAYF-eg9cRAi1)ifi{|1~@UNv7TL@%8o zl&VeEyy~EN*$}->yYtSfQlXmn3TpT6tvkkNcJG!i)bT04DpkFFs#2=X&2L!0d+X#( zcK77WfV%i%)qX8IJUu?zadr3ZZJF)kJBhn{V4z#J)l{kGZS(V9DxDq}>>7gNI#Esd z^FtHfUazdOzF!Wbr?k)9?O}_O^67rP*gaK!IqNTTaV+pF-7iayPL!NeE^5A1FRG$j z&6mBfYyNA?=0mP7l?}NzK@EgUXGMZ6eYG>AW%t5G71jfC-aWSkKiET)Fip7oh2h{qY+s>U@Roa+DGG3_u07KND}KIF_7YtK zN>$vw+`I&og4XHg-MULwr~psp+;Um&*PpD8eo{C!ijpmQTO`5)UnK*nS}7mbD}_Os z&4ruv4J1({7x$bC+zNdmto9?fya2i3icDMd>ZFz;g+aA2pk6UVVy4-uzH->7&hA^| z)pLF4I?h(4o8m#;s`3`xN{vF(1xwilzH~NsQ3PV%SEc$!#}V1+mg*ENrJZvdp{Ex8 zMi6I(>moVbKqApc=h9B=ldDD*uQ=rv$gScrlrF3SJzqcBjP5A%L=+&Eg-i|`6)&Gw zYRoN_8;Ig*ui{l^yeqG6NHw&V z`MNIOt>?RRI<0Rq7kD-0H|n(pwI8Z{DXf*B^;*d7)|Wv~3EcK{=P| zB`>7xMoraHfqizUobcz;Fy{q*X=ldssEg3wsQNoDryDh@$Qv)y5y~b;|Dcpxx4#q_ zGK0p*bS9e_8J-v*WM>L0$_690>F(*K*yv*tr0-TX92%|& zr=7#o+ZoACG%}&we4gs`tImjDsUSamw2v%~+o783dzhwi6})ffxovDax=Fq*S5K(Y8{Y18(Z?NUJ>QHCEKU!j7^ks zUX`-qZ=)LDzC(>qO$;h#i;}QfuV^OjtiM;!6G!~oV!*Ifm$1zbsgVJ-e(lYm!L zVeKHTF|7Mk$hKjn)~;W-Zr#wj4Qo$PYRAm53V#Y7j=V{z}@C%E6qnt-j@AZ(gIj^)=It22%riW6Aq|3>pq^X;!#%#HiQ??u( zXX$IY&*{-N?@>`WP&?a3r$@F9Z_f^&o|(vGcS&iFWwP5xXJ*vc7AME*2x`NHN1V7bgXF-+qFpxO9Z*1V^(#a6B$#IuH*)R zTdm8JI9ZuvL?f+{_l!{_N;rC@JZRCc$*t&D(a1<|W=twH%1Fu--|I2b*HU5tnX!l( zBIBQJKxwC=j8(IyHz|)=YKE5PCQ~0TD$PL(#Np0b*ysx~69}VF%M>*NtR@u`7I~Q2 z#g1n!NVSKy+Ba#DDzZ5681!r*$Ri_+)=(!*#7YJH>sQj|m+Wm94bj?Hsfpq3<2#1O zN7cyGlv>4<4`J*Ex#CdWos(W=Bw#E)RD~|B3Z=5=i2i>Gdh5H;ZAJed=H<)i`fq{@ zAPc9!bK#puI?gBIeQ*_s4dAWta!A2L==~4E9dJ9m4HjS?)`J7TLFd070vLjypyOW; z&xb?cJLveIfY(C?j)uF?>AwnBLm5s5(e=NN9{=C)b$ADy3n#!Ka4&lNJ#ZU*5k3QN zgbQFB90|YTnSTjCg9qS#xDli*u7ciQuLOD}&?|vn2^{h>qfo2qrc zX2Ner|3-sbE{L6dPl?SfJ)>2NFrAsJV$C_=XlN!=nW@q4@w(nf>`9nKjDakOBL<#Z zHcv;xp_rH^scwH(8@7_Cu=999fHgC(o6Y`1 z%j}xaliFIc|KQBw2%V{7Lx}@7+lhH{wZcE!K2y!swZDkDvLAY5^iWJMh0d7>lT-VQmQ&-5ZmOC_4HEkyTTgnHWM+Xp3Ti%ll%0 zta_*sp(3%afu)R~Ls|I)G( zF=KJL|Cr{v5^=Xl1t@C2>z}^sIQ2yHlpbL1m8gTw>ZZ6?o`}?6OCrtsMeeU4of+1i zBsbIy&!S72tRNWYQCxMkNq_ZnI?Hl5u^5@$4=S3h=xv2k5Z2QU4bG~sQkAqsZS{$4 zsv*WOo>F1w&{{cqZj}!hjoIdmnr%#NtaFBH*W`|Anrv9ZXj?L7oZ~UqiV-$cr3z-; z5^672JZ+X24R$KCB~nv$`y#y^+HTb^R%Y9D`{mxUj7LV5yO(iGn}ztYY1tPGiJES3 zAF)Ab?QoE+m?Dsts+%O{d2C5o!Z9jztf4$UD{yUNv~69sGX#617HF)-6II4MJ3g`y zsP*!`C{%~ceI(e(n66nn9=FbEICQw%$P_QfJlBu%gvxsr%sB1Si9=3|b+ zHrL`D*n2RV>!E1%@p8NFF}Yx(v2b7~2F(_}9|`7|ki_dI==7}<(oQ923NlR){r~H% zAE#M&7X4p*_8&plza4IYcfvd1EwB$RhgZUj;0|>DYvD5R!G+hrVekmL{td7XM&Sr} z0Db@4@Kv}G{t-S0IS{{qemDUh!Vd5td;rdZov;~R4u``JunF7@pM&?nKG*}N!lT#) zZh%W+2ERs%XKxLRub*^d7h#EpH4EKIx_&<@j6~)XHw-niuv1JYwSCZ&x38RJDDT`)VUnXZFnUa^wTH!MFJJ1?e2U_LoG1R&0sPvZNa+<}n{JXf; zTgq$c=*w37G#)@>SPi<=yD^7VTI^xAFKcTVhMl@6@#0(4Xmri0S|y&z>wZB~i;ZGQ zgP2O$_8*Uh_Ki&kSuZybpFe4ov6jsHcnlmm)ln#q%g9$eJ3{d_akW@6%B$8t2eoS1 zpJ@91qWO0Vj2@b1krWPW zKfVlZ7?OnOl<22;28zz86=N1K?H#b}SO>4PqnFf`cxOfr)DhUKkx!(iSn`c|)-;Y- zH^TxUz7WQWDGk#@456O&*&dPiwspGr@sTf0= zQSfXKUH_x-TDTY{;Fa(TGW-enI9v&Dg;_Wao)6E4AEWQz2{*#u!VWkRZb$F`7&M?C z{tI3IYw$jJ4Ll$2MZdouE`?LzA@utn!F_NqTmhHBcGw0RU_Ja0{r~fD12kYQ+>gKh zC!qmr;Y#c-mjXRR{-VZUKG}~wtuhj%PdV##Ppf>Q?aH>Nb-Z-ZGFs-ntuuvW^qyAP z(<}i#v8TPbFy@_)r8#Nt~B0a6Li?7?`p;d|s8E>bI zo%^+)lr^%ogy?Jew1V&~L$^jje_q1u*6O0eHXS?|!j8?5>DJ`1)L}*w?-Og#!qSZO zt7@FvjC+N#zR2b;Z9ZdjjOS0ro5Sde7aQ7x`$g<)+?X%R!*{Zn(N=7wDp|WuFAbJ^mN> zAl#SOghS58utmt0J~7*I-$q%!oVE@lZT=x)W7g(C+=sA}bayz>`oAofeic1b^#2Mk ze}~S0CCtOw@KQ*_bKnqo0G0iFh5 z!8Y(-coT%M4UU03umyYpu7X)O8?rD1zriN(0DKre1ac0*QScLN13!ju!>w=?Tnf8k z3k<;ta2&iCr0$*ocO0`{HWw>HIkC_ear+watL${cq-~a_=rty2QE%7O+la;dADQc& z8s_%o7x?7GUo9^R5`H~w<Xmb@!B=ar9!-ixh&u3)ubWvHiBi&D8eG zbbHUm$0}&sqpU6Hk*(gWFtBfVa{I(CH9VFboz}+oux-CC%NcpG^6G7WvVU`zxRiiqn zlUmv8)q$!J%pJNqavMKxJ-3kgMf0!e2F_Nus)%76&upV*oxr-NuXdU-qIb)9fLlK= zv*MLl@IqX-I$zYJU#-X?Ji2S*HEA_oxreh!ATHOgYleD>FZN2;s}kZVnWeY47)!*B zaR3VS2){5<)t*_P4a#c3bBSY!=oN zj;Qj}?7i+7)XgqOy=E76J*D;|cJxsTxCOH#ReP0+2(atJ%|$x1bjW8pmBEYlIkp`b zz~)A?TDO0BVRH9`ii$(+!g=5v8n4%_R-sua!)Le8IaD_jx7&4G|ATs;BW*?;S+#G0 zlW6ler)bxkBt{CrQ+wWw(jl;vuVtao3NR=c0gIWyp%J(;&|t zDY}8)d$QC#wiyC{ESz;|S@`2t#rIayZ?^QvwSa|yp`pAt+nC#?QiPtBjU$r9v|jv@ zNCQTNOl+GONTy4^_P3o)EiEtu?4IvY~Br{K|}j7;Tw$We<&bI6#+aMybXfty`!!3(1PCha~v}}Uw znv8M62)kahmDTlHX7X{;@MQge9XkI{tp2};_di0%{~){%u7N2y3=W0+(d&Nzx4^%^ z+u;%r-Cy+nqv0;}{SU!Ka6U}KOW>#I`r_|@H8kLK*aRoR1`t1he+Kadkn;d91M&Hn zvjP4T9!1apHQWRrgUcZYa!$Z0uoea&1>Z#fzY$&!TVWg?M#uj&dM^ue>> z>F_1={lAARL3{&tf!F|kh@SshxE#)a{r# zYeDu2eD@Ii6<{A+4kyD);d$^)^m;i5@C|S_oD9c;ocZ?%b@fw_I{UHI+X4OABkAmm zmCJT$-@i&PGGS?t(^NEP^_x1J*y5N~tY-g|?x`wOoHB<#)%{|0tdALd;z@+Q3&)C) zj5aEWdz#5?RgA3lA{ojbG%vAb8)dV8D2q0efz&i6gG7UgrX13`n28qJ9G>gG zb_|a~>4@#&MBkMQEg@U9;kH!bYohsf#Ej=YEpHCY1fiC)LFfXAC)C|+5bCL6gpi_b zEB2Q1v>&VqLaNY)76U}o9qc24*J3(v}^2|0r6Qt4%wI zso$m@M2oga^R#vl{oOL+u3gBP`SYNhk%;f_vi1;U)6ymoxi10u*O*V)DvQu4`?)=O zVr^zg7>F_0W_^qA!`zRuebUWU|p*=yH1T8REXg8q1&=#i}d@8m_+|IdS?LG=88 z1<~{6-2XaE!Ex|Qbo!e>&i&sFvd;f=^!S_L-LM@}a2LA!ZSY-?_5E?^gX7^wboGCN zx5EOQ2M?jEi~jy4kTd_zgemBU=fd~V(XWOx;W=;w91fpFNB^+Z*N@@#QFQbFh3nuN zcrRQ4C&TmLm+0s>!<%6zybN9hvY-DpxE3yiSHsKTKJ@ZiMK=doudl)>@C>*Gz5HDu z=k;Fz=R*!=;c)mByi+JCu9fATpc^yT@+fYVO#IjCvTGU5@dMTtGOUlru3! zNtJU#L`Ov_?`#VP#fKmg>rE-j?l)r=+vbLQl+Q6&9LL?fY~Qt>^d#G{UbQ2WmEad} zgsVbd?{ZQV28GUene93nlhQ7+n6qNu_N+UQBroBjyO_*jWa!9Va-Frd?CzXqRC2eH z+v%I>Jw4`BA-f}JsjNkLvnCy0u;xZzHgB%q*-{hph~5RK`l4@4Y}xrF^VW9R7@u*{ zmYzPgNuPHXZ+w<<#N>e`Hoe$gsmWohQI1wz0^CYsqDi&q#+=(V#*y6E=4C}%=A%*i z(H9a?Oi^~eq*BS}>QznSC;^^k`@FoHe&xzC~gnTu! zbz+O+B;xv_`EI7!=1EgGX%g*hyt>hw67Ph3CxVkGmG}dTU~1MURR~QDiwh0T2=OR?C8ksv^|1Jls@U6*x8ukh#8Od zmF=8;9GLUWwV}+5mLa${Sw*Lf&s#FX_JK<2rgTo+{@^VPw%Ua0aB?`f&kq#H0y{FI zWz%V2;t2Y9HAy>##)pjQ6td0VS$OP;$Pd$yisiP(sZXTMXC5iM2Prrh!( zo+{cgCNd+gX2I6>bAFzH(McAFwOfgHiQ@}hlgUK%NS}&g5kmT6M<|KW?QRK~a9}q~ zL|pEk2r4TRI-GUdM1kbcJc|_y?INb@b9KhBopV5oqz*|UchP^*^a^p)tz5=g`>*1l zWDm77<4*fzOHZQg%2IP4C5@j6rTyMaNLohT$7&F&ZQR@F zt(^!A{Y3zKn_^6Ghh2FCu!^Jq3j)OO=PyvRc$AaYA3#Jo;oxA83TA? kXMxq-cZm2{p|^=Vjz23t9QrXmIpM%msg~Kl`=31fKh*qing9R* literal 0 HcmV?d00001 diff --git a/System/Cmd/Utils.hs b/System/Cmd/Utils.hs new file mode 100644 index 0000000000..23c2bcedfd --- /dev/null +++ b/System/Cmd/Utils.hs @@ -0,0 +1,568 @@ +-- arch-tag: Command utilities main file +{-# LANGUAGE CPP #-} +{- +Copyright (C) 2004-2006 John Goerzen + +This program is free software; you can redistribute it and/or modify +it under the terms of the GNU General Public License as published by +the Free Software Foundation; either version 2 of the License, or +(at your option) any later version. + +This program is distributed in the hope that it will be useful, +but WITHOUT ANY WARRANTY; without even the implied warranty of +MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +GNU General Public License for more details. + +You should have received a copy of the GNU General Public License +along with this program; if not, write to the Free Software +Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA +-} + +{- | + Module : System.Cmd.Utils + Copyright : Copyright (C) 2004-2006 John Goerzen + License : GNU GPL, version 2 or above + + Maintainer : John Goerzen + Stability : provisional + Portability: portable to platforms with POSIX process\/signal tools + +Command invocation utilities. + +Written by John Goerzen, jgoerzen\@complete.org + +Please note: Most of this module is not compatible with Hugs. + +Command lines executed will be logged using "System.Log.Logger" at the +DEBUG level. Failure messages will be logged at the WARNING level in addition +to being raised as an exception. Both are logged under +\"System.Cmd.Utils.funcname\" -- for instance, +\"System.Cmd.Utils.safeSystem\". If you wish to suppress these messages +globally, you can simply run: + +> updateGlobalLogger "System.Cmd.Utils.safeSystem" +> (setLevel CRITICAL) + +See also: 'System.Log.Logger.updateGlobalLogger', +"System.Log.Logger". + +It is possible to set up pipelines with these utilities. Example: + +> (pid1, x1) <- pipeFrom "ls" ["/etc"] +> (pid2, x2) <- pipeBoth "grep" ["x"] x1 +> putStr x2 +> ... the grep output is displayed ... +> forceSuccess pid2 +> forceSuccess pid1 + +Remember, when you use the functions that return a String, you must not call +'forceSuccess' until after all data from the String has been consumed. Failure +to wait will cause your program to appear to hang. + +Here is an example of the wrong way to do it: + +> (pid, x) <- pipeFrom "ls" ["/etc"] +> forceSuccess pid -- Hangs; the called program hasn't terminated yet +> processTheData x + +You must instead process the data before calling 'forceSuccess'. + +When using the hPipe family of functions, this is probably more obvious. + +Most of this module will be incompatible with Windows. +-} + + +module System.Cmd.Utils(-- * High-Level Tools + PipeHandle(..), + safeSystem, +#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) + forceSuccess, +#ifndef __HUGS__ + posixRawSystem, + forkRawSystem, + -- ** Piping with lazy strings + pipeFrom, + pipeLinesFrom, + pipeTo, + pipeBoth, + -- ** Piping with handles + hPipeFrom, + hPipeTo, + hPipeBoth, +#endif +#endif + -- * Low-Level Tools + PipeMode(..), +#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) +#ifndef __HUGS__ + pOpen, pOpen3, pOpen3Raw +#endif +#endif + ) +where + +-- FIXME - largely obsoleted by 6.4 - convert to wrappers. + +import System.Exit +import System.Cmd +#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) +import System.Posix.IO +import System.Posix.Process +import System.Posix.Signals +import qualified System.Posix.Signals +#endif +import System.Posix.Types +import System.IO +import System.IO.Error +import Control.Concurrent(forkIO) +import Control.Exception(finally) + +data PipeMode = ReadFromPipe | WriteToPipe + +logbase :: String +logbase = "System.Cmd.Utils" + +{- | Return value from 'pipeFrom', 'pipeLinesFrom', 'pipeTo', or +'pipeBoth'. Contains both a ProcessID and the original command that was +executed. If you prefer not to use 'forceSuccess' on the result of one +of these pipe calls, you can use (processID ph), assuming ph is your 'PipeHandle', +as a parameter to 'System.Posix.Process.getProcessStatus'. -} +data PipeHandle = + PipeHandle { processID :: ProcessID, + phCommand :: FilePath, + phArgs :: [String], + phCreator :: String -- ^ Function that created it + } + deriving (Eq, Show) + +#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) +#ifndef __HUGS__ +{- | Like 'pipeFrom', but returns data in lines instead of just a String. +Shortcut for calling lines on the result from 'pipeFrom'. + +Note: this function logs as pipeFrom. + +Not available on Windows. -} +pipeLinesFrom :: FilePath -> [String] -> IO (PipeHandle, [String]) +pipeLinesFrom fp args = + do (pid, c) <- pipeFrom fp args + return $ (pid, lines c) +#endif +#endif + +logRunning :: String -> FilePath -> [String] -> IO () +logRunning func fp args = return () --debugM (logbase ++ "." ++ func) (showCmd fp args) + +warnFail :: [Char] -> FilePath -> [String] -> [Char] -> IO t +warnFail funcname fp args msg = + let m = showCmd fp args ++ ": " ++ msg + in do putStrLn m + fail m + +ddd s a = do + putStrLn $ s ++ " start" + r <- a + putStrLn $ s ++ " end" + return r + +#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) +#ifndef __HUGS__ +{- | Read data from a pipe. Returns a Handle and a 'PipeHandle'. + +When done, you must hClose the handle, and then use either 'forceSuccess' or +getProcessStatus on the 'PipeHandle'. Zombies will result otherwise. + +This function logs as pipeFrom. + +Not available on Windows or with Hugs. +-} +hPipeFrom :: FilePath -> [String] -> IO (PipeHandle, Handle) +hPipeFrom fp args = + ddd "hPipeFrom" $ do + pipepair <- createPipe + let childstuff = do dupTo (snd pipepair) stdOutput + closeFd (fst pipepair) + executeFile fp True args Nothing + p <- try (forkProcess childstuff) + -- parent + pid <- case p of + Right x -> return x + Left e -> warnFail "pipeFrom" fp args $ + "Error in fork: " ++ show e + closeFd (snd pipepair) + h <- fdToHandle (fst pipepair) + return (PipeHandle pid fp args "pipeFrom", h) +#endif +#endif + +#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) +#ifndef __HUGS__ +{- | Read data from a pipe. Returns a lazy string and a 'PipeHandle'. + +ONLY AFTER the string has been read completely, You must call either +'System.Posix.Process.getProcessStatus' or 'forceSuccess' on the 'PipeHandle'. +Zombies will result otherwise. + +Not available on Windows. +-} +pipeFrom :: FilePath -> [String] -> IO (PipeHandle, String) +pipeFrom fp args = + do (pid, h) <- hPipeFrom fp args + c <- hGetContents h + return (pid, c) +#endif +#endif + +#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) +#ifndef __HUGS__ +{- | Write data to a pipe. Returns a 'PipeHandle' and a new Handle to write +to. + +When done, you must hClose the handle, and then use either 'forceSuccess' or +getProcessStatus on the 'PipeHandle'. Zombies will result otherwise. + +This function logs as pipeTo. + +Not available on Windows. +-} +hPipeTo :: FilePath -> [String] -> IO (PipeHandle, Handle) +hPipeTo fp args = + ddd "hPipeTo" $ do + pipepair <- createPipe + let childstuff = do dupTo (fst pipepair) stdInput + closeFd (snd pipepair) + executeFile fp True args Nothing + p <- try (forkProcess childstuff) + -- parent + pid <- case p of + Right x -> return x + Left e -> warnFail "pipeTo" fp args $ + "Error in fork: " ++ show e + closeFd (fst pipepair) + h <- fdToHandle (snd pipepair) + return (PipeHandle pid fp args "pipeTo", h) +#endif +#endif + +#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) +#ifndef __HUGS__ +{- | Write data to a pipe. Returns a ProcessID. + +You must call either +'System.Posix.Process.getProcessStatus' or 'forceSuccess' on the ProcessID. +Zombies will result otherwise. + +Not available on Windows. +-} +pipeTo :: FilePath -> [String] -> String -> IO PipeHandle +pipeTo fp args message = + do (pid, h) <- hPipeTo fp args + finally (hPutStr h message) + (hClose h) + return pid +#endif +#endif + +#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) +#ifndef __HUGS__ +{- | Like a combination of 'hPipeTo' and 'hPipeFrom'; returns +a 3-tuple of ('PipeHandle', Data From Pipe, Data To Pipe). + +When done, you must hClose both handles, and then use either 'forceSuccess' or +getProcessStatus on the 'PipeHandle'. Zombies will result otherwise. + +Hint: you will usually need to ForkIO a thread to handle one of the Handles; +otherwise, deadlock can result. + +This function logs as pipeBoth. + +Not available on Windows. +-} +hPipeBoth :: FilePath -> [String] -> IO (PipeHandle, Handle, Handle) +hPipeBoth fp args = + ddd "hPipeBoth" $ do + frompair <- createPipe + topair <- createPipe + let childstuff = do dupTo (snd frompair) stdOutput + closeFd (fst frompair) + dupTo (fst topair) stdInput + closeFd (snd topair) + executeFile fp True args Nothing + p <- try (forkProcess childstuff) + -- parent + pid <- case p of + Right x -> return x + Left e -> warnFail "pipeBoth" fp args $ + "Error in fork: " ++ show e + closeFd (snd frompair) + closeFd (fst topair) + fromh <- fdToHandle (fst frompair) + toh <- fdToHandle (snd topair) + return (PipeHandle pid fp args "pipeBoth", fromh, toh) +#endif +#endif + +#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) +#ifndef __HUGS__ +{- | Like a combination of 'pipeTo' and 'pipeFrom'; forks an IO thread +to send data to the piped program, and simultaneously returns its output +stream. + +The same note about checking the return status applies here as with 'pipeFrom'. + +Not available on Windows. -} +pipeBoth :: FilePath -> [String] -> String -> IO (PipeHandle, String) +pipeBoth fp args message = + do (pid, fromh, toh) <- hPipeBoth fp args + forkIO $ finally (hPutStr toh message) + (hClose toh) + c <- hGetContents fromh + return (pid, c) +#endif +#endif + +#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) +{- | Uses 'System.Posix.Process.getProcessStatus' to obtain the exit status +of the given process ID. If the process terminated normally, does nothing. +Otherwise, raises an exception with an appropriate error message. + +This call will block waiting for the given pid to terminate. + +Not available on Windows. -} +forceSuccess :: PipeHandle -> IO () +forceSuccess (PipeHandle pid fp args funcname) = + let warnfail = warnFail funcname + in do status <- getProcessStatus True False pid + case status of + Nothing -> warnfail fp args $ "Got no process status" + Just (Exited (ExitSuccess)) -> return () + Just (Exited (ExitFailure fc)) -> + cmdfailed funcname fp args fc + Just (Terminated sig) -> + warnfail fp args $ "Terminated by signal " ++ show sig + Just (Stopped sig) -> + warnfail fp args $ "Stopped by signal " ++ show sig +#endif + +{- | Invokes the specified command in a subprocess, waiting for the result. +If the command terminated successfully, return normally. Otherwise, +raises a userError with the problem. + +Implemented in terms of 'posixRawSystem' where supported, and System.Posix.rawSystem otherwise. +-} +safeSystem :: FilePath -> [String] -> IO () +safeSystem command args = + ddd "safeSystem" $ do +#if defined(__HUGS__) || defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__) + ec <- rawSystem command args + case ec of + ExitSuccess -> return () + ExitFailure fc -> cmdfailed "safeSystem" command args fc +#else + ec <- posixRawSystem command args + case ec of + Exited ExitSuccess -> return () + Exited (ExitFailure fc) -> cmdfailed "safeSystem" command args fc + Terminated s -> cmdsignalled "safeSystem" command args s + Stopped s -> cmdsignalled "safeSystem" command args s +#endif + +#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) +#ifndef __HUGS__ +{- | Invokes the specified command in a subprocess, waiting for the result. +Return the result status. Never raises an exception. Only available +on POSIX platforms. + +Like system(3), this command ignores SIGINT and SIGQUIT and blocks SIGCHLD +during its execution. + +Logs as System.Cmd.Utils.posixRawSystem -} +posixRawSystem :: FilePath -> [String] -> IO ProcessStatus +posixRawSystem program args = + ddd "posixRawSystem" $ do + oldint <- installHandler sigINT Ignore Nothing + oldquit <- installHandler sigQUIT Ignore Nothing + let sigset = addSignal sigCHLD emptySignalSet + oldset <- getSignalMask + blockSignals sigset + childpid <- forkProcess (childaction oldint oldquit oldset) + + mps <- getProcessStatus True False childpid + restoresignals oldint oldquit oldset + let retval = case mps of + Just x -> x + Nothing -> error "Nothing returned from getProcessStatus" + return retval + + where childaction oldint oldquit oldset = + do restoresignals oldint oldquit oldset + executeFile program True args Nothing + restoresignals oldint oldquit oldset = + do installHandler sigINT oldint Nothing + installHandler sigQUIT oldquit Nothing + setSignalMask oldset + +#endif +#endif + +#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) +#ifndef __HUGS__ +{- | Invokes the specified command in a subprocess, without waiting for +the result. Returns the PID of the subprocess -- it is YOUR responsibility +to use getProcessStatus or getAnyProcessStatus on that at some point. Failure +to do so will lead to resource leakage (zombie processes). + +This function does nothing with signals. That too is up to you. + +Logs as System.Cmd.Utils.forkRawSystem -} +forkRawSystem :: FilePath -> [String] -> IO ProcessID +forkRawSystem program args = ddd "forkRawSystem" $ + do + forkProcess childaction + where + childaction = executeFile program True args Nothing + +#endif +#endif + +cmdfailed :: String -> FilePath -> [String] -> Int -> IO a +cmdfailed funcname command args failcode = do + let errormsg = "Command " ++ command ++ " " ++ (show args) ++ + " failed; exit code " ++ (show failcode) + let e = userError (errormsg) + putStrLn errormsg + ioError e + +#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) +#ifndef __HUGS__ +cmdsignalled :: String -> FilePath -> [String] -> Signal -> IO a +cmdsignalled funcname command args failcode = do + let errormsg = "Command " ++ command ++ " " ++ (show args) ++ + " failed due to signal " ++ (show failcode) + let e = userError (errormsg) + putStrLn errormsg + ioError e +#endif +#endif + +#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) +#ifndef __HUGS__ +{- | Open a pipe to the specified command. + +Passes the handle on to the specified function. + +The 'PipeMode' specifies what you will be doing. That is, specifing 'ReadFromPipe' +sets up a pipe from stdin, and 'WriteToPipe' sets up a pipe from stdout. + +Not available on Windows. + -} +pOpen :: PipeMode -> FilePath -> [String] -> + (Handle -> IO a) -> IO a +pOpen pm fp args func = ddd "pOpen" $ + do + pipepair <- createPipe + case pm of + ReadFromPipe -> do + let callfunc _ = do + closeFd (snd pipepair) + h <- fdToHandle (fst pipepair) + x <- func h + hClose h + return $! x + pOpen3 Nothing (Just (snd pipepair)) Nothing fp args + callfunc (closeFd (fst pipepair)) + WriteToPipe -> do + let callfunc _ = do + closeFd (fst pipepair) + h <- fdToHandle (snd pipepair) + x <- func h + hClose h + return $! x + pOpen3 (Just (fst pipepair)) Nothing Nothing fp args + callfunc (closeFd (snd pipepair)) +#endif +#endif + +#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) +#ifndef __HUGS__ +{- | Runs a command, redirecting things to pipes. + +Not available on Windows. + +Note that you may not use the same fd on more than one item. If you +want to redirect stdout and stderr, dup it first. +-} +pOpen3 :: Maybe Fd -- ^ Send stdin to this fd + -> Maybe Fd -- ^ Get stdout from this fd + -> Maybe Fd -- ^ Get stderr from this fd + -> FilePath -- ^ Command to run + -> [String] -- ^ Command args + -> (ProcessID -> IO a) -- ^ Action to run in parent + -> IO () -- ^ Action to run in child before execing (if you don't need something, set this to @return ()@) -- IGNORED IN HUGS + -> IO a +pOpen3 pin pout perr fp args func childfunc = ddd "pOpen3" $ + do pid <- pOpen3Raw pin pout perr fp args childfunc + putStrLn "got pid" + retval <- func $! pid + putStrLn "got retval" + let rv = seq retval retval + forceSuccess (PipeHandle (seq retval pid) fp args "pOpen3") + putStrLn "process finished" + return rv +#endif +#endif + +#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) +#ifndef __HUGS__ +{- | Runs a command, redirecting things to pipes. + +Not available on Windows. + +Returns immediately with the PID of the child. Using 'waitProcess' on it +is YOUR responsibility! + +Note that you may not use the same fd on more than one item. If you +want to redirect stdout and stderr, dup it first. +-} +pOpen3Raw :: Maybe Fd -- ^ Send stdin to this fd + -> Maybe Fd -- ^ Get stdout from this fd + -> Maybe Fd -- ^ Get stderr from this fd + -> FilePath -- ^ Command to run + -> [String] -- ^ Command args + -> IO () -- ^ Action to run in child before execing (if you don't need something, set this to @return ()@) -- IGNORED IN HUGS + -> IO ProcessID +pOpen3Raw pin pout perr fp args childfunc = + let mayberedir Nothing _ = return () + mayberedir (Just fromfd) tofd = do + dupTo fromfd tofd + closeFd fromfd + return () + childstuff = do + mayberedir pin stdInput + mayberedir pout stdOutput + mayberedir perr stdError + childfunc + executeFile fp True args Nothing +{- + realfunc p = do + System.Posix.Signals.installHandler + System.Posix.Signals.sigPIPE + System.Posix.Signals.Ignore + Nothing + func p +-} + in + ddd "pOpen3Raw" $ + do + p <- try (forkProcess childstuff) + pid <- case p of + Right x -> return x + Left e -> fail ("Error in fork: " ++ (show e)) + return pid + +#endif +#endif + +showCmd :: FilePath -> [String] -> String +showCmd fp args = fp ++ " " ++ show args From 182526ff68b1ca68952b4dbd32121e46d4a80e85 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Tue, 17 Jul 2012 14:40:05 -0400 Subject: [PATCH 053/331] add debugging --- Git/Branch.hs | 10 +++++----- Git/Command.hs | 12 +++++++----- Git/HashObject.hs | 8 +++----- Git/Ref.hs | 5 ++++- System/Cmd/Utils.hs | 4 ++-- Utility/Misc.hs | 2 +- Utility/SafeCommand.hs | 4 ++-- git-annex.cabal | 2 +- 8 files changed, 25 insertions(+), 22 deletions(-) diff --git a/Git/Branch.hs b/Git/Branch.hs index 6edc1c306d..6f3d251863 100644 --- a/Git/Branch.hs +++ b/Git/Branch.hs @@ -73,12 +73,12 @@ commit :: String -> Branch -> [Ref] -> Repo -> IO Sha commit message branch parentrefs repo = do tree <- getSha "write-tree" $ pipeRead [Param "write-tree"] repo - sha <- getSha "commit-tree" $ - ignorehandle $ pipeWriteRead - (map Param $ ["commit-tree", show tree] ++ ps) - message repo + sha <- getSha "commit-tree" $ pipeWriteRead + (map Param $ ["commit-tree", show tree] ++ ps) + message repo + print ("got", sha) run "update-ref" [Param $ show branch, Param $ show sha] repo + print ("update-ref done", sha) return sha where - ignorehandle a = snd <$> a ps = concatMap (\r -> ["-p", show r]) parentrefs diff --git a/Git/Command.hs b/Git/Command.hs index 35f0838ba9..9a09300e24 100644 --- a/Git/Command.hs +++ b/Git/Command.hs @@ -57,16 +57,18 @@ pipeWrite params s repo = assertLocal repo $ do hClose h return p -{- Runs a git subcommand, feeding it input, and returning its output. - - You should call either getProcessStatus or forceSuccess on the PipeHandle. -} -pipeWriteRead :: [CommandParam] -> String -> Repo -> IO (PipeHandle, String) +{- Runs a git subcommand, feeding it input, and returning its output, + - which is expected to be fairly small, since it's all read into memory + - strictly. -} +pipeWriteRead :: [CommandParam] -> String -> Repo -> IO String pipeWriteRead params s repo = assertLocal repo $ do (p, from, to) <- hPipeBoth "git" (toCommand $ gitCommandLine params repo) fileEncoding to fileEncoding from _ <- forkIO $ finally (hPutStr to s) (hClose to) - c <- hGetContents from - return (p, c) + c <- hGetContentsStrict from + forceSuccess p + return c {- Reads null terminated output of a git command (as enabled by the -z - parameter), and splits it. -} diff --git a/Git/HashObject.hs b/Git/HashObject.hs index 9f37de5ba9..c90c9ec3d6 100644 --- a/Git/HashObject.hs +++ b/Git/HashObject.hs @@ -38,11 +38,9 @@ hashFile h file = CoProcess.query h send receive {- Injects some content into git, returning its Sha. -} hashObject :: ObjectType -> String -> Repo -> IO Sha hashObject objtype content repo = getSha subcmd $ do - (h, s) <- pipeWriteRead (map Param params) content repo - length s `seq` do - forceSuccess h - reap -- XXX unsure why this is needed - return s + s <- pipeWriteRead (map Param params) content repo + reap -- XXX unsure why this is needed, of if it is anymore + return s where subcmd = "hash-object" params = [subcmd, "-t", show objtype, "-w", "--stdin"] diff --git a/Git/Ref.hs b/Git/Ref.hs index ee2f021871..3052d0a6ef 100644 --- a/Git/Ref.hs +++ b/Git/Ref.hs @@ -40,7 +40,10 @@ exists ref = runBool "show-ref" {- Get the sha of a fully qualified git ref, if it exists. -} sha :: Branch -> Repo -> IO (Maybe Sha) -sha branch repo = process <$> showref repo +sha branch repo = do + r <- process <$> showref repo + print r + return r where showref = pipeRead [Param "show-ref", Param "--hash", -- get the hash diff --git a/System/Cmd/Utils.hs b/System/Cmd/Utils.hs index 23c2bcedfd..15544d6846 100644 --- a/System/Cmd/Utils.hs +++ b/System/Cmd/Utils.hs @@ -179,7 +179,7 @@ Not available on Windows or with Hugs. -} hPipeFrom :: FilePath -> [String] -> IO (PipeHandle, Handle) hPipeFrom fp args = - ddd "hPipeFrom" $ do + ddd (show ("hPipeFrom", fp, args)) $ do pipepair <- createPipe let childstuff = do dupTo (snd pipepair) stdOutput closeFd (fst pipepair) @@ -281,7 +281,7 @@ Not available on Windows. -} hPipeBoth :: FilePath -> [String] -> IO (PipeHandle, Handle, Handle) hPipeBoth fp args = - ddd "hPipeBoth" $ do + ddd (show ("hPipeBoth", fp, args)) $ do frompair <- createPipe topair <- createPipe let childstuff = do dupTo (snd frompair) stdOutput diff --git a/Utility/Misc.hs b/Utility/Misc.hs index 3b359139b9..e11586467d 100644 --- a/Utility/Misc.hs +++ b/Utility/Misc.hs @@ -33,7 +33,7 @@ separate c l = unbreak $ break c l | otherwise = (a, tail b) {- Breaks out the first line. -} -firstLine :: String-> String +firstLine :: String -> String firstLine = takeWhile (/= '\n') {- Splits a list into segments that are delimited by items matching diff --git a/Utility/SafeCommand.hs b/Utility/SafeCommand.hs index aedf271373..2c6439b452 100644 --- a/Utility/SafeCommand.hs +++ b/Utility/SafeCommand.hs @@ -78,8 +78,8 @@ safeSystemEnv command params env = do {- executeFile with debug logging -} executeFile :: FilePath -> Bool -> [String] -> Maybe [(String, String)] -> IO () executeFile c path p e = do - debugM "Utility.SafeCommand.executeFile" $ - "Running: " ++ c ++ " " ++ show p ++ " " ++ maybe "" show e + --debugM "Utility.SafeCommand.executeFile" $ + -- "Running: " ++ c ++ " " ++ show p ++ " " ++ maybe "" show e System.Posix.Process.executeFile c path p e {- Escapes a filename or other parameter to be safely able to be exposed to diff --git a/git-annex.cabal b/git-annex.cabal index 0bd35e14fe..3f237ce70e 100644 --- a/git-annex.cabal +++ b/git-annex.cabal @@ -1,5 +1,5 @@ Name: git-annex -Version: 3.20120629 +Version: 3.20120630 Cabal-Version: >= 1.8 License: GPL Maintainer: Joey Hess From e816776a6247daa2adfa73d9029c6f155ae46b4a Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Tue, 17 Jul 2012 15:57:49 -0400 Subject: [PATCH 054/331] add inodes to kqueue's directory cache This is necessary to generate events when a file is deleted and immediately replaced. Otherwise, the cache will have the old file, and so no event would be generated. Use of getFileStatus is suboptimal, it would be faster to use the inode returned by readdir -- but getDirectoryContents does not expose it, so I'd have to copy and modify a lot of low-level code. --- Utility/Kqueue.hs | 18 ++++++++++++------ 1 file changed, 12 insertions(+), 6 deletions(-) diff --git a/Utility/Kqueue.hs b/Utility/Kqueue.hs index 7e7e653ec3..17a5be5456 100644 --- a/Utility/Kqueue.hs +++ b/Utility/Kqueue.hs @@ -22,6 +22,7 @@ module Utility.Kqueue ( import Common import Utility.Types.DirWatcher +import System.Posix.Directory import System.Posix.Types import Foreign.C.Types import Foreign.C.Error @@ -62,15 +63,19 @@ type DirMap = M.Map Fd DirInfo {- A directory, and its last known contents (with filenames relative to it) -} data DirInfo = DirInfo { dirName :: FilePath - , dirCache :: S.Set FilePath + , dirCache :: S.Set (FilePath, FileID) } deriving (Show) getDirInfo :: FilePath -> IO DirInfo getDirInfo dir = do - contents <- S.fromList . filter (not . dirCruft) - <$> getDirectoryContents dir + l <- filter (not . dirCruft) <$> getDirectoryContents dir + contents <- S.fromList <$> mapM addinode l return $ DirInfo dir contents + where + addinode f = do + inode <- fileID <$> getFileStatus (dir f) + return (f, inode) {- Difference between the dirCaches of two DirInfos. -} (//) :: DirInfo -> DirInfo -> [Change] @@ -78,7 +83,7 @@ oldc // newc = deleted ++ added where deleted = calc Deleted oldc newc added = calc Added newc oldc - calc a x y = map a . map (dirName x ) $ + calc a x y = map a . map (dirName x ) . map fst $ S.toList $ S.difference (dirCache x) (dirCache y) {- Builds a map of directories in a tree, possibly pruning some. @@ -99,7 +104,7 @@ scanRecursive topdir prune = M.fromList <$> walk [] [topdir] case mfd of Nothing -> walk c rest Just fd -> do - let subdirs = map (dir ) $ + let subdirs = map (dir ) . map fst $ S.toList $ dirCache info walk ((fd, info):c) (subdirs ++ rest) @@ -123,7 +128,8 @@ removeSubDir dirmap dir = do findDirContents :: DirMap -> FilePath -> [FilePath] findDirContents dirmap dir = concatMap absolutecontents $ search where - absolutecontents i = map (dirName i ) (S.toList $ dirCache i) + absolutecontents i = map (dirName i ) + (map fst $ S.toList $ dirCache i) search = map snd $ M.toList $ M.filter (\i -> dirName i == dir) dirmap From 7d89cf0eb9aeffff25dc1b7db129c47c9f434078 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Tue, 17 Jul 2012 16:02:29 -0400 Subject: [PATCH 055/331] cleanup --- Utility/Kqueue.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/Utility/Kqueue.hs b/Utility/Kqueue.hs index 17a5be5456..b475de3a3b 100644 --- a/Utility/Kqueue.hs +++ b/Utility/Kqueue.hs @@ -22,7 +22,6 @@ module Utility.Kqueue ( import Common import Utility.Types.DirWatcher -import System.Posix.Directory import System.Posix.Types import Foreign.C.Types import Foreign.C.Error From 30ac6d7be04d677cdc4a1da6d60622657665083f Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Tue, 17 Jul 2012 16:29:49 -0400 Subject: [PATCH 056/331] robustness fix Don't fall over symlinks, and avoid crashing if the file goes away. --- Utility/Kqueue.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Utility/Kqueue.hs b/Utility/Kqueue.hs index b475de3a3b..62b06a5323 100644 --- a/Utility/Kqueue.hs +++ b/Utility/Kqueue.hs @@ -69,10 +69,10 @@ data DirInfo = DirInfo getDirInfo :: FilePath -> IO DirInfo getDirInfo dir = do l <- filter (not . dirCruft) <$> getDirectoryContents dir - contents <- S.fromList <$> mapM addinode l + contents <- S.fromList . catMaybes <$> mapM addinode l return $ DirInfo dir contents where - addinode f = do + addinode f = catchMaybeIO $ do inode <- fileID <$> getFileStatus (dir f) return (f, inode) From 9ab9ef3ebd931549b41d40c73ceeeba82a8099cc Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Tue, 17 Jul 2012 17:16:30 -0400 Subject: [PATCH 057/331] change transfer lock filenames to avoid ambiguity foo.lck could be a lock file for a transfer of foo, or a transfer of a key that happened to end in ".lck". Fix this by using "lck.foo" instead. --- Logs/Transfer.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Logs/Transfer.hs b/Logs/Transfer.hs index 8b88041273..daec476ef0 100644 --- a/Logs/Transfer.hs +++ b/Logs/Transfer.hs @@ -67,7 +67,7 @@ fieldTransfer direction key a = do =<< Fields.getField Fields.remoteUUID {- Runs a transfer action. Creates and locks the lock file while the - - action is running, and stores into in the transfer information + - action is running, and stores info in the transfer information - file. Will throw an error if the transfer is already in progress. -} transfer :: Transfer -> Maybe FilePath -> Annex a -> Annex a @@ -139,7 +139,7 @@ transferFile (Transfer direction u key) r = gitAnnexTransferDir r {- The transfer lock file corresponding to a given transfer info file. -} transferLockFile :: FilePath -> FilePath -transferLockFile infofile = infofile ++ ".lck" +transferLockFile infofile = "lck." ++ infofile {- Parses a transfer information filename to a Transfer. -} parseTransferFile :: FilePath -> Maybe Transfer From b702bae9501676082a1f9388286b3c9855d8a44a Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Tue, 17 Jul 2012 17:22:00 -0400 Subject: [PATCH 058/331] bugfix --- Logs/Transfer.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/Logs/Transfer.hs b/Logs/Transfer.hs index daec476ef0..55db855cc3 100644 --- a/Logs/Transfer.hs +++ b/Logs/Transfer.hs @@ -139,7 +139,8 @@ transferFile (Transfer direction u key) r = gitAnnexTransferDir r {- The transfer lock file corresponding to a given transfer info file. -} transferLockFile :: FilePath -> FilePath -transferLockFile infofile = "lck." ++ infofile +transferLockFile infofile = let (d,f) = splitFileName infofile in + combine d ("lck." ++ f) {- Parses a transfer information filename to a Transfer. -} parseTransferFile :: FilePath -> Maybe Transfer From d53f70e2039a00b2ba2b87e26f29705d8f4c629a Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Tue, 17 Jul 2012 17:26:53 -0400 Subject: [PATCH 059/331] avoid parsing lock files as transfer files This seems to happen with kqueue, not inotify. The newly added lck file triggers an add event and was then parsed as a transfer file. --- Logs/Transfer.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/Logs/Transfer.hs b/Logs/Transfer.hs index 55db855cc3..2605120674 100644 --- a/Logs/Transfer.hs +++ b/Logs/Transfer.hs @@ -144,8 +144,9 @@ transferLockFile infofile = let (d,f) = splitFileName infofile in {- Parses a transfer information filename to a Transfer. -} parseTransferFile :: FilePath -> Maybe Transfer -parseTransferFile file = - case drop (length bits - 3) bits of +parseTransferFile file + | "lck." `isPrefixOf` (takeFileName file) = Nothing + | otherwise = case drop (length bits - 3) bits of [direction, u, key] -> Transfer <$> readDirection direction <*> pure (toUUID u) From 32ac7739348f6bc6aaf0db1e85a395368300dc33 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Tue, 17 Jul 2012 18:32:55 -0400 Subject: [PATCH 060/331] kqueue: properly call delHook for file deletion, not delDirHook --- Utility/Kqueue.hs | 60 +++++++++++++++++++++++++++++------------------ 1 file changed, 37 insertions(+), 23 deletions(-) diff --git a/Utility/Kqueue.hs b/Utility/Kqueue.hs index 62b06a5323..58fc5a5b7f 100644 --- a/Utility/Kqueue.hs +++ b/Utility/Kqueue.hs @@ -14,8 +14,6 @@ module Utility.Kqueue ( waitChange, Change(..), changedFile, - isAdd, - isDelete, runHooks, ) where @@ -34,15 +32,14 @@ import Control.Concurrent data Change = Deleted FilePath + | DeletedDir FilePath | Added FilePath deriving (Show) isAdd :: Change -> Bool isAdd (Added _) = True isAdd (Deleted _) = False - -isDelete :: Change -> Bool -isDelete = not . isAdd +isAdd (DeletedDir _) = False changedFile :: Change -> FilePath changedFile (Added f) = f @@ -59,31 +56,43 @@ type Pruner = FilePath -> Bool type DirMap = M.Map Fd DirInfo -{- A directory, and its last known contents (with filenames relative to it) -} +{- Enough information to uniquely identify a file in a directory, + - but not too much. -} +data DirEnt = DirEnt + { dirEnt :: FilePath -- relative to the parent directory + , _dirInode :: FileID -- included to notice file replacements + , isSubDir :: Bool + } + deriving (Eq, Ord, Show) + +{- A directory, and its last known contents. -} data DirInfo = DirInfo { dirName :: FilePath - , dirCache :: S.Set (FilePath, FileID) + , dirCache :: S.Set DirEnt } deriving (Show) getDirInfo :: FilePath -> IO DirInfo getDirInfo dir = do l <- filter (not . dirCruft) <$> getDirectoryContents dir - contents <- S.fromList . catMaybes <$> mapM addinode l + contents <- S.fromList . catMaybes <$> mapM getDirEnt l return $ DirInfo dir contents where - addinode f = catchMaybeIO $ do - inode <- fileID <$> getFileStatus (dir f) - return (f, inode) + getDirEnt f = catchMaybeIO $ do + s <- getFileStatus (dir f) + return $ DirEnt f (fileID s) (isDirectory s) {- Difference between the dirCaches of two DirInfos. -} (//) :: DirInfo -> DirInfo -> [Change] oldc // newc = deleted ++ added where - deleted = calc Deleted oldc newc - added = calc Added newc oldc - calc a x y = map a . map (dirName x ) . map fst $ - S.toList $ S.difference (dirCache x) (dirCache y) + deleted = calc gendel oldc newc + added = calc genadd newc oldc + gendel x = (if isSubDir x then DeletedDir else Deleted) $ + dirName oldc dirEnt x + genadd x = Added $ dirName newc dirEnt x + calc a x y = map a $ S.toList $ + S.difference (dirCache x) (dirCache y) {- Builds a map of directories in a tree, possibly pruning some. - Opens each directory in the tree, and records its current contents. -} @@ -103,7 +112,7 @@ scanRecursive topdir prune = M.fromList <$> walk [] [topdir] case mfd of Nothing -> walk c rest Just fd -> do - let subdirs = map (dir ) . map fst $ + let subdirs = map (dir ) . map dirEnt $ S.toList $ dirCache info walk ((fd, info):c) (subdirs ++ rest) @@ -128,7 +137,7 @@ findDirContents :: DirMap -> FilePath -> [FilePath] findDirContents dirmap dir = concatMap absolutecontents $ search where absolutecontents i = map (dirName i ) - (map fst $ S.toList $ dirCache i) + (map dirEnt $ S.toList $ dirCache i) search = map snd $ M.toList $ M.filter (\i -> dirName i == dir) dirmap @@ -229,12 +238,14 @@ runHooks kq hooks = do (q', changes) <- waitChange q forM_ changes $ dispatch (kqueueMap q') loop q' - -- Kqueue returns changes for both whole directories - -- being added and deleted, and individual files being - -- added and deleted. - dispatch dirmap change - | isAdd change = withstatus change $ dispatchadd dirmap - | otherwise = callhook delDirHook Nothing change + + dispatch dirmap change@(Deleted _) = + callhook delHook Nothing change + dispatch dirmap change@(DeletedDir _) = + callhook delDirHook Nothing change + dispatch dirmap change@(Added _) = + withstatus change $ dispatchadd dirmap + dispatchadd dirmap change s | Files.isSymbolicLink s = callhook addSymlinkHook (Just s) change @@ -242,12 +253,15 @@ runHooks kq hooks = do | Files.isRegularFile s = callhook addHook (Just s) change | otherwise = noop + recursiveadd dirmap change = do let contents = findDirContents dirmap $ changedFile change forM_ contents $ \f -> withstatus (Added f) $ dispatchadd dirmap + callhook h s change = case h hooks of Nothing -> noop Just a -> a (changedFile change) s + withstatus change a = maybe noop (a change) =<< (catchMaybeIO (getSymbolicLinkStatus (changedFile change))) From 62a35162a0988f8d6e51796debceafda4d35c061 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Tue, 17 Jul 2012 18:35:56 -0400 Subject: [PATCH 061/331] bugfix --- Utility/Kqueue.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/Utility/Kqueue.hs b/Utility/Kqueue.hs index 58fc5a5b7f..9013dbe7e2 100644 --- a/Utility/Kqueue.hs +++ b/Utility/Kqueue.hs @@ -44,6 +44,7 @@ isAdd (DeletedDir _) = False changedFile :: Change -> FilePath changedFile (Added f) = f changedFile (Deleted f) = f +changedFile (DeletedDir f) = f data Kqueue = Kqueue { kqueueFd :: Fd From fb85d8e563d071d7355c2cc7f8fb68860312e616 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Tue, 17 Jul 2012 18:36:51 -0400 Subject: [PATCH 062/331] cleanup --- Utility/Kqueue.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Utility/Kqueue.hs b/Utility/Kqueue.hs index 9013dbe7e2..c1a0a5cd60 100644 --- a/Utility/Kqueue.hs +++ b/Utility/Kqueue.hs @@ -240,9 +240,9 @@ runHooks kq hooks = do forM_ changes $ dispatch (kqueueMap q') loop q' - dispatch dirmap change@(Deleted _) = + dispatch _ change@(Deleted _) = callhook delHook Nothing change - dispatch dirmap change@(DeletedDir _) = + dispatch _ change@(DeletedDir _) = callhook delDirHook Nothing change dispatch dirmap change@(Added _) = withstatus change $ dispatchadd dirmap From 05310538ef4f2c0c483bab355083ec2044a12a0a Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 18 Jul 2012 13:30:53 -0400 Subject: [PATCH 063/331] more debugging --- Annex/Branch.hs | 4 +++- Git/CatFile.hs | 12 +++++++++++- Git/CheckAttr.hs | 4 ++++ System/Cmd/Utils.hs | 2 +- Utility/SafeCommand.hs | 7 ++++++- 5 files changed, 25 insertions(+), 4 deletions(-) diff --git a/Annex/Branch.hs b/Annex/Branch.hs index 8e7f45a4ad..e551bfcd01 100644 --- a/Annex/Branch.hs +++ b/Annex/Branch.hs @@ -164,7 +164,9 @@ get' staleok file = fromcache =<< getCache file fromjournal Nothing | staleok = withIndex frombranch | otherwise = withIndexUpdate $ frombranch >>= cache - frombranch = L.unpack <$> catFile fullname file + frombranch = do + liftIO $ putStrLn $ "frombranch " ++ file + L.unpack <$> catFile fullname file cache content = do setCache file content return content diff --git a/Git/CatFile.hs b/Git/CatFile.hs index e667b20879..e8f362685d 100644 --- a/Git/CatFile.hs +++ b/Git/CatFile.hs @@ -50,11 +50,16 @@ catObjectDetails :: CatFileHandle -> Ref -> IO (Maybe (L.ByteString, Sha)) catObjectDetails h object = CoProcess.query h send receive where send to = do + putStrLn "catObjectDetails send start" fileEncoding to hPutStrLn to $ show object + putStrLn $ "catObjectDetails send done " ++ show object receive from = do + putStrLn "catObjectDetails read header start" fileEncoding from + putStrLn "catObjectDetails read header start2" header <- hGetLine from + putStrLn "catObjectDetails read header done" case words header of [sha, objtype, size] | length sha == shaSize && @@ -67,9 +72,14 @@ catObjectDetails h object = CoProcess.query h send receive | header == show object ++ " missing" -> dne | otherwise -> error $ "unknown response from git cat-file " ++ show (header, object) readcontent bytes from sha = do + putStrLn "readcontent start" content <- S.hGet from bytes + putStrLn "readcontent end" c <- hGetChar from + putStrLn "readcontent newline read" when (c /= '\n') $ error "missing newline from git cat-file" return $ Just (L.fromChunks [content], Ref sha) - dne = return Nothing + dne = do + putStrLn "dne" + return Nothing diff --git a/Git/CheckAttr.hs b/Git/CheckAttr.hs index 6b321f8b8f..7636ea6411 100644 --- a/Git/CheckAttr.hs +++ b/Git/CheckAttr.hs @@ -44,11 +44,15 @@ checkAttr (h, attrs, cwd) want file = do _ -> error $ "unable to determine " ++ want ++ " attribute of " ++ file where send to = do + putStrLn "checkAttr send start" fileEncoding to hPutStr to $ file' ++ "\0" + putStrLn "checkAttr send end" receive from = forM attrs $ \attr -> do + putStrLn "checkAttr receive start" fileEncoding from l <- hGetLine from + putStrLn "checkAttr receive end" return (attr, attrvalue attr l) {- Before git 1.7.7, git check-attr worked best with - absolute filenames; using them worked around some bugs diff --git a/System/Cmd/Utils.hs b/System/Cmd/Utils.hs index 15544d6846..a81126146b 100644 --- a/System/Cmd/Utils.hs +++ b/System/Cmd/Utils.hs @@ -501,7 +501,7 @@ pOpen3 :: Maybe Fd -- ^ Send stdin to this fd -> (ProcessID -> IO a) -- ^ Action to run in parent -> IO () -- ^ Action to run in child before execing (if you don't need something, set this to @return ()@) -- IGNORED IN HUGS -> IO a -pOpen3 pin pout perr fp args func childfunc = ddd "pOpen3" $ +pOpen3 pin pout perr fp args func childfunc = ddd (show ("pOpen3", fp, args)) $ do pid <- pOpen3Raw pin pout perr fp args childfunc putStrLn "got pid" retval <- func $! pid diff --git a/Utility/SafeCommand.hs b/Utility/SafeCommand.hs index 2c6439b452..5f6a53e715 100644 --- a/Utility/SafeCommand.hs +++ b/Utility/SafeCommand.hs @@ -54,6 +54,7 @@ safeSystem command params = safeSystemEnv command params Nothing {- SIGINT(ctrl-c) is allowed to propigate and will terminate the program. -} safeSystemEnv :: FilePath -> [CommandParam] -> Maybe [(String, String)] -> IO ExitCode safeSystemEnv command params env = do + putStrLn "safeSystemEnv start" -- Going low-level because all the high-level system functions -- block SIGINT etc. We need to block SIGCHLD, but allow -- SIGINT to do its default program termination. @@ -65,7 +66,9 @@ safeSystemEnv command params env = do mps <- getProcessStatus True False childpid restoresignals oldint oldset case mps of - Just (Exited code) -> return code + Just (Exited code) -> do + putStrLn "safeSystemEnv end" + return code _ -> error $ "unknown error running " ++ command where restoresignals oldint oldset = do @@ -78,9 +81,11 @@ safeSystemEnv command params env = do {- executeFile with debug logging -} executeFile :: FilePath -> Bool -> [String] -> Maybe [(String, String)] -> IO () executeFile c path p e = do + putStrLn "executeFile start" --debugM "Utility.SafeCommand.executeFile" $ -- "Running: " ++ c ++ " " ++ show p ++ " " ++ maybe "" show e System.Posix.Process.executeFile c path p e + putStrLn "executeFile end" {- Escapes a filename or other parameter to be safely able to be exposed to - the shell. -} From d1da9cf221aeea5c7ac8a313a18b559791a04f12 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 18 Jul 2012 15:30:26 -0400 Subject: [PATCH 064/331] switch from System.Cmd.Utils to System.Process Test suite now passes with -threaded! I traced back all the hangs with -threaded to System.Cmd.Utils. It seems it's just crappy/unsafe/outdated, and should not be used. System.Process seems to be the cool new thing, so converted all the code to use it instead. In the process, --debug stopped printing commands it runs. I may try to bring that back later. Note that even SafeSystem was switched to use System.Process. Since that was a modified version of code from System.Cmd.Utils, it needed to be converted too. I also got rid of nearly all calls to forkProcess, and all calls to executeFile, which I'm also doubtful about working well with -threaded. --- Annex/Branch.hs | 4 +- Annex/UUID.hs | 6 +- Backend/SHA.hs | 17 +- Build/Configure.hs | 4 +- Command/Fsck.hs | 2 + Command/Map.hs | 11 +- Common.hs | 3 +- Config.hs | 6 +- Git/Branch.hs | 2 - Git/CatFile.hs | 12 +- Git/CheckAttr.hs | 4 - Git/Command.hs | 29 +- Git/Config.hs | 14 +- Git/Queue.hs | 17 +- Git/Ref.hs | 5 +- Git/UpdateIndex.hs | 7 +- Remote/Bup.hs | 6 +- Remote/Git.hs | 14 +- Remote/Hook.hs | 17 +- Remote/Rsync.hs | 1 + System/Cmd/.Utils.hs.swp | Bin 36864 -> 0 bytes System/Cmd/Utils.hs | 568 ----------------------- Utility/CoProcess.hs | 14 +- Utility/Gpg.hs | 39 +- Utility/INotify.hs | 8 +- Utility/Lsof.hs | 7 +- Utility/Process.hs | 40 ++ Utility/SafeCommand.hs | 49 +- Utility/TempFile.hs | 2 +- doc/todo/assistant_threaded_runtime.mdwn | 3 + git-annex.cabal | 6 +- test.hs | 1 + 32 files changed, 178 insertions(+), 740 deletions(-) delete mode 100644 System/Cmd/.Utils.hs.swp delete mode 100644 System/Cmd/Utils.hs create mode 100644 Utility/Process.hs diff --git a/Annex/Branch.hs b/Annex/Branch.hs index e551bfcd01..8e7f45a4ad 100644 --- a/Annex/Branch.hs +++ b/Annex/Branch.hs @@ -164,9 +164,7 @@ get' staleok file = fromcache =<< getCache file fromjournal Nothing | staleok = withIndex frombranch | otherwise = withIndexUpdate $ frombranch >>= cache - frombranch = do - liftIO $ putStrLn $ "frombranch " ++ file - L.unpack <$> catFile fullname file + frombranch = L.unpack <$> catFile fullname file cache content = do setCache file content return content diff --git a/Annex/UUID.hs b/Annex/UUID.hs index 517840fbad..1d2175bcb6 100644 --- a/Annex/UUID.hs +++ b/Annex/UUID.hs @@ -20,6 +20,8 @@ module Annex.UUID ( removeRepoUUID, ) where +import System.Process + import Common.Annex import qualified Git import qualified Git.Config @@ -32,8 +34,10 @@ configkey = annexConfig "uuid" {- Generates a UUID. There is a library for this, but it's not packaged, - so use the command line tool. -} genUUID :: IO UUID -genUUID = pOpen ReadFromPipe command params $ liftM toUUID . hGetLine +genUUID = gen . lines <$> readProcess command params [] where + gen [] = error $ "no output from " ++ command + gen (l:_) = toUUID l command = SysConfig.uuid params -- request a random uuid be generated diff --git a/Backend/SHA.hs b/Backend/SHA.hs index cf61139e00..a1dd1cf648 100644 --- a/Backend/SHA.hs +++ b/Backend/SHA.hs @@ -12,6 +12,7 @@ import qualified Annex import Types.Backend import Types.Key import Types.KeySource +import System.Process import qualified Build.SysConfig as SysConfig import Data.Digest.Pure.SHA @@ -53,14 +54,16 @@ shaN shasize file filesize = do showAction "checksum" case shaCommand shasize filesize of Left sha -> liftIO $ sha <$> L.readFile file - Right command -> liftIO $ runcommand command + Right command -> liftIO $ parse command . lines <$> + readProcess command (toCommand [File file]) "" where - runcommand command = - pOpen ReadFromPipe command (toCommand [File file]) $ \h -> do - sha <- fst . separate (== ' ') <$> hGetLine h - if null sha - then error $ command ++ " parse error" - else return sha + parse command [] = bad command + parse command (l:_) + | null sha = bad command + | otherwise = sha + where + sha = fst $ separate (== ' ') l + bad command = error $ command ++ " parse error" shaCommand :: SHASize -> Integer -> Either (L.ByteString -> String) String shaCommand shasize filesize diff --git a/Build/Configure.hs b/Build/Configure.hs index cf6623b226..9468e1704d 100644 --- a/Build/Configure.hs +++ b/Build/Configure.hs @@ -4,7 +4,7 @@ module Build.Configure where import System.Directory import Data.List -import System.Cmd.Utils +import System.Process import Control.Applicative import System.FilePath @@ -71,7 +71,7 @@ getVersionString = do getGitVersion :: Test getGitVersion = do - (_, s) <- pipeFrom "git" ["--version"] + s <- readProcess "git" ["--version"] "" let version = unwords $ drop 2 $ words $ head $ lines s return $ Config "gitversion" (StringConfig version) diff --git a/Command/Fsck.hs b/Command/Fsck.hs index 10cca489b1..0e3cc934c3 100644 --- a/Command/Fsck.hs +++ b/Command/Fsck.hs @@ -7,6 +7,8 @@ module Command.Fsck where +import System.Posix.Process (getProcessID) + import Common.Annex import Command import qualified Annex diff --git a/Command/Map.hs b/Command/Map.hs index 0773f68283..f69b88a5d6 100644 --- a/Command/Map.hs +++ b/Command/Map.hs @@ -9,6 +9,7 @@ module Command.Map where import Control.Exception.Extensible import qualified Data.Map as M +import System.Process import Common.Annex import Command @@ -198,9 +199,13 @@ tryScan r case result of Left _ -> return Nothing Right r' -> return $ Just r' - pipedconfig cmd params = safely $ - pOpen ReadFromPipe cmd (toCommand params) $ - Git.Config.hRead r + pipedconfig cmd params = safely $ do + (_, Just h, _, pid) <- + createProcess (proc cmd $ toCommand params) + { std_out = CreatePipe } + r' <- Git.Config.hRead r h + forceSuccessProcess pid cmd $ toCommand params + return r' configlist = onRemote r (pipedconfig, Nothing) "configlist" [] [] diff --git a/Common.hs b/Common.hs index 7f07781ce9..04ec1e044e 100644 --- a/Common.hs +++ b/Common.hs @@ -13,16 +13,15 @@ import Data.String.Utils as X import System.Path as X import System.FilePath as X import System.Directory as X -import System.Cmd.Utils as X hiding (safeSystem) import System.IO as X hiding (FilePath) import System.Posix.Files as X import System.Posix.IO as X -import System.Posix.Process as X hiding (executeFile) import System.Exit as X import Utility.Misc as X import Utility.Exception as X import Utility.SafeCommand as X +import Utility.Process as X import Utility.Path as X import Utility.Directory as X import Utility.Monad as X diff --git a/Config.hs b/Config.hs index e66947e2cc..84f6125c63 100644 --- a/Config.hs +++ b/Config.hs @@ -7,6 +7,8 @@ module Config where +import System.Process + import Common.Annex import qualified Git import qualified Git.Config @@ -56,7 +58,7 @@ remoteCost r def = do cmd <- getRemoteConfig r "cost-command" "" (fromMaybe def . readish) <$> if not $ null cmd - then liftIO $ snd <$> pipeFrom "sh" ["-c", cmd] + then liftIO $ readProcess "sh" ["-c", cmd] "" else getRemoteConfig r "cost" "" cheapRemoteCost :: Int @@ -116,4 +118,4 @@ getHttpHeaders = do cmd <- getConfig (annexConfig "http-headers-command") "" if null cmd then fromRepo $ Git.Config.getList "annex.http-headers" - else lines . snd <$> liftIO (pipeFrom "sh" ["-c", cmd]) + else lines <$> liftIO (readProcess "sh" ["-c", cmd] "") diff --git a/Git/Branch.hs b/Git/Branch.hs index 6f3d251863..4d239d8fc5 100644 --- a/Git/Branch.hs +++ b/Git/Branch.hs @@ -76,9 +76,7 @@ commit message branch parentrefs repo = do sha <- getSha "commit-tree" $ pipeWriteRead (map Param $ ["commit-tree", show tree] ++ ps) message repo - print ("got", sha) run "update-ref" [Param $ show branch, Param $ show sha] repo - print ("update-ref done", sha) return sha where ps = concatMap (\r -> ["-p", show r]) parentrefs diff --git a/Git/CatFile.hs b/Git/CatFile.hs index e8f362685d..e667b20879 100644 --- a/Git/CatFile.hs +++ b/Git/CatFile.hs @@ -50,16 +50,11 @@ catObjectDetails :: CatFileHandle -> Ref -> IO (Maybe (L.ByteString, Sha)) catObjectDetails h object = CoProcess.query h send receive where send to = do - putStrLn "catObjectDetails send start" fileEncoding to hPutStrLn to $ show object - putStrLn $ "catObjectDetails send done " ++ show object receive from = do - putStrLn "catObjectDetails read header start" fileEncoding from - putStrLn "catObjectDetails read header start2" header <- hGetLine from - putStrLn "catObjectDetails read header done" case words header of [sha, objtype, size] | length sha == shaSize && @@ -72,14 +67,9 @@ catObjectDetails h object = CoProcess.query h send receive | header == show object ++ " missing" -> dne | otherwise -> error $ "unknown response from git cat-file " ++ show (header, object) readcontent bytes from sha = do - putStrLn "readcontent start" content <- S.hGet from bytes - putStrLn "readcontent end" c <- hGetChar from - putStrLn "readcontent newline read" when (c /= '\n') $ error "missing newline from git cat-file" return $ Just (L.fromChunks [content], Ref sha) - dne = do - putStrLn "dne" - return Nothing + dne = return Nothing diff --git a/Git/CheckAttr.hs b/Git/CheckAttr.hs index 7636ea6411..6b321f8b8f 100644 --- a/Git/CheckAttr.hs +++ b/Git/CheckAttr.hs @@ -44,15 +44,11 @@ checkAttr (h, attrs, cwd) want file = do _ -> error $ "unable to determine " ++ want ++ " attribute of " ++ file where send to = do - putStrLn "checkAttr send start" fileEncoding to hPutStr to $ file' ++ "\0" - putStrLn "checkAttr send end" receive from = forM attrs $ \attr -> do - putStrLn "checkAttr receive start" fileEncoding from l <- hGetLine from - putStrLn "checkAttr receive end" return (attr, attrvalue attr l) {- Before git 1.7.7, git check-attr worked best with - absolute filenames; using them worked around some bugs diff --git a/Git/Command.hs b/Git/Command.hs index 9a09300e24..038824f268 100644 --- a/Git/Command.hs +++ b/Git/Command.hs @@ -7,10 +7,8 @@ module Git.Command where -import qualified Data.Text.Lazy as L -import qualified Data.Text.Lazy.IO as L -import Control.Concurrent -import Control.Exception (finally) +import System.Process +import System.Posix.Process (getAnyProcessStatus) import Common import Git @@ -44,31 +42,18 @@ run subcommand params repo = assertLocal repo $ -} pipeRead :: [CommandParam] -> Repo -> IO String pipeRead params repo = assertLocal repo $ do - (_, h) <- hPipeFrom "git" $ toCommand $ gitCommandLine params repo + (_, Just h, _, _) <- createProcess + (proc "git" $ toCommand $ gitCommandLine params repo) + { std_out = CreatePipe } fileEncoding h hGetContents h -{- Runs a git subcommand, feeding it input. - - You should call either getProcessStatus or forceSuccess on the PipeHandle. -} -pipeWrite :: [CommandParam] -> L.Text -> Repo -> IO PipeHandle -pipeWrite params s repo = assertLocal repo $ do - (p, h) <- hPipeTo "git" (toCommand $ gitCommandLine params repo) - L.hPutStr h s - hClose h - return p - {- Runs a git subcommand, feeding it input, and returning its output, - which is expected to be fairly small, since it's all read into memory - strictly. -} pipeWriteRead :: [CommandParam] -> String -> Repo -> IO String -pipeWriteRead params s repo = assertLocal repo $ do - (p, from, to) <- hPipeBoth "git" (toCommand $ gitCommandLine params repo) - fileEncoding to - fileEncoding from - _ <- forkIO $ finally (hPutStr to s) (hClose to) - c <- hGetContentsStrict from - forceSuccess p - return c +pipeWriteRead params s repo = assertLocal repo $ + readProcess "git" (toCommand $ gitCommandLine params repo) s {- Reads null terminated output of a git command (as enabled by the -z - parameter), and splits it. -} diff --git a/Git/Config.hs b/Git/Config.hs index c9e4f9a2dc..2347501131 100644 --- a/Git/Config.hs +++ b/Git/Config.hs @@ -9,6 +9,7 @@ module Git.Config where import qualified Data.Map as M import Data.Char +import System.Process import Common import Git @@ -39,7 +40,7 @@ reRead :: Repo -> IO Repo reRead = read' {- Cannot use pipeRead because it relies on the config having been already - - read. Instead, chdir to the repo. + - read. Instead, chdir to the repo and run git config. -} read' :: Repo -> IO Repo read' repo = go repo @@ -47,9 +48,14 @@ read' repo = go repo go Repo { location = Local { gitdir = d } } = git_config d go Repo { location = LocalUnknown d } = git_config d go _ = assertLocal repo $ error "internal" - git_config d = bracketCd d $ - pOpen ReadFromPipe "git" ["config", "--null", "--list"] $ - hRead repo + git_config d = do + (_, Just h, _, pid) + <- createProcess (proc "git" params) + { std_out = CreatePipe, cwd = Just d } + repo' <- hRead repo h + forceSuccessProcess pid "git" params + return repo' + params = ["config", "--null", "--list"] {- Reads git config from a handle and populates a repo with it. -} hRead :: Repo -> Handle -> IO Repo diff --git a/Git/Queue.hs b/Git/Queue.hs index ddcf135197..4e6f05c2e0 100644 --- a/Git/Queue.hs +++ b/Git/Queue.hs @@ -19,7 +19,7 @@ module Git.Queue ( import qualified Data.Map as M import System.IO -import System.Cmd.Utils +import System.Process import Data.String.Utils import Utility.SafeCommand @@ -148,11 +148,14 @@ runAction :: Repo -> Action -> IO () runAction repo (UpdateIndexAction streamers) = -- list is stored in reverse order Git.UpdateIndex.streamUpdateIndex repo $ reverse streamers -runAction repo action@(CommandAction {}) = - pOpen WriteToPipe "xargs" ("-0":"git":params) feedxargs +runAction repo action@(CommandAction {}) = do + (Just h, _, _, pid) <- createProcess (proc "xargs" params) + { std_in = CreatePipe } + fileEncoding h + hPutStr h $ join "\0" $ getFiles action + hClose h + forceSuccessProcess pid "xargs" params where - params = toCommand $ gitCommandLine + params = "-0":"git":baseparams + baseparams = toCommand $ gitCommandLine (Param (getSubcommand action):getParams action) repo - feedxargs h = do - fileEncoding h - hPutStr h $ join "\0" $ getFiles action diff --git a/Git/Ref.hs b/Git/Ref.hs index 3052d0a6ef..ee2f021871 100644 --- a/Git/Ref.hs +++ b/Git/Ref.hs @@ -40,10 +40,7 @@ exists ref = runBool "show-ref" {- Get the sha of a fully qualified git ref, if it exists. -} sha :: Branch -> Repo -> IO (Maybe Sha) -sha branch repo = do - r <- process <$> showref repo - print r - return r +sha branch repo = process <$> showref repo where showref = pipeRead [Param "show-ref", Param "--hash", -- get the hash diff --git a/Git/UpdateIndex.hs b/Git/UpdateIndex.hs index abdc4bcbe3..6de0c3adab 100644 --- a/Git/UpdateIndex.hs +++ b/Git/UpdateIndex.hs @@ -17,7 +17,7 @@ module Git.UpdateIndex ( stageSymlink ) where -import System.Cmd.Utils +import System.Process import Common import Git @@ -37,12 +37,13 @@ pureStreamer !s = \streamer -> streamer s {- Streams content into update-index from a list of Streamers. -} streamUpdateIndex :: Repo -> [Streamer] -> IO () streamUpdateIndex repo as = do - (p, h) <- hPipeTo "git" (toCommand $ gitCommandLine params repo) + (Just h, _, _, p) <- createProcess (proc "git" ps) { std_in = CreatePipe } fileEncoding h forM_ as (stream h) hClose h - forceSuccess p + forceSuccessProcess p "git" ps where + ps = toCommand $ gitCommandLine params repo params = map Param ["update-index", "-z", "--index-info"] stream h a = a (streamer h) streamer h s = do diff --git a/Remote/Bup.hs b/Remote/Bup.hs index 0d1b606d3d..9da374174b 100644 --- a/Remote/Bup.hs +++ b/Remote/Bup.hs @@ -136,9 +136,11 @@ retrieveEncrypted :: BupRepo -> (Cipher, Key) -> Key -> FilePath -> Annex Bool retrieveEncrypted buprepo (cipher, enck) _ f = do let params = bupParams "join" buprepo [Param $ bupRef enck] liftIO $ catchBoolIO $ do - (pid, h) <- hPipeFrom "bup" $ toCommand params + (_, Just h, _, pid) + <- createProcess (proc "bup" $ toCommand params) + { std_out = CreatePipe } withDecryptedContent cipher (L.hGetContents h) $ L.writeFile f - forceSuccess pid + forceSuccessProcess pid "bup" $ toCommand params return True remove :: Key -> Annex Bool diff --git a/Remote/Git.hs b/Remote/Git.hs index d80f580fc5..a9a6d6004e 100644 --- a/Remote/Git.hs +++ b/Remote/Git.hs @@ -9,6 +9,7 @@ module Remote.Git (remote, repoAvail) where import qualified Data.Map as M import Control.Exception.Extensible +import System.Process import Common.Annex import Utility.CopyFile @@ -126,17 +127,20 @@ tryGitConfigRead r safely a = either (const $ return r) return =<< liftIO (try a :: IO (Either SomeException Git.Repo)) - pipedconfig cmd params = safely $ - pOpen ReadFromPipe cmd (toCommand params) $ - Git.Config.hRead r + pipedconfig cmd params = safely $ do + (_, Just h, _, pid) <- + createProcess (proc cmd $ toCommand params) + { std_out = CreatePipe } + r' <- Git.Config.hRead r h + forceSuccessProcess pid cmd $ toCommand params + return r' geturlconfig headers = do s <- Url.get (Git.repoLocation r ++ "/config") headers withTempFile "git-annex.tmp" $ \tmpfile h -> do hPutStr h s hClose h - pOpen ReadFromPipe "git" ["config", "--null", "--list", "--file", tmpfile] $ - Git.Config.hRead r + pipedconfig "git" [Param "config", Param "--null", Param "--list", Param "--file", File tmpfile] store = observe $ \r' -> do g <- gitRepo diff --git a/Remote/Hook.hs b/Remote/Hook.hs index 9e8d3c620d..cad6e2fc94 100644 --- a/Remote/Hook.hs +++ b/Remote/Hook.hs @@ -9,7 +9,6 @@ module Remote.Hook (remote) where import qualified Data.ByteString.Lazy as L import qualified Data.Map as M -import System.Exit import System.Environment import Common.Annex @@ -136,17 +135,5 @@ checkPresent r h k = do findkey s = show k `elem` lines s check Nothing = error "checkpresent hook misconfigured" check (Just hook) = do - (frompipe, topipe) <- createPipe - pid <- forkProcess $ do - _ <- dupTo topipe stdOutput - closeFd frompipe - executeFile "sh" True ["-c", hook] - =<< hookEnv k Nothing - closeFd topipe - fromh <- fdToHandle frompipe - reply <- hGetContentsStrict fromh - hClose fromh - s <- getProcessStatus True False pid - case s of - Just (Exited ExitSuccess) -> return $ findkey reply - _ -> error "checkpresent hook failed" + env <- hookEnv k Nothing + findkey <$> readProcessEnv "sh" ["-c", hook] env diff --git a/Remote/Rsync.hs b/Remote/Rsync.hs index 29bceb2db8..ee516a8a59 100644 --- a/Remote/Rsync.hs +++ b/Remote/Rsync.hs @@ -9,6 +9,7 @@ module Remote.Rsync (remote) where import qualified Data.ByteString.Lazy as L import qualified Data.Map as M +import System.Posix.Process (getProcessID) import Common.Annex import Types.Remote diff --git a/System/Cmd/.Utils.hs.swp b/System/Cmd/.Utils.hs.swp deleted file mode 100644 index 65e9e77e4437e33e567a27e7f34f6b8301ca5f47..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 36864 zcmeI53zTFnT26r%!i0tpEy7@r{c2>Jf1y0>pX zW_A{3A=m@o_TyI7ty_=3>i_Gn>e;ntX11wQ(imGc8bJ`BaIp6md zgV%~hzI!I@f!jeoKMQukC?DkW)8SBful@Xoyq|$u0=*LGl|ZiqdL_^+fnEvpN}yK)y%Ok^K(7RPC2){Rz|A|(iQMad z(9320Uu*#1dA8%+1Yd-|g1>}Uz%Pz;oPU5T;B7Dke+;)Cfu0W^h8*<6orhy9fZO0( za2>o3rr}laLU7=7f8;nfz+Cyc-vNW>EdS+E9U-s%=Ud=A5lhY@0Dd$)BdL&l&)qLRAYF-eg9cRAi1)ifi{|1~@UNv7TL@%8o zl&VeEyy~EN*$}->yYtSfQlXmn3TpT6tvkkNcJG!i)bT04DpkFFs#2=X&2L!0d+X#( zcK77WfV%i%)qX8IJUu?zadr3ZZJF)kJBhn{V4z#J)l{kGZS(V9DxDq}>>7gNI#Esd z^FtHfUazdOzF!Wbr?k)9?O}_O^67rP*gaK!IqNTTaV+pF-7iayPL!NeE^5A1FRG$j z&6mBfYyNA?=0mP7l?}NzK@EgUXGMZ6eYG>AW%t5G71jfC-aWSkKiET)Fip7oh2h{qY+s>U@Roa+DGG3_u07KND}KIF_7YtK zN>$vw+`I&og4XHg-MULwr~psp+;Um&*PpD8eo{C!ijpmQTO`5)UnK*nS}7mbD}_Os z&4ruv4J1({7x$bC+zNdmto9?fya2i3icDMd>ZFz;g+aA2pk6UVVy4-uzH->7&hA^| z)pLF4I?h(4o8m#;s`3`xN{vF(1xwilzH~NsQ3PV%SEc$!#}V1+mg*ENrJZvdp{Ex8 zMi6I(>moVbKqApc=h9B=ldDD*uQ=rv$gScrlrF3SJzqcBjP5A%L=+&Eg-i|`6)&Gw zYRoN_8;Ig*ui{l^yeqG6NHw&V z`MNIOt>?RRI<0Rq7kD-0H|n(pwI8Z{DXf*B^;*d7)|Wv~3EcK{=P| zB`>7xMoraHfqizUobcz;Fy{q*X=ldssEg3wsQNoDryDh@$Qv)y5y~b;|Dcpxx4#q_ zGK0p*bS9e_8J-v*WM>L0$_690>F(*K*yv*tr0-TX92%|& zr=7#o+ZoACG%}&we4gs`tImjDsUSamw2v%~+o783dzhwi6})ffxovDax=Fq*S5K(Y8{Y18(Z?NUJ>QHCEKU!j7^ks zUX`-qZ=)LDzC(>qO$;h#i;}QfuV^OjtiM;!6G!~oV!*Ifm$1zbsgVJ-e(lYm!L zVeKHTF|7Mk$hKjn)~;W-Zr#wj4Qo$PYRAm53V#Y7j=V{z}@C%E6qnt-j@AZ(gIj^)=It22%riW6Aq|3>pq^X;!#%#HiQ??u( zXX$IY&*{-N?@>`WP&?a3r$@F9Z_f^&o|(vGcS&iFWwP5xXJ*vc7AME*2x`NHN1V7bgXF-+qFpxO9Z*1V^(#a6B$#IuH*)R zTdm8JI9ZuvL?f+{_l!{_N;rC@JZRCc$*t&D(a1<|W=twH%1Fu--|I2b*HU5tnX!l( zBIBQJKxwC=j8(IyHz|)=YKE5PCQ~0TD$PL(#Np0b*ysx~69}VF%M>*NtR@u`7I~Q2 z#g1n!NVSKy+Ba#DDzZ5681!r*$Ri_+)=(!*#7YJH>sQj|m+Wm94bj?Hsfpq3<2#1O zN7cyGlv>4<4`J*Ex#CdWos(W=Bw#E)RD~|B3Z=5=i2i>Gdh5H;ZAJed=H<)i`fq{@ zAPc9!bK#puI?gBIeQ*_s4dAWta!A2L==~4E9dJ9m4HjS?)`J7TLFd070vLjypyOW; z&xb?cJLveIfY(C?j)uF?>AwnBLm5s5(e=NN9{=C)b$ADy3n#!Ka4&lNJ#ZU*5k3QN zgbQFB90|YTnSTjCg9qS#xDli*u7ciQuLOD}&?|vn2^{h>qfo2qrc zX2Ner|3-sbE{L6dPl?SfJ)>2NFrAsJV$C_=XlN!=nW@q4@w(nf>`9nKjDakOBL<#Z zHcv;xp_rH^scwH(8@7_Cu=999fHgC(o6Y`1 z%j}xaliFIc|KQBw2%V{7Lx}@7+lhH{wZcE!K2y!swZDkDvLAY5^iWJMh0d7>lT-VQmQ&-5ZmOC_4HEkyTTgnHWM+Xp3Ti%ll%0 zta_*sp(3%afu)R~Ls|I)G( zF=KJL|Cr{v5^=Xl1t@C2>z}^sIQ2yHlpbL1m8gTw>ZZ6?o`}?6OCrtsMeeU4of+1i zBsbIy&!S72tRNWYQCxMkNq_ZnI?Hl5u^5@$4=S3h=xv2k5Z2QU4bG~sQkAqsZS{$4 zsv*WOo>F1w&{{cqZj}!hjoIdmnr%#NtaFBH*W`|Anrv9ZXj?L7oZ~UqiV-$cr3z-; z5^672JZ+X24R$KCB~nv$`y#y^+HTb^R%Y9D`{mxUj7LV5yO(iGn}ztYY1tPGiJES3 zAF)Ab?QoE+m?Dsts+%O{d2C5o!Z9jztf4$UD{yUNv~69sGX#617HF)-6II4MJ3g`y zsP*!`C{%~ceI(e(n66nn9=FbEICQw%$P_QfJlBu%gvxsr%sB1Si9=3|b+ zHrL`D*n2RV>!E1%@p8NFF}Yx(v2b7~2F(_}9|`7|ki_dI==7}<(oQ923NlR){r~H% zAE#M&7X4p*_8&plza4IYcfvd1EwB$RhgZUj;0|>DYvD5R!G+hrVekmL{td7XM&Sr} z0Db@4@Kv}G{t-S0IS{{qemDUh!Vd5td;rdZov;~R4u``JunF7@pM&?nKG*}N!lT#) zZh%W+2ERs%XKxLRub*^d7h#EpH4EKIx_&<@j6~)XHw-niuv1JYwSCZ&x38RJDDT`)VUnXZFnUa^wTH!MFJJ1?e2U_LoG1R&0sPvZNa+<}n{JXf; zTgq$c=*w37G#)@>SPi<=yD^7VTI^xAFKcTVhMl@6@#0(4Xmri0S|y&z>wZB~i;ZGQ zgP2O$_8*Uh_Ki&kSuZybpFe4ov6jsHcnlmm)ln#q%g9$eJ3{d_akW@6%B$8t2eoS1 zpJ@91qWO0Vj2@b1krWPW zKfVlZ7?OnOl<22;28zz86=N1K?H#b}SO>4PqnFf`cxOfr)DhUKkx!(iSn`c|)-;Y- zH^TxUz7WQWDGk#@456O&*&dPiwspGr@sTf0= zQSfXKUH_x-TDTY{;Fa(TGW-enI9v&Dg;_Wao)6E4AEWQz2{*#u!VWkRZb$F`7&M?C z{tI3IYw$jJ4Ll$2MZdouE`?LzA@utn!F_NqTmhHBcGw0RU_Ja0{r~fD12kYQ+>gKh zC!qmr;Y#c-mjXRR{-VZUKG}~wtuhj%PdV##Ppf>Q?aH>Nb-Z-ZGFs-ntuuvW^qyAP z(<}i#v8TPbFy@_)r8#Nt~B0a6Li?7?`p;d|s8E>bI zo%^+)lr^%ogy?Jew1V&~L$^jje_q1u*6O0eHXS?|!j8?5>DJ`1)L}*w?-Og#!qSZO zt7@FvjC+N#zR2b;Z9ZdjjOS0ro5Sde7aQ7x`$g<)+?X%R!*{Zn(N=7wDp|WuFAbJ^mN> zAl#SOghS58utmt0J~7*I-$q%!oVE@lZT=x)W7g(C+=sA}bayz>`oAofeic1b^#2Mk ze}~S0CCtOw@KQ*_bKnqo0G0iFh5 z!8Y(-coT%M4UU03umyYpu7X)O8?rD1zriN(0DKre1ac0*QScLN13!ju!>w=?Tnf8k z3k<;ta2&iCr0$*ocO0`{HWw>HIkC_ear+watL${cq-~a_=rty2QE%7O+la;dADQc& z8s_%o7x?7GUo9^R5`H~w<Xmb@!B=ar9!-ixh&u3)ubWvHiBi&D8eG zbbHUm$0}&sqpU6Hk*(gWFtBfVa{I(CH9VFboz}+oux-CC%NcpG^6G7WvVU`zxRiiqn zlUmv8)q$!J%pJNqavMKxJ-3kgMf0!e2F_Nus)%76&upV*oxr-NuXdU-qIb)9fLlK= zv*MLl@IqX-I$zYJU#-X?Ji2S*HEA_oxreh!ATHOgYleD>FZN2;s}kZVnWeY47)!*B zaR3VS2){5<)t*_P4a#c3bBSY!=oN zj;Qj}?7i+7)XgqOy=E76J*D;|cJxsTxCOH#ReP0+2(atJ%|$x1bjW8pmBEYlIkp`b zz~)A?TDO0BVRH9`ii$(+!g=5v8n4%_R-sua!)Le8IaD_jx7&4G|ATs;BW*?;S+#G0 zlW6ler)bxkBt{CrQ+wWw(jl;vuVtao3NR=c0gIWyp%J(;&|t zDY}8)d$QC#wiyC{ESz;|S@`2t#rIayZ?^QvwSa|yp`pAt+nC#?QiPtBjU$r9v|jv@ zNCQTNOl+GONTy4^_P3o)EiEtu?4IvY~Br{K|}j7;Tw$We<&bI6#+aMybXfty`!!3(1PCha~v}}Uw znv8M62)kahmDTlHX7X{;@MQge9XkI{tp2};_di0%{~){%u7N2y3=W0+(d&Nzx4^%^ z+u;%r-Cy+nqv0;}{SU!Ka6U}KOW>#I`r_|@H8kLK*aRoR1`t1he+Kadkn;d91M&Hn zvjP4T9!1apHQWRrgUcZYa!$Z0uoea&1>Z#fzY$&!TVWg?M#uj&dM^ue>> z>F_1={lAARL3{&tf!F|kh@SshxE#)a{r# zYeDu2eD@Ii6<{A+4kyD);d$^)^m;i5@C|S_oD9c;ocZ?%b@fw_I{UHI+X4OABkAmm zmCJT$-@i&PGGS?t(^NEP^_x1J*y5N~tY-g|?x`wOoHB<#)%{|0tdALd;z@+Q3&)C) zj5aEWdz#5?RgA3lA{ojbG%vAb8)dV8D2q0efz&i6gG7UgrX13`n28qJ9G>gG zb_|a~>4@#&MBkMQEg@U9;kH!bYohsf#Ej=YEpHCY1fiC)LFfXAC)C|+5bCL6gpi_b zEB2Q1v>&VqLaNY)76U}o9qc24*J3(v}^2|0r6Qt4%wI zso$m@M2oga^R#vl{oOL+u3gBP`SYNhk%;f_vi1;U)6ymoxi10u*O*V)DvQu4`?)=O zVr^zg7>F_0W_^qA!`zRuebUWU|p*=yH1T8REXg8q1&=#i}d@8m_+|IdS?LG=88 z1<~{6-2XaE!Ex|Qbo!e>&i&sFvd;f=^!S_L-LM@}a2LA!ZSY-?_5E?^gX7^wboGCN zx5EOQ2M?jEi~jy4kTd_zgemBU=fd~V(XWOx;W=;w91fpFNB^+Z*N@@#QFQbFh3nuN zcrRQ4C&TmLm+0s>!<%6zybN9hvY-DpxE3yiSHsKTKJ@ZiMK=doudl)>@C>*Gz5HDu z=k;Fz=R*!=;c)mByi+JCu9fATpc^yT@+fYVO#IjCvTGU5@dMTtGOUlru3! zNtJU#L`Ov_?`#VP#fKmg>rE-j?l)r=+vbLQl+Q6&9LL?fY~Qt>^d#G{UbQ2WmEad} zgsVbd?{ZQV28GUene93nlhQ7+n6qNu_N+UQBroBjyO_*jWa!9Va-Frd?CzXqRC2eH z+v%I>Jw4`BA-f}JsjNkLvnCy0u;xZzHgB%q*-{hph~5RK`l4@4Y}xrF^VW9R7@u*{ zmYzPgNuPHXZ+w<<#N>e`Hoe$gsmWohQI1wz0^CYsqDi&q#+=(V#*y6E=4C}%=A%*i z(H9a?Oi^~eq*BS}>QznSC;^^k`@FoHe&xzC~gnTu! zbz+O+B;xv_`EI7!=1EgGX%g*hyt>hw67Ph3CxVkGmG}dTU~1MURR~QDiwh0T2=OR?C8ksv^|1Jls@U6*x8ukh#8Od zmF=8;9GLUWwV}+5mLa${Sw*Lf&s#FX_JK<2rgTo+{@^VPw%Ua0aB?`f&kq#H0y{FI zWz%V2;t2Y9HAy>##)pjQ6td0VS$OP;$Pd$yisiP(sZXTMXC5iM2Prrh!( zo+{cgCNd+gX2I6>bAFzH(McAFwOfgHiQ@}hlgUK%NS}&g5kmT6M<|KW?QRK~a9}q~ zL|pEk2r4TRI-GUdM1kbcJc|_y?INb@b9KhBopV5oqz*|UchP^*^a^p)tz5=g`>*1l zWDm77<4*fzOHZQg%2IP4C5@j6rTyMaNLohT$7&F&ZQR@F zt(^!A{Y3zKn_^6Ghh2FCu!^Jq3j)OO=PyvRc$AaYA3#Jo;oxA83TA? kXMxq-cZm2{p|^=Vjz23t9QrXmIpM%msg~Kl`=31fKh*qing9R* diff --git a/System/Cmd/Utils.hs b/System/Cmd/Utils.hs deleted file mode 100644 index a81126146b..0000000000 --- a/System/Cmd/Utils.hs +++ /dev/null @@ -1,568 +0,0 @@ --- arch-tag: Command utilities main file -{-# LANGUAGE CPP #-} -{- -Copyright (C) 2004-2006 John Goerzen - -This program is free software; you can redistribute it and/or modify -it under the terms of the GNU General Public License as published by -the Free Software Foundation; either version 2 of the License, or -(at your option) any later version. - -This program is distributed in the hope that it will be useful, -but WITHOUT ANY WARRANTY; without even the implied warranty of -MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -GNU General Public License for more details. - -You should have received a copy of the GNU General Public License -along with this program; if not, write to the Free Software -Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA --} - -{- | - Module : System.Cmd.Utils - Copyright : Copyright (C) 2004-2006 John Goerzen - License : GNU GPL, version 2 or above - - Maintainer : John Goerzen - Stability : provisional - Portability: portable to platforms with POSIX process\/signal tools - -Command invocation utilities. - -Written by John Goerzen, jgoerzen\@complete.org - -Please note: Most of this module is not compatible with Hugs. - -Command lines executed will be logged using "System.Log.Logger" at the -DEBUG level. Failure messages will be logged at the WARNING level in addition -to being raised as an exception. Both are logged under -\"System.Cmd.Utils.funcname\" -- for instance, -\"System.Cmd.Utils.safeSystem\". If you wish to suppress these messages -globally, you can simply run: - -> updateGlobalLogger "System.Cmd.Utils.safeSystem" -> (setLevel CRITICAL) - -See also: 'System.Log.Logger.updateGlobalLogger', -"System.Log.Logger". - -It is possible to set up pipelines with these utilities. Example: - -> (pid1, x1) <- pipeFrom "ls" ["/etc"] -> (pid2, x2) <- pipeBoth "grep" ["x"] x1 -> putStr x2 -> ... the grep output is displayed ... -> forceSuccess pid2 -> forceSuccess pid1 - -Remember, when you use the functions that return a String, you must not call -'forceSuccess' until after all data from the String has been consumed. Failure -to wait will cause your program to appear to hang. - -Here is an example of the wrong way to do it: - -> (pid, x) <- pipeFrom "ls" ["/etc"] -> forceSuccess pid -- Hangs; the called program hasn't terminated yet -> processTheData x - -You must instead process the data before calling 'forceSuccess'. - -When using the hPipe family of functions, this is probably more obvious. - -Most of this module will be incompatible with Windows. --} - - -module System.Cmd.Utils(-- * High-Level Tools - PipeHandle(..), - safeSystem, -#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) - forceSuccess, -#ifndef __HUGS__ - posixRawSystem, - forkRawSystem, - -- ** Piping with lazy strings - pipeFrom, - pipeLinesFrom, - pipeTo, - pipeBoth, - -- ** Piping with handles - hPipeFrom, - hPipeTo, - hPipeBoth, -#endif -#endif - -- * Low-Level Tools - PipeMode(..), -#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) -#ifndef __HUGS__ - pOpen, pOpen3, pOpen3Raw -#endif -#endif - ) -where - --- FIXME - largely obsoleted by 6.4 - convert to wrappers. - -import System.Exit -import System.Cmd -#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) -import System.Posix.IO -import System.Posix.Process -import System.Posix.Signals -import qualified System.Posix.Signals -#endif -import System.Posix.Types -import System.IO -import System.IO.Error -import Control.Concurrent(forkIO) -import Control.Exception(finally) - -data PipeMode = ReadFromPipe | WriteToPipe - -logbase :: String -logbase = "System.Cmd.Utils" - -{- | Return value from 'pipeFrom', 'pipeLinesFrom', 'pipeTo', or -'pipeBoth'. Contains both a ProcessID and the original command that was -executed. If you prefer not to use 'forceSuccess' on the result of one -of these pipe calls, you can use (processID ph), assuming ph is your 'PipeHandle', -as a parameter to 'System.Posix.Process.getProcessStatus'. -} -data PipeHandle = - PipeHandle { processID :: ProcessID, - phCommand :: FilePath, - phArgs :: [String], - phCreator :: String -- ^ Function that created it - } - deriving (Eq, Show) - -#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) -#ifndef __HUGS__ -{- | Like 'pipeFrom', but returns data in lines instead of just a String. -Shortcut for calling lines on the result from 'pipeFrom'. - -Note: this function logs as pipeFrom. - -Not available on Windows. -} -pipeLinesFrom :: FilePath -> [String] -> IO (PipeHandle, [String]) -pipeLinesFrom fp args = - do (pid, c) <- pipeFrom fp args - return $ (pid, lines c) -#endif -#endif - -logRunning :: String -> FilePath -> [String] -> IO () -logRunning func fp args = return () --debugM (logbase ++ "." ++ func) (showCmd fp args) - -warnFail :: [Char] -> FilePath -> [String] -> [Char] -> IO t -warnFail funcname fp args msg = - let m = showCmd fp args ++ ": " ++ msg - in do putStrLn m - fail m - -ddd s a = do - putStrLn $ s ++ " start" - r <- a - putStrLn $ s ++ " end" - return r - -#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) -#ifndef __HUGS__ -{- | Read data from a pipe. Returns a Handle and a 'PipeHandle'. - -When done, you must hClose the handle, and then use either 'forceSuccess' or -getProcessStatus on the 'PipeHandle'. Zombies will result otherwise. - -This function logs as pipeFrom. - -Not available on Windows or with Hugs. --} -hPipeFrom :: FilePath -> [String] -> IO (PipeHandle, Handle) -hPipeFrom fp args = - ddd (show ("hPipeFrom", fp, args)) $ do - pipepair <- createPipe - let childstuff = do dupTo (snd pipepair) stdOutput - closeFd (fst pipepair) - executeFile fp True args Nothing - p <- try (forkProcess childstuff) - -- parent - pid <- case p of - Right x -> return x - Left e -> warnFail "pipeFrom" fp args $ - "Error in fork: " ++ show e - closeFd (snd pipepair) - h <- fdToHandle (fst pipepair) - return (PipeHandle pid fp args "pipeFrom", h) -#endif -#endif - -#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) -#ifndef __HUGS__ -{- | Read data from a pipe. Returns a lazy string and a 'PipeHandle'. - -ONLY AFTER the string has been read completely, You must call either -'System.Posix.Process.getProcessStatus' or 'forceSuccess' on the 'PipeHandle'. -Zombies will result otherwise. - -Not available on Windows. --} -pipeFrom :: FilePath -> [String] -> IO (PipeHandle, String) -pipeFrom fp args = - do (pid, h) <- hPipeFrom fp args - c <- hGetContents h - return (pid, c) -#endif -#endif - -#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) -#ifndef __HUGS__ -{- | Write data to a pipe. Returns a 'PipeHandle' and a new Handle to write -to. - -When done, you must hClose the handle, and then use either 'forceSuccess' or -getProcessStatus on the 'PipeHandle'. Zombies will result otherwise. - -This function logs as pipeTo. - -Not available on Windows. --} -hPipeTo :: FilePath -> [String] -> IO (PipeHandle, Handle) -hPipeTo fp args = - ddd "hPipeTo" $ do - pipepair <- createPipe - let childstuff = do dupTo (fst pipepair) stdInput - closeFd (snd pipepair) - executeFile fp True args Nothing - p <- try (forkProcess childstuff) - -- parent - pid <- case p of - Right x -> return x - Left e -> warnFail "pipeTo" fp args $ - "Error in fork: " ++ show e - closeFd (fst pipepair) - h <- fdToHandle (snd pipepair) - return (PipeHandle pid fp args "pipeTo", h) -#endif -#endif - -#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) -#ifndef __HUGS__ -{- | Write data to a pipe. Returns a ProcessID. - -You must call either -'System.Posix.Process.getProcessStatus' or 'forceSuccess' on the ProcessID. -Zombies will result otherwise. - -Not available on Windows. --} -pipeTo :: FilePath -> [String] -> String -> IO PipeHandle -pipeTo fp args message = - do (pid, h) <- hPipeTo fp args - finally (hPutStr h message) - (hClose h) - return pid -#endif -#endif - -#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) -#ifndef __HUGS__ -{- | Like a combination of 'hPipeTo' and 'hPipeFrom'; returns -a 3-tuple of ('PipeHandle', Data From Pipe, Data To Pipe). - -When done, you must hClose both handles, and then use either 'forceSuccess' or -getProcessStatus on the 'PipeHandle'. Zombies will result otherwise. - -Hint: you will usually need to ForkIO a thread to handle one of the Handles; -otherwise, deadlock can result. - -This function logs as pipeBoth. - -Not available on Windows. --} -hPipeBoth :: FilePath -> [String] -> IO (PipeHandle, Handle, Handle) -hPipeBoth fp args = - ddd (show ("hPipeBoth", fp, args)) $ do - frompair <- createPipe - topair <- createPipe - let childstuff = do dupTo (snd frompair) stdOutput - closeFd (fst frompair) - dupTo (fst topair) stdInput - closeFd (snd topair) - executeFile fp True args Nothing - p <- try (forkProcess childstuff) - -- parent - pid <- case p of - Right x -> return x - Left e -> warnFail "pipeBoth" fp args $ - "Error in fork: " ++ show e - closeFd (snd frompair) - closeFd (fst topair) - fromh <- fdToHandle (fst frompair) - toh <- fdToHandle (snd topair) - return (PipeHandle pid fp args "pipeBoth", fromh, toh) -#endif -#endif - -#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) -#ifndef __HUGS__ -{- | Like a combination of 'pipeTo' and 'pipeFrom'; forks an IO thread -to send data to the piped program, and simultaneously returns its output -stream. - -The same note about checking the return status applies here as with 'pipeFrom'. - -Not available on Windows. -} -pipeBoth :: FilePath -> [String] -> String -> IO (PipeHandle, String) -pipeBoth fp args message = - do (pid, fromh, toh) <- hPipeBoth fp args - forkIO $ finally (hPutStr toh message) - (hClose toh) - c <- hGetContents fromh - return (pid, c) -#endif -#endif - -#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) -{- | Uses 'System.Posix.Process.getProcessStatus' to obtain the exit status -of the given process ID. If the process terminated normally, does nothing. -Otherwise, raises an exception with an appropriate error message. - -This call will block waiting for the given pid to terminate. - -Not available on Windows. -} -forceSuccess :: PipeHandle -> IO () -forceSuccess (PipeHandle pid fp args funcname) = - let warnfail = warnFail funcname - in do status <- getProcessStatus True False pid - case status of - Nothing -> warnfail fp args $ "Got no process status" - Just (Exited (ExitSuccess)) -> return () - Just (Exited (ExitFailure fc)) -> - cmdfailed funcname fp args fc - Just (Terminated sig) -> - warnfail fp args $ "Terminated by signal " ++ show sig - Just (Stopped sig) -> - warnfail fp args $ "Stopped by signal " ++ show sig -#endif - -{- | Invokes the specified command in a subprocess, waiting for the result. -If the command terminated successfully, return normally. Otherwise, -raises a userError with the problem. - -Implemented in terms of 'posixRawSystem' where supported, and System.Posix.rawSystem otherwise. --} -safeSystem :: FilePath -> [String] -> IO () -safeSystem command args = - ddd "safeSystem" $ do -#if defined(__HUGS__) || defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__) - ec <- rawSystem command args - case ec of - ExitSuccess -> return () - ExitFailure fc -> cmdfailed "safeSystem" command args fc -#else - ec <- posixRawSystem command args - case ec of - Exited ExitSuccess -> return () - Exited (ExitFailure fc) -> cmdfailed "safeSystem" command args fc - Terminated s -> cmdsignalled "safeSystem" command args s - Stopped s -> cmdsignalled "safeSystem" command args s -#endif - -#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) -#ifndef __HUGS__ -{- | Invokes the specified command in a subprocess, waiting for the result. -Return the result status. Never raises an exception. Only available -on POSIX platforms. - -Like system(3), this command ignores SIGINT and SIGQUIT and blocks SIGCHLD -during its execution. - -Logs as System.Cmd.Utils.posixRawSystem -} -posixRawSystem :: FilePath -> [String] -> IO ProcessStatus -posixRawSystem program args = - ddd "posixRawSystem" $ do - oldint <- installHandler sigINT Ignore Nothing - oldquit <- installHandler sigQUIT Ignore Nothing - let sigset = addSignal sigCHLD emptySignalSet - oldset <- getSignalMask - blockSignals sigset - childpid <- forkProcess (childaction oldint oldquit oldset) - - mps <- getProcessStatus True False childpid - restoresignals oldint oldquit oldset - let retval = case mps of - Just x -> x - Nothing -> error "Nothing returned from getProcessStatus" - return retval - - where childaction oldint oldquit oldset = - do restoresignals oldint oldquit oldset - executeFile program True args Nothing - restoresignals oldint oldquit oldset = - do installHandler sigINT oldint Nothing - installHandler sigQUIT oldquit Nothing - setSignalMask oldset - -#endif -#endif - -#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) -#ifndef __HUGS__ -{- | Invokes the specified command in a subprocess, without waiting for -the result. Returns the PID of the subprocess -- it is YOUR responsibility -to use getProcessStatus or getAnyProcessStatus on that at some point. Failure -to do so will lead to resource leakage (zombie processes). - -This function does nothing with signals. That too is up to you. - -Logs as System.Cmd.Utils.forkRawSystem -} -forkRawSystem :: FilePath -> [String] -> IO ProcessID -forkRawSystem program args = ddd "forkRawSystem" $ - do - forkProcess childaction - where - childaction = executeFile program True args Nothing - -#endif -#endif - -cmdfailed :: String -> FilePath -> [String] -> Int -> IO a -cmdfailed funcname command args failcode = do - let errormsg = "Command " ++ command ++ " " ++ (show args) ++ - " failed; exit code " ++ (show failcode) - let e = userError (errormsg) - putStrLn errormsg - ioError e - -#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) -#ifndef __HUGS__ -cmdsignalled :: String -> FilePath -> [String] -> Signal -> IO a -cmdsignalled funcname command args failcode = do - let errormsg = "Command " ++ command ++ " " ++ (show args) ++ - " failed due to signal " ++ (show failcode) - let e = userError (errormsg) - putStrLn errormsg - ioError e -#endif -#endif - -#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) -#ifndef __HUGS__ -{- | Open a pipe to the specified command. - -Passes the handle on to the specified function. - -The 'PipeMode' specifies what you will be doing. That is, specifing 'ReadFromPipe' -sets up a pipe from stdin, and 'WriteToPipe' sets up a pipe from stdout. - -Not available on Windows. - -} -pOpen :: PipeMode -> FilePath -> [String] -> - (Handle -> IO a) -> IO a -pOpen pm fp args func = ddd "pOpen" $ - do - pipepair <- createPipe - case pm of - ReadFromPipe -> do - let callfunc _ = do - closeFd (snd pipepair) - h <- fdToHandle (fst pipepair) - x <- func h - hClose h - return $! x - pOpen3 Nothing (Just (snd pipepair)) Nothing fp args - callfunc (closeFd (fst pipepair)) - WriteToPipe -> do - let callfunc _ = do - closeFd (fst pipepair) - h <- fdToHandle (snd pipepair) - x <- func h - hClose h - return $! x - pOpen3 (Just (fst pipepair)) Nothing Nothing fp args - callfunc (closeFd (snd pipepair)) -#endif -#endif - -#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) -#ifndef __HUGS__ -{- | Runs a command, redirecting things to pipes. - -Not available on Windows. - -Note that you may not use the same fd on more than one item. If you -want to redirect stdout and stderr, dup it first. --} -pOpen3 :: Maybe Fd -- ^ Send stdin to this fd - -> Maybe Fd -- ^ Get stdout from this fd - -> Maybe Fd -- ^ Get stderr from this fd - -> FilePath -- ^ Command to run - -> [String] -- ^ Command args - -> (ProcessID -> IO a) -- ^ Action to run in parent - -> IO () -- ^ Action to run in child before execing (if you don't need something, set this to @return ()@) -- IGNORED IN HUGS - -> IO a -pOpen3 pin pout perr fp args func childfunc = ddd (show ("pOpen3", fp, args)) $ - do pid <- pOpen3Raw pin pout perr fp args childfunc - putStrLn "got pid" - retval <- func $! pid - putStrLn "got retval" - let rv = seq retval retval - forceSuccess (PipeHandle (seq retval pid) fp args "pOpen3") - putStrLn "process finished" - return rv -#endif -#endif - -#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__)) -#ifndef __HUGS__ -{- | Runs a command, redirecting things to pipes. - -Not available on Windows. - -Returns immediately with the PID of the child. Using 'waitProcess' on it -is YOUR responsibility! - -Note that you may not use the same fd on more than one item. If you -want to redirect stdout and stderr, dup it first. --} -pOpen3Raw :: Maybe Fd -- ^ Send stdin to this fd - -> Maybe Fd -- ^ Get stdout from this fd - -> Maybe Fd -- ^ Get stderr from this fd - -> FilePath -- ^ Command to run - -> [String] -- ^ Command args - -> IO () -- ^ Action to run in child before execing (if you don't need something, set this to @return ()@) -- IGNORED IN HUGS - -> IO ProcessID -pOpen3Raw pin pout perr fp args childfunc = - let mayberedir Nothing _ = return () - mayberedir (Just fromfd) tofd = do - dupTo fromfd tofd - closeFd fromfd - return () - childstuff = do - mayberedir pin stdInput - mayberedir pout stdOutput - mayberedir perr stdError - childfunc - executeFile fp True args Nothing -{- - realfunc p = do - System.Posix.Signals.installHandler - System.Posix.Signals.sigPIPE - System.Posix.Signals.Ignore - Nothing - func p --} - in - ddd "pOpen3Raw" $ - do - p <- try (forkProcess childstuff) - pid <- case p of - Right x -> return x - Left e -> fail ("Error in fork: " ++ (show e)) - return pid - -#endif -#endif - -showCmd :: FilePath -> [String] -> String -showCmd fp args = fp ++ " " ++ show args diff --git a/Utility/CoProcess.hs b/Utility/CoProcess.hs index 9fa8d864fe..d3b0c46efc 100644 --- a/Utility/CoProcess.hs +++ b/Utility/CoProcess.hs @@ -13,23 +13,25 @@ module Utility.CoProcess ( query ) where -import System.Cmd.Utils +import System.Process import Common -type CoProcessHandle = (PipeHandle, Handle, Handle) +type CoProcessHandle = (ProcessHandle, Handle, Handle, FilePath, [String]) start :: FilePath -> [String] -> IO CoProcessHandle -start command params = hPipeBoth command params +start command params = do + (from, to, _err, pid) <- runInteractiveProcess command params Nothing Nothing + return (pid, to, from, command, params) stop :: CoProcessHandle -> IO () -stop (pid, from, to) = do +stop (pid, from, to, command, params) = do hClose to hClose from - forceSuccess pid + forceSuccessProcess pid command params query :: CoProcessHandle -> (Handle -> IO a) -> (Handle -> IO b) -> IO b -query (_, from, to) send receive = do +query (_, from, to, _, _) send receive = do _ <- send to hFlush to receive from diff --git a/Utility/Gpg.hs b/Utility/Gpg.hs index e13afe5d48..26ac688e3a 100644 --- a/Utility/Gpg.hs +++ b/Utility/Gpg.hs @@ -11,9 +11,9 @@ import qualified Data.ByteString.Lazy as L import System.Posix.Types import Control.Applicative import Control.Concurrent -import Control.Exception (finally, bracket) -import System.Exit +import Control.Exception (bracket) import System.Posix.Env (setEnv, unsetEnv, getEnv) +import System.Process import Common @@ -39,18 +39,30 @@ stdParams params = do readStrict :: [CommandParam] -> IO String readStrict params = do params' <- stdParams params - pOpen ReadFromPipe "gpg" params' hGetContentsStrict + (_, Just from, _, pid) + <- createProcess (proc "gpg" params') + { std_out = CreatePipe } + hSetBinaryMode from True + r <- hGetContentsStrict from + forceSuccessProcess pid "gpg" params' + return r {- Runs gpg, piping an input value to it, and returning its stdout, - strictly. -} pipeStrict :: [CommandParam] -> String -> IO String pipeStrict params input = do params' <- stdParams params - (pid, fromh, toh) <- hPipeBoth "gpg" params' - _ <- forkIO $ finally (hPutStr toh input) (hClose toh) - output <- hGetContentsStrict fromh - forceSuccess pid - return output + (Just to, Just from, _, pid) + <- createProcess (proc "gpg" params') + { std_in = CreatePipe + , std_out = CreatePipe } + hSetBinaryMode to True + hSetBinaryMode from True + hPutStr to input + hClose to + r <- hGetContentsStrict from + forceSuccessProcess pid "gpg" params' + return r {- Runs gpg with some parameters, first feeding it a passphrase via - --passphrase-fd, then feeding it an input, and passing a handle @@ -70,17 +82,14 @@ passphraseHandle params passphrase a b = do let passphrasefd = [Param "--passphrase-fd", Param $ show pfd] params' <- stdParams $ passphrasefd ++ params - (pid, fromh, toh) <- hPipeBoth "gpg" params' - pid2 <- forkProcess $ do - L.hPut toh =<< a - hClose toh - exitSuccess + (Just toh, Just fromh, _, pid) <- createProcess (proc "gpg" params') + { std_in = CreatePipe, std_out = CreatePipe } + L.hPut toh =<< a hClose toh ret <- b fromh -- cleanup - forceSuccess pid - _ <- getProcessStatus True False pid2 + forceSuccessProcess pid "gpg" params' closeFd frompipe return ret diff --git a/Utility/INotify.hs b/Utility/INotify.hs index bf87f4e71b..55233ef762 100644 --- a/Utility/INotify.hs +++ b/Utility/INotify.hs @@ -10,6 +10,7 @@ module Utility.INotify where import Common hiding (isDirectory) import Utility.ThreadLock import Utility.Types.DirWatcher +import System.Process import System.INotify import qualified System.Posix.Files as Files @@ -160,12 +161,9 @@ tooManyWatches hook dir = do querySysctl :: Read a => [CommandParam] -> IO (Maybe a) querySysctl ps = do - v <- catchMaybeIO $ hPipeFrom "sysctl" $ toCommand ps + v <- catchMaybeIO $ readProcess "sysctl" (toCommand ps) [] case v of Nothing -> return Nothing - Just (pid, h) -> do - val <- parsesysctl <$> hGetContentsStrict h - void $ getProcessStatus True False $ processID pid - return val + Just s -> return $ parsesysctl s where parsesysctl s = readish =<< lastMaybe (words s) diff --git a/Utility/Lsof.hs b/Utility/Lsof.hs index 0061dfe574..ebd273b2e1 100644 --- a/Utility/Lsof.hs +++ b/Utility/Lsof.hs @@ -12,6 +12,7 @@ module Utility.Lsof where import Common import System.Posix.Types +import System.Process data LsofOpenMode = OpenReadWrite | OpenReadOnly | OpenWriteOnly | OpenUnknown deriving (Show, Eq) @@ -34,10 +35,8 @@ queryDir path = query ["+d", path] -} query :: [String] -> IO [(FilePath, LsofOpenMode, ProcessInfo)] query opts = do - (pid, s) <- pipeFrom "lsof" ("-F0can" : opts) - let !r = parse s - void $ getProcessStatus True False $ processID pid - return r + (_, s, _) <- readProcessWithExitCode "lsof" ("-F0can" : opts) [] + return $ parse s {- Parsing null-delimited output like: - diff --git a/Utility/Process.hs b/Utility/Process.hs new file mode 100644 index 0000000000..9f79efa813 --- /dev/null +++ b/Utility/Process.hs @@ -0,0 +1,40 @@ +{- System.Process enhancements + - + - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Utility.Process where + +import System.Process +import System.Exit +import System.IO + +import Utility.Misc + +{- Waits for a ProcessHandle, and throws an exception if the process + - did not exit successfully. -} +forceSuccessProcess :: ProcessHandle -> String -> [String] -> IO () +forceSuccessProcess pid cmd args = do + code <- waitForProcess pid + case code of + ExitSuccess -> return () + ExitFailure n -> error $ + cmd ++ " " ++ show args ++ " exited " ++ show n + +{- Like readProcess, but allows specifying the environment, and does + - not mess with stdin. -} +readProcessEnv :: FilePath -> [String] -> Maybe [(String, String)] -> IO String +readProcessEnv cmd args environ = do + (_, Just h, _, pid) + <- createProcess (proc cmd args) + { std_in = Inherit + , std_out = CreatePipe + , std_err = Inherit + , env = environ + } + output <- hGetContentsStrict h + hClose h + forceSuccessProcess pid cmd args + return output diff --git a/Utility/SafeCommand.hs b/Utility/SafeCommand.hs index 5f6a53e715..47280a40b1 100644 --- a/Utility/SafeCommand.hs +++ b/Utility/SafeCommand.hs @@ -1,6 +1,6 @@ {- safely running shell commands - - - Copyright 2010-2011 Joey Hess + - Copyright 2010-2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} @@ -8,11 +8,8 @@ module Utility.SafeCommand where import System.Exit -import qualified System.Posix.Process -import System.Posix.Process hiding (executeFile) -import System.Posix.Signals +import System.Process import Data.String.Utils -import System.Log.Logger import Control.Applicative {- A type for parameters passed to a shell command. A command can @@ -42,7 +39,7 @@ boolSystem :: FilePath -> [CommandParam] -> IO Bool boolSystem command params = boolSystemEnv command params Nothing boolSystemEnv :: FilePath -> [CommandParam] -> Maybe [(String, String)] -> IO Bool -boolSystemEnv command params env = dispatch <$> safeSystemEnv command params env +boolSystemEnv command params environ = dispatch <$> safeSystemEnv command params environ where dispatch ExitSuccess = True dispatch _ = False @@ -51,41 +48,13 @@ boolSystemEnv command params env = dispatch <$> safeSystemEnv command params env safeSystem :: FilePath -> [CommandParam] -> IO ExitCode safeSystem command params = safeSystemEnv command params Nothing -{- SIGINT(ctrl-c) is allowed to propigate and will terminate the program. -} +{- Unlike many implementations of system, SIGINT(ctrl-c) is allowed + - to propigate and will terminate the program. -} safeSystemEnv :: FilePath -> [CommandParam] -> Maybe [(String, String)] -> IO ExitCode -safeSystemEnv command params env = do - putStrLn "safeSystemEnv start" - -- Going low-level because all the high-level system functions - -- block SIGINT etc. We need to block SIGCHLD, but allow - -- SIGINT to do its default program termination. - let sigset = addSignal sigCHLD emptySignalSet - oldint <- installHandler sigINT Default Nothing - oldset <- getSignalMask - blockSignals sigset - childpid <- forkProcess $ childaction oldint oldset - mps <- getProcessStatus True False childpid - restoresignals oldint oldset - case mps of - Just (Exited code) -> do - putStrLn "safeSystemEnv end" - return code - _ -> error $ "unknown error running " ++ command - where - restoresignals oldint oldset = do - _ <- installHandler sigINT oldint Nothing - setSignalMask oldset - childaction oldint oldset = do - restoresignals oldint oldset - executeFile command True (toCommand params) env - -{- executeFile with debug logging -} -executeFile :: FilePath -> Bool -> [String] -> Maybe [(String, String)] -> IO () -executeFile c path p e = do - putStrLn "executeFile start" - --debugM "Utility.SafeCommand.executeFile" $ - -- "Running: " ++ c ++ " " ++ show p ++ " " ++ maybe "" show e - System.Posix.Process.executeFile c path p e - putStrLn "executeFile end" +safeSystemEnv command params environ = do + (_, _, _, pid) <- createProcess (proc command $ toCommand params) + { env = environ } + waitForProcess pid {- Escapes a filename or other parameter to be safely able to be exposed to - the shell. -} diff --git a/Utility/TempFile.hs b/Utility/TempFile.hs index 4dcbf1cca4..62e0fc8596 100644 --- a/Utility/TempFile.hs +++ b/Utility/TempFile.hs @@ -9,7 +9,7 @@ module Utility.TempFile where import Control.Exception (bracket) import System.IO -import System.Posix.Process hiding (executeFile) +import System.Posix.Process import System.Directory import Utility.Exception diff --git a/doc/todo/assistant_threaded_runtime.mdwn b/doc/todo/assistant_threaded_runtime.mdwn index edfa51669f..412f52ae81 100644 --- a/doc/todo/assistant_threaded_runtime.mdwn +++ b/doc/todo/assistant_threaded_runtime.mdwn @@ -23,6 +23,9 @@ git-annex does not otherwise use threads, so this is surprising. --[[Joey]] > I've spent a lot of time debugging this, and trying to fix it, in the > "threaded" branch. There are still deadlocks. --[[Joey]] +>> Fixed, by switching from `System.Cmd.Utils` to `System.Process` +>> --[[Joey]] + --- It would be possible to not use the threaded runtime. Instead, we could diff --git a/git-annex.cabal b/git-annex.cabal index 3f237ce70e..e58bd4d957 100644 --- a/git-annex.cabal +++ b/git-annex.cabal @@ -40,11 +40,12 @@ Executable git-annex unix, containers, utf8-string, network, mtl, bytestring, old-locale, time, pcre-light, extensible-exceptions, dataenc, SHA, process, json, HTTP, base == 4.5.*, monad-control, transformers-base, lifted-base, - IfElse, text, QuickCheck >= 2.1, bloomfilter, edit-distance + IfElse, text, QuickCheck >= 2.1, bloomfilter, edit-distance, process -- Need to list this because it's generated from a .hsc file. Other-Modules: Utility.Touch C-Sources: Utility/libdiskfree.c Extensions: CPP + GHC-Options: -threaded if flag(S3) Build-Depends: hS3 @@ -65,10 +66,11 @@ Test-Suite test unix, containers, utf8-string, network, mtl, bytestring, old-locale, time, pcre-light, extensible-exceptions, dataenc, SHA, process, json, HTTP, base == 4.5.*, monad-control, transformers-base, lifted-base, - IfElse, text, QuickCheck >= 2.1, bloomfilter, edit-distance + IfElse, text, QuickCheck >= 2.1, bloomfilter, edit-distance, process Other-Modules: Utility.Touch C-Sources: Utility/libdiskfree.c Extensions: CPP + GHC-Options: -threaded source-repository head type: git diff --git a/test.hs b/test.hs index 9de73264ee..a377057c28 100644 --- a/test.hs +++ b/test.hs @@ -14,6 +14,7 @@ import Test.QuickCheck import System.Posix.Directory (changeWorkingDirectory) import System.Posix.Files import System.Posix.Env +import System.Posix.Process import Control.Exception.Extensible import qualified Data.Map as M import System.IO.HVFS (SystemFS(..)) From f520a2c10359257ea6f920d26fe29831db8d07e3 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 18 Jul 2012 18:29:33 -0400 Subject: [PATCH 065/331] add missing imports --- Assistant/ThreadedMonad.hs | 1 + Assistant/Threads/TransferWatcher.hs | 1 + Utility/Parallel.hs | 2 ++ 3 files changed, 4 insertions(+) diff --git a/Assistant/ThreadedMonad.hs b/Assistant/ThreadedMonad.hs index 16f3a9dd9f..f32adff435 100644 --- a/Assistant/ThreadedMonad.hs +++ b/Assistant/ThreadedMonad.hs @@ -13,6 +13,7 @@ import qualified Annex import Control.Concurrent import Data.Tuple import System.Posix.Types +import System.Posix.Process {- The Annex state is stored in a MVar, so that threaded actions can access - it. -} diff --git a/Assistant/Threads/TransferWatcher.hs b/Assistant/Threads/TransferWatcher.hs index 5be63fce4f..766c1f89e8 100644 --- a/Assistant/Threads/TransferWatcher.hs +++ b/Assistant/Threads/TransferWatcher.hs @@ -17,6 +17,7 @@ import Utility.Types.DirWatcher import Annex.BranchState import Data.Map as M +import System.Posix.Process {- This thread watches for changes to the gitAnnexTransferDir, - and updates the DaemonStatus's map of ongoing transfers. -} diff --git a/Utility/Parallel.hs b/Utility/Parallel.hs index 9df95ab2b0..f4a79316c7 100644 --- a/Utility/Parallel.hs +++ b/Utility/Parallel.hs @@ -9,6 +9,8 @@ module Utility.Parallel where import Common +import System.Posix.Process + {- Runs an action in parallel with a set of values. - Returns the values partitioned into ones with which the action succeeded, - and ones with which it failed. -} From eea0a3616cd1cbaf033649c11a5c2b650b6b632f Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 18 Jul 2012 18:42:41 -0400 Subject: [PATCH 066/331] add thread id field to transferinfo Also converted its timestand to posix seconds, like is used in the other log files. --- Assistant/ThreadedMonad.hs | 10 ++++------ Assistant/Threads/Transferrer.hs | 16 ++++++++-------- Assistant/TransferQueue.hs | 1 + Logs/Transfer.hs | 15 ++++++++++++--- 4 files changed, 25 insertions(+), 17 deletions(-) diff --git a/Assistant/ThreadedMonad.hs b/Assistant/ThreadedMonad.hs index f32adff435..2fc5265997 100644 --- a/Assistant/ThreadedMonad.hs +++ b/Assistant/ThreadedMonad.hs @@ -12,8 +12,6 @@ import qualified Annex import Control.Concurrent import Data.Tuple -import System.Posix.Types -import System.Posix.Process {- The Annex state is stored in a MVar, so that threaded actions can access - it. -} @@ -39,14 +37,14 @@ withThreadState a = do runThreadState :: ThreadState -> Annex a -> IO a runThreadState mvar a = modifyMVar mvar $ \state -> swap <$> Annex.run state a -{- Runs an Annex action in a separate process, using a copy of the state +{- Runs an Annex action in a separate thread, using a copy of the state - from the MVar. - - It's up to the action to perform any necessary shutdown tasks in order - for state to not be lost. And it's up to the caller to resynchronise - with any changes the action makes to eg, the git-annex branch. -} -unsafeForkProcessThreadState :: ThreadState -> Annex a -> IO ProcessID -unsafeForkProcessThreadState mvar a = do +unsafeForkIOThreadState :: ThreadState -> Annex a -> IO ThreadId +unsafeForkIOThreadState mvar a = do state <- readMVar mvar - forkProcess $ void $ Annex.eval state a + forkIO $ void $ Annex.eval state a diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs index 9d3358f546..dd63d4d128 100644 --- a/Assistant/Threads/Transferrer.hs +++ b/Assistant/Threads/Transferrer.hs @@ -18,6 +18,7 @@ import Logs.Location import Annex.Content import qualified Remote +import Data.Time.Clock.POSIX import Data.Time.Clock import qualified Data.Map as M @@ -58,12 +59,12 @@ shouldTransfer dstatus t info = | otherwise = return False key = transferKey t -{- A transfer is run in a separate process, with a *copy* of the Annex +{- A transfer is run in a separate thread, with a *copy* of the Annex - state. This is necessary to avoid blocking the rest of the assistant - on the transfer completing, and also to allow multiple transfers to run - - at once. + - at once. This requires GHC's threaded runtime to work! - - - However, it means that the transfer processes are responsible + - The copy of state means that the transfer processes are responsible - for doing any necessary shutdown cleanups, and that the parent - thread's cache must be invalidated once a transfer completes, as - changes may have been made to the git-annex branch. @@ -73,15 +74,14 @@ runTransfer st dstatus slots t info = case (transferRemote info, associatedFile (Nothing, _) -> noop (_, Nothing) -> noop (Just remote, Just file) -> do - pid <- inTransferSlot slots $ - unsafeForkProcessThreadState st $ + tid <- inTransferSlot slots $ + unsafeForkIOThreadState st $ transferprocess remote file now <- getCurrentTime runThreadState st $ adjustTransfers dstatus $ M.insertWith' const t info - { startedTime = Just now - , transferPid = Just pid - , shouldWait = True + { startedTime = Just $ utcTimeToPOSIXSeconds now + , transferTid = Just tid } where isdownload = transferDirection t == Download diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs index 73e73ca0af..fb7fa87cdf 100644 --- a/Assistant/TransferQueue.hs +++ b/Assistant/TransferQueue.hs @@ -24,6 +24,7 @@ stubInfo :: AssociatedFile -> TransferInfo stubInfo f = TransferInfo { startedTime = Nothing , transferPid = Nothing + , transferTid = Nothing , transferRemote = Nothing , bytesComplete = Nothing , associatedFile = f diff --git a/Logs/Transfer.hs b/Logs/Transfer.hs index 2605120674..f74d128dc9 100644 --- a/Logs/Transfer.hs +++ b/Logs/Transfer.hs @@ -16,6 +16,10 @@ import qualified Fields import System.Posix.Types import Data.Time.Clock +import Data.Time.Clock.POSIX +import Data.Time +import System.Locale +import Control.Concurrent {- Enough information to uniquely identify a transfer, used as the filename - of the transfer information file. -} @@ -33,8 +37,9 @@ data Transfer = Transfer - of some repository, that was acted on to initiate the transfer. -} data TransferInfo = TransferInfo - { startedTime :: Maybe UTCTime + { startedTime :: Maybe POSIXTime , transferPid :: Maybe ProcessID + , transferTid :: Maybe ThreadId , transferRemote :: Maybe Remote , bytesComplete :: Maybe Integer , associatedFile :: Maybe FilePath @@ -76,8 +81,9 @@ transfer t file a = do createAnnexDirectory $ takeDirectory tfile mode <- annexFileMode info <- liftIO $ TransferInfo - <$> (Just <$> getCurrentTime) + <$> (Just . utcTimeToPOSIXSeconds <$> getCurrentTime) <*> pure Nothing -- pid not stored in file, so omitted for speed + <*> pure Nothing -- tid ditto <*> pure Nothing -- not 0; transfer may be resuming <*> pure Nothing <*> pure file @@ -168,13 +174,16 @@ readTransferInfo :: ProcessID -> String -> Maybe TransferInfo readTransferInfo pid s = case bits of [time] -> TransferInfo - <$> readish time + <$> parsetime time <*> pure (Just pid) <*> pure Nothing <*> pure Nothing + <*> pure Nothing <*> pure (if null filename then Nothing else Just filename) <*> pure False _ -> Nothing where (bits, filebits) = splitAt 1 $ lines s filename = join "\n" filebits + parsetime t = Just . utcTimeToPOSIXSeconds + <$> parseTime defaultTimeLocale "%s%Qs" t From cf47bb3f509ae63ad868b66c0b6f2baecb93e4c7 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 18 Jul 2012 19:13:56 -0400 Subject: [PATCH 067/331] run file transfers in threads, not processes This should fix OSX/BSD issues with not noticing transfer information files with kqueue. Now that threads are used, the thread can manage the transfer slot allocation and deallocation by itself; much cleaner. --- Assistant.hs | 2 +- Assistant/ThreadedMonad.hs | 9 +++--- Assistant/Threads/TransferWatcher.hs | 46 +++++++++------------------- Assistant/Threads/Transferrer.hs | 5 ++- Assistant/TransferQueue.hs | 1 - Assistant/TransferSlots.hs | 16 +++++----- Logs/Transfer.hs | 3 -- 7 files changed, 29 insertions(+), 53 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index 91ebf2d2e0..06484b0862 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -123,7 +123,7 @@ startDaemon assistant foreground , pushThread st dstatus commitchan pushmap , pushRetryThread st pushmap , mergeThread st - , transferWatcherThread st dstatus transferslots + , transferWatcherThread st dstatus , transfererThread st dstatus transferqueue transferslots , daemonStatusThread st dstatus , sanityCheckerThread st dstatus transferqueue changechan diff --git a/Assistant/ThreadedMonad.hs b/Assistant/ThreadedMonad.hs index 2fc5265997..1decd8e913 100644 --- a/Assistant/ThreadedMonad.hs +++ b/Assistant/ThreadedMonad.hs @@ -37,14 +37,13 @@ withThreadState a = do runThreadState :: ThreadState -> Annex a -> IO a runThreadState mvar a = modifyMVar mvar $ \state -> swap <$> Annex.run state a -{- Runs an Annex action in a separate thread, using a copy of the state - - from the MVar. +{- Runs an Annex action, using a copy of the state from the MVar. - - It's up to the action to perform any necessary shutdown tasks in order - for state to not be lost. And it's up to the caller to resynchronise - with any changes the action makes to eg, the git-annex branch. -} -unsafeForkIOThreadState :: ThreadState -> Annex a -> IO ThreadId -unsafeForkIOThreadState mvar a = do +unsafeRunThreadState :: ThreadState -> Annex a -> IO () +unsafeRunThreadState mvar a = do state <- readMVar mvar - forkIO $ void $ Annex.eval state a + void $ Annex.eval state a diff --git a/Assistant/Threads/TransferWatcher.hs b/Assistant/Threads/TransferWatcher.hs index 766c1f89e8..364ce04689 100644 --- a/Assistant/Threads/TransferWatcher.hs +++ b/Assistant/Threads/TransferWatcher.hs @@ -10,23 +10,20 @@ module Assistant.Threads.TransferWatcher where import Common.Annex import Assistant.ThreadedMonad import Assistant.DaemonStatus -import Assistant.TransferSlots import Logs.Transfer import Utility.DirWatcher import Utility.Types.DirWatcher -import Annex.BranchState import Data.Map as M -import System.Posix.Process {- This thread watches for changes to the gitAnnexTransferDir, - and updates the DaemonStatus's map of ongoing transfers. -} -transferWatcherThread :: ThreadState -> DaemonStatusHandle -> TransferSlots -> IO () -transferWatcherThread st dstatus transferslots = do +transferWatcherThread :: ThreadState -> DaemonStatusHandle -> IO () +transferWatcherThread st dstatus = do g <- runThreadState st $ fromRepo id let dir = gitAnnexTransferDir g createDirectoryIfMissing True dir - let hook a = Just $ runHandler st dstatus transferslots a + let hook a = Just $ runHandler st dstatus a let hooks = mkWatchHooks { addHook = hook onAdd , delHook = hook onDel @@ -34,51 +31,36 @@ transferWatcherThread st dstatus transferslots = do } void $ watchDir dir (const False) hooks id -type Handler = ThreadState -> DaemonStatusHandle -> TransferSlots -> FilePath -> Maybe FileStatus -> IO () +type Handler = ThreadState -> DaemonStatusHandle -> FilePath -> Maybe FileStatus -> IO () {- Runs an action handler. - - Exceptions are ignored, otherwise a whole thread could be crashed. -} -runHandler :: ThreadState -> DaemonStatusHandle -> TransferSlots -> Handler -> FilePath -> Maybe FileStatus -> IO () -runHandler st dstatus transferslots handler file filestatus = void $ do +runHandler :: ThreadState -> DaemonStatusHandle -> Handler -> FilePath -> Maybe FileStatus -> IO () +runHandler st dstatus handler file filestatus = void $ do either print (const noop) =<< tryIO go where - go = handler st dstatus transferslots file filestatus + go = handler st dstatus file filestatus {- Called when there's an error with inotify. -} onErr :: Handler -onErr _ _ _ msg _ = error msg +onErr _ _ msg _ = error msg {- Called when a new transfer information file is written. -} onAdd :: Handler -onAdd st dstatus _ file _ = case parseTransferFile file of +onAdd st dstatus file _ = case parseTransferFile file of Nothing -> noop Just t -> runThreadState st $ go t =<< checkTransfer t where go _ Nothing = noop -- transfer already finished go t (Just info) = adjustTransfers dstatus $ M.insertWith' merge t info - -- preseve shouldWait flag, which is not written to disk - merge new old = new { shouldWait = shouldWait old } + -- preseve transferTid, which is not written to disk + merge new old = new { transferTid = transferTid old } -{- Called when a transfer information file is removed. - - - - When the transfer process is a child of this process, wait on it - - to avoid zombies. - -} +{- Called when a transfer information file is removed. -} onDel :: Handler -onDel st dstatus transferslots file _ = case parseTransferFile file of +onDel st dstatus file _ = case parseTransferFile file of Nothing -> noop - Just t -> maybe noop waitchild - =<< runThreadState st (removeTransfer dstatus t) - where - waitchild info - | shouldWait info = case transferPid info of - Nothing -> noop - Just pid -> do - void $ tryIO $ - getProcessStatus True False pid - runThreadState st invalidateCache - transferComplete transferslots - | otherwise = noop + Just t -> void $ runThreadState st $ removeTransfer dstatus t diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs index dd63d4d128..c439d8b7ed 100644 --- a/Assistant/Threads/Transferrer.hs +++ b/Assistant/Threads/Transferrer.hs @@ -74,9 +74,8 @@ runTransfer st dstatus slots t info = case (transferRemote info, associatedFile (Nothing, _) -> noop (_, Nothing) -> noop (Just remote, Just file) -> do - tid <- inTransferSlot slots $ - unsafeForkIOThreadState st $ - transferprocess remote file + tid <- inTransferSlot slots st $ + transferprocess remote file now <- getCurrentTime runThreadState st $ adjustTransfers dstatus $ M.insertWith' const t info diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs index fb7fa87cdf..b0eca96c84 100644 --- a/Assistant/TransferQueue.hs +++ b/Assistant/TransferQueue.hs @@ -28,7 +28,6 @@ stubInfo f = TransferInfo , transferRemote = Nothing , bytesComplete = Nothing , associatedFile = f - , shouldWait = False } {- Adds pending transfers to the end of the queue for some of the known diff --git a/Assistant/TransferSlots.hs b/Assistant/TransferSlots.hs index 1859b281bb..dc077254d9 100644 --- a/Assistant/TransferSlots.hs +++ b/Assistant/TransferSlots.hs @@ -10,6 +10,9 @@ module Assistant.TransferSlots where import Control.Exception import Control.Concurrent +import Common.Annex +import Assistant.ThreadedMonad + type TransferSlots = QSemN {- Number of concurrent transfers allowed to be run from the assistant. @@ -24,16 +27,13 @@ newTransferSlots :: IO TransferSlots newTransferSlots = newQSemN numSlots {- Waits until a transfer slot becomes available, and runs a transfer - - action in the slot. If the action throws an exception, its slot is - - freed here, otherwise it should be freed by the TransferWatcher when - - the transfer is complete. - -} -inTransferSlot :: TransferSlots -> IO a -> IO a -inTransferSlot s a = bracketOnError start abort run + - action in the slot, in its own thread. -} +inTransferSlot :: TransferSlots -> ThreadState -> Annex a -> IO ThreadId +inTransferSlot s st a = forkIO $ bracket_ start done run where start = waitQSemN s 1 - abort = const $ transferComplete s - run = const a + done = transferComplete s + run = unsafeRunThreadState st a {- Call when a transfer is complete. -} transferComplete :: TransferSlots -> IO () diff --git a/Logs/Transfer.hs b/Logs/Transfer.hs index f74d128dc9..1e3d0abdb9 100644 --- a/Logs/Transfer.hs +++ b/Logs/Transfer.hs @@ -43,7 +43,6 @@ data TransferInfo = TransferInfo , transferRemote :: Maybe Remote , bytesComplete :: Maybe Integer , associatedFile :: Maybe FilePath - , shouldWait :: Bool } deriving (Show, Eq, Ord) @@ -87,7 +86,6 @@ transfer t file a = do <*> pure Nothing -- not 0; transfer may be resuming <*> pure Nothing <*> pure file - <*> pure False bracketIO (prep tfile mode info) (cleanup tfile) a where prep tfile mode info = do @@ -180,7 +178,6 @@ readTransferInfo pid s = <*> pure Nothing <*> pure Nothing <*> pure (if null filename then Nothing else Just filename) - <*> pure False _ -> Nothing where (bits, filebits) = splitAt 1 $ lines s From 2edb5d145c66c36d0f5fd90bfb7905989643266a Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 18 Jul 2012 19:25:46 -0400 Subject: [PATCH 068/331] rewrote to not use forkProcess That can make the threaded runtime stall.. But it can use threads now! --- Utility/Parallel.hs | 25 ++++++++++++++++++------- 1 file changed, 18 insertions(+), 7 deletions(-) diff --git a/Utility/Parallel.hs b/Utility/Parallel.hs index f4a79316c7..fcab2a90a1 100644 --- a/Utility/Parallel.hs +++ b/Utility/Parallel.hs @@ -1,4 +1,4 @@ -{- parallel processes +{- parallel processing via threads - - Copyright 2012 Joey Hess - @@ -9,16 +9,27 @@ module Utility.Parallel where import Common -import System.Posix.Process +import Control.Concurrent +import Control.Exception -{- Runs an action in parallel with a set of values. +{- Runs an action in parallel with a set of values, in a set of threads. + - In order for the actions to truely run in parallel, requires GHC's + - threaded runtime, + - - Returns the values partitioned into ones with which the action succeeded, - and ones with which it failed. -} inParallel :: (v -> IO ()) -> [v] -> IO ([v], [v]) inParallel a l = do - pids <- mapM (forkProcess . a) l - statuses <- mapM (getProcessStatus True False) pids - return $ reduce $ partition (succeeded . snd) $ zip l statuses + mvars <- mapM thread l + statuses <- mapM takeMVar mvars + return $ reduce $ partition snd $ zip l statuses where - succeeded v = v == Just (Exited ExitSuccess) reduce (x,y) = (map fst x, map fst y) + thread v = do + mvar <- newEmptyMVar + _ <- forkIO $ do + r <- try (a v) :: IO (Either SomeException ()) + case r of + Left _ -> putMVar mvar False + Right _ -> putMVar mvar True + return mvar From 549f8619998eab17aaf2122f11f036fac7e6cc40 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 18 Jul 2012 20:48:08 -0400 Subject: [PATCH 069/331] fix parsing of startedTime --- Logs/Transfer.hs | 12 +++++++----- 1 file changed, 7 insertions(+), 5 deletions(-) diff --git a/Logs/Transfer.hs b/Logs/Transfer.hs index 1e3d0abdb9..b6962262d1 100644 --- a/Logs/Transfer.hs +++ b/Logs/Transfer.hs @@ -118,7 +118,7 @@ checkTransfer t = do case locked of Nothing -> return Nothing Just (pid, _) -> liftIO $ - flip catchDefaultIO Nothing $ + flip catchDefaultIO Nothing $ do readTransferInfo pid <$> readFile tfile @@ -163,7 +163,7 @@ writeTransferInfo :: TransferInfo -> String writeTransferInfo info = unlines -- transferPid is not included; instead obtained by looking at -- the process that locks the file. - [ show $ startedTime info + [ maybe "" show $ startedTime info -- bytesComplete is not included; changes too fast , fromMaybe "" $ associatedFile info -- comes last; arbitrary content ] @@ -172,7 +172,7 @@ readTransferInfo :: ProcessID -> String -> Maybe TransferInfo readTransferInfo pid s = case bits of [time] -> TransferInfo - <$> parsetime time + <$> (Just <$> parsePOSIXTime time) <*> pure (Just pid) <*> pure Nothing <*> pure Nothing @@ -182,5 +182,7 @@ readTransferInfo pid s = where (bits, filebits) = splitAt 1 $ lines s filename = join "\n" filebits - parsetime t = Just . utcTimeToPOSIXSeconds - <$> parseTime defaultTimeLocale "%s%Qs" t + +parsePOSIXTime :: String -> Maybe POSIXTime +parsePOSIXTime s = utcTimeToPOSIXSeconds + <$> parseTime defaultTimeLocale "%s%Qs" s From 1db7d27a451f552dbae8760e83c73b90da8114d5 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 19 Jul 2012 00:43:36 -0400 Subject: [PATCH 070/331] add back debug logging Make Utility.Process wrap the parts of System.Process that I use, and add debug logging to them. Also wrote some higher-level code that allows running an action with handles to a processes stdin or stdout (or both), and checking its exit status, all in a single function call. As a bonus, the debug logging now indicates whether the process is being run to read from it, feed it data, chat with it (writing and reading), or just call it for its side effect. --- Annex/UUID.hs | 2 - Backend/SHA.hs | 1 - Command/Map.hs | 13 +-- Config.hs | 2 - Git/Command.hs | 13 ++- Git/Config.hs | 15 ++- Git/Queue.hs | 13 +-- Git/UpdateIndex.hs | 13 +-- Remote/Bup.hs | 12 +-- Remote/Git.hs | 13 +-- Seek.hs | 4 +- Utility/CoProcess.hs | 12 +-- Utility/Gpg.hs | 45 ++++----- Utility/INotify.hs | 1 - Utility/Lsof.hs | 9 +- Utility/Process.hs | 206 ++++++++++++++++++++++++++++++++++++----- Utility/SafeCommand.hs | 3 +- 17 files changed, 251 insertions(+), 126 deletions(-) diff --git a/Annex/UUID.hs b/Annex/UUID.hs index 1d2175bcb6..13cee865d5 100644 --- a/Annex/UUID.hs +++ b/Annex/UUID.hs @@ -20,8 +20,6 @@ module Annex.UUID ( removeRepoUUID, ) where -import System.Process - import Common.Annex import qualified Git import qualified Git.Config diff --git a/Backend/SHA.hs b/Backend/SHA.hs index a1dd1cf648..04b3e362aa 100644 --- a/Backend/SHA.hs +++ b/Backend/SHA.hs @@ -12,7 +12,6 @@ import qualified Annex import Types.Backend import Types.Key import Types.KeySource -import System.Process import qualified Build.SysConfig as SysConfig import Data.Digest.Pure.SHA diff --git a/Command/Map.hs b/Command/Map.hs index f69b88a5d6..3dbdadbd6c 100644 --- a/Command/Map.hs +++ b/Command/Map.hs @@ -9,7 +9,6 @@ module Command.Map where import Control.Exception.Extensible import qualified Data.Map as M -import System.Process import Common.Annex import Command @@ -199,13 +198,11 @@ tryScan r case result of Left _ -> return Nothing Right r' -> return $ Just r' - pipedconfig cmd params = safely $ do - (_, Just h, _, pid) <- - createProcess (proc cmd $ toCommand params) - { std_out = CreatePipe } - r' <- Git.Config.hRead r h - forceSuccessProcess pid cmd $ toCommand params - return r' + pipedconfig cmd params = safely $ + withHandle StdoutHandle createProcessSuccess p $ + Git.Config.hRead r + where + p = proc cmd $ toCommand params configlist = onRemote r (pipedconfig, Nothing) "configlist" [] [] diff --git a/Config.hs b/Config.hs index 84f6125c63..1aa5a4ac50 100644 --- a/Config.hs +++ b/Config.hs @@ -7,8 +7,6 @@ module Config where -import System.Process - import Common.Annex import qualified Git import qualified Git.Config diff --git a/Git/Command.hs b/Git/Command.hs index 038824f268..d7c9830649 100644 --- a/Git/Command.hs +++ b/Git/Command.hs @@ -7,7 +7,6 @@ module Git.Command where -import System.Process import System.Posix.Process (getAnyProcessStatus) import Common @@ -41,12 +40,12 @@ run subcommand params repo = assertLocal repo $ - result unless reap is called. -} pipeRead :: [CommandParam] -> Repo -> IO String -pipeRead params repo = assertLocal repo $ do - (_, Just h, _, _) <- createProcess - (proc "git" $ toCommand $ gitCommandLine params repo) - { std_out = CreatePipe } - fileEncoding h - hGetContents h +pipeRead params repo = assertLocal repo $ + withHandle StdoutHandle createBackgroundProcess p $ \h -> do + fileEncoding h + hGetContents h + where + p = proc "git" $ toCommand $ gitCommandLine params repo {- Runs a git subcommand, feeding it input, and returning its output, - which is expected to be fairly small, since it's all read into memory diff --git a/Git/Config.hs b/Git/Config.hs index 2347501131..c82d6bb1b0 100644 --- a/Git/Config.hs +++ b/Git/Config.hs @@ -9,7 +9,7 @@ module Git.Config where import qualified Data.Map as M import Data.Char -import System.Process +import System.Process (cwd) import Common import Git @@ -48,14 +48,11 @@ read' repo = go repo go Repo { location = Local { gitdir = d } } = git_config d go Repo { location = LocalUnknown d } = git_config d go _ = assertLocal repo $ error "internal" - git_config d = do - (_, Just h, _, pid) - <- createProcess (proc "git" params) - { std_out = CreatePipe, cwd = Just d } - repo' <- hRead repo h - forceSuccessProcess pid "git" params - return repo' - params = ["config", "--null", "--list"] + git_config d = withHandle StdoutHandle createProcessSuccess p $ + hRead repo + where + params = ["config", "--null", "--list"] + p = (proc "git" params) { cwd = Just d } {- Reads git config from a handle and populates a repo with it. -} hRead :: Repo -> Handle -> IO Repo diff --git a/Git/Queue.hs b/Git/Queue.hs index 4e6f05c2e0..f515ad1045 100644 --- a/Git/Queue.hs +++ b/Git/Queue.hs @@ -19,7 +19,6 @@ module Git.Queue ( import qualified Data.Map as M import System.IO -import System.Process import Data.String.Utils import Utility.SafeCommand @@ -148,13 +147,11 @@ runAction :: Repo -> Action -> IO () runAction repo (UpdateIndexAction streamers) = -- list is stored in reverse order Git.UpdateIndex.streamUpdateIndex repo $ reverse streamers -runAction repo action@(CommandAction {}) = do - (Just h, _, _, pid) <- createProcess (proc "xargs" params) - { std_in = CreatePipe } - fileEncoding h - hPutStr h $ join "\0" $ getFiles action - hClose h - forceSuccessProcess pid "xargs" params +runAction repo action@(CommandAction {}) = + withHandle StdinHandle createProcessSuccess (proc "xargs" params) $ \h -> do + fileEncoding h + hPutStr h $ join "\0" $ getFiles action + hClose h where params = "-0":"git":baseparams baseparams = toCommand $ gitCommandLine diff --git a/Git/UpdateIndex.hs b/Git/UpdateIndex.hs index 6de0c3adab..9294487298 100644 --- a/Git/UpdateIndex.hs +++ b/Git/UpdateIndex.hs @@ -17,8 +17,6 @@ module Git.UpdateIndex ( stageSymlink ) where -import System.Process - import Common import Git import Git.Types @@ -36,12 +34,11 @@ pureStreamer !s = \streamer -> streamer s {- Streams content into update-index from a list of Streamers. -} streamUpdateIndex :: Repo -> [Streamer] -> IO () -streamUpdateIndex repo as = do - (Just h, _, _, p) <- createProcess (proc "git" ps) { std_in = CreatePipe } - fileEncoding h - forM_ as (stream h) - hClose h - forceSuccessProcess p "git" ps +streamUpdateIndex repo as = + withHandle StdinHandle createProcessSuccess (proc "git" ps) $ \h -> do + fileEncoding h + forM_ as (stream h) + hClose h where ps = toCommand $ gitCommandLine params repo params = map Param ["update-index", "-z", "--index-info"] diff --git a/Remote/Bup.hs b/Remote/Bup.hs index 9da374174b..8a2c1afefe 100644 --- a/Remote/Bup.hs +++ b/Remote/Bup.hs @@ -133,15 +133,13 @@ retrieveCheap :: BupRepo -> Key -> FilePath -> Annex Bool retrieveCheap _ _ _ = return False retrieveEncrypted :: BupRepo -> (Cipher, Key) -> Key -> FilePath -> Annex Bool -retrieveEncrypted buprepo (cipher, enck) _ f = do - let params = bupParams "join" buprepo [Param $ bupRef enck] - liftIO $ catchBoolIO $ do - (_, Just h, _, pid) - <- createProcess (proc "bup" $ toCommand params) - { std_out = CreatePipe } +retrieveEncrypted buprepo (cipher, enck) _ f = liftIO $ catchBoolIO $ + withHandle StdoutHandle createProcessSuccess p $ \h -> do withDecryptedContent cipher (L.hGetContents h) $ L.writeFile f - forceSuccessProcess pid "bup" $ toCommand params return True + where + params = bupParams "join" buprepo [Param $ bupRef enck] + p = proc "bup" $ toCommand params remove :: Key -> Annex Bool remove _ = do diff --git a/Remote/Git.hs b/Remote/Git.hs index a9a6d6004e..3412de89b4 100644 --- a/Remote/Git.hs +++ b/Remote/Git.hs @@ -9,7 +9,6 @@ module Remote.Git (remote, repoAvail) where import qualified Data.Map as M import Control.Exception.Extensible -import System.Process import Common.Annex import Utility.CopyFile @@ -127,13 +126,11 @@ tryGitConfigRead r safely a = either (const $ return r) return =<< liftIO (try a :: IO (Either SomeException Git.Repo)) - pipedconfig cmd params = safely $ do - (_, Just h, _, pid) <- - createProcess (proc cmd $ toCommand params) - { std_out = CreatePipe } - r' <- Git.Config.hRead r h - forceSuccessProcess pid cmd $ toCommand params - return r' + pipedconfig cmd params = safely $ + withHandle StdoutHandle createProcessSuccess p $ + Git.Config.hRead r + where + p = proc cmd $ toCommand params geturlconfig headers = do s <- Url.get (Git.repoLocation r ++ "/config") headers diff --git a/Seek.hs b/Seek.hs index 2cf0d8d460..3306a02fcd 100644 --- a/Seek.hs +++ b/Seek.hs @@ -108,9 +108,9 @@ withNothing _ _ = error "This command takes no parameters." prepFiltered :: (FilePath -> CommandStart) -> Annex [FilePath] -> Annex [CommandStart] prepFiltered a fs = do matcher <- Limit.getMatcher - map (proc matcher) <$> fs + map (process matcher) <$> fs where - proc matcher f = do + process matcher f = do ok <- matcher f if ok then a f else return Nothing diff --git a/Utility/CoProcess.hs b/Utility/CoProcess.hs index d3b0c46efc..67f861bb32 100644 --- a/Utility/CoProcess.hs +++ b/Utility/CoProcess.hs @@ -13,25 +13,23 @@ module Utility.CoProcess ( query ) where -import System.Process - import Common -type CoProcessHandle = (ProcessHandle, Handle, Handle, FilePath, [String]) +type CoProcessHandle = (ProcessHandle, Handle, Handle, CreateProcess) start :: FilePath -> [String] -> IO CoProcessHandle start command params = do (from, to, _err, pid) <- runInteractiveProcess command params Nothing Nothing - return (pid, to, from, command, params) + return (pid, to, from, proc command params) stop :: CoProcessHandle -> IO () -stop (pid, from, to, command, params) = do +stop (pid, from, to, p) = do hClose to hClose from - forceSuccessProcess pid command params + forceSuccessProcess p pid query :: CoProcessHandle -> (Handle -> IO a) -> (Handle -> IO b) -> IO b -query (_, from, to, _, _) send receive = do +query (_, from, to, _) send receive = do _ <- send to hFlush to receive from diff --git a/Utility/Gpg.hs b/Utility/Gpg.hs index 26ac688e3a..eed77805cb 100644 --- a/Utility/Gpg.hs +++ b/Utility/Gpg.hs @@ -13,7 +13,6 @@ import Control.Applicative import Control.Concurrent import Control.Exception (bracket) import System.Posix.Env (setEnv, unsetEnv, getEnv) -import System.Process import Common @@ -39,30 +38,21 @@ stdParams params = do readStrict :: [CommandParam] -> IO String readStrict params = do params' <- stdParams params - (_, Just from, _, pid) - <- createProcess (proc "gpg" params') - { std_out = CreatePipe } - hSetBinaryMode from True - r <- hGetContentsStrict from - forceSuccessProcess pid "gpg" params' - return r + withHandle StdoutHandle createProcessSuccess (proc "gpg" params') $ \h -> do + hSetBinaryMode h True + hGetContentsStrict h {- Runs gpg, piping an input value to it, and returning its stdout, - strictly. -} pipeStrict :: [CommandParam] -> String -> IO String pipeStrict params input = do params' <- stdParams params - (Just to, Just from, _, pid) - <- createProcess (proc "gpg" params') - { std_in = CreatePipe - , std_out = CreatePipe } - hSetBinaryMode to True - hSetBinaryMode from True - hPutStr to input - hClose to - r <- hGetContentsStrict from - forceSuccessProcess pid "gpg" params' - return r + withBothHandles createProcessSuccess (proc "gpg" params') $ \(to, from) -> do + hSetBinaryMode to True + hSetBinaryMode from True + hPutStr to input + hClose to + hGetContentsStrict from {- Runs gpg with some parameters, first feeding it a passphrase via - --passphrase-fd, then feeding it an input, and passing a handle @@ -82,16 +72,13 @@ passphraseHandle params passphrase a b = do let passphrasefd = [Param "--passphrase-fd", Param $ show pfd] params' <- stdParams $ passphrasefd ++ params - (Just toh, Just fromh, _, pid) <- createProcess (proc "gpg" params') - { std_in = CreatePipe, std_out = CreatePipe } - L.hPut toh =<< a - hClose toh - ret <- b fromh - - -- cleanup - forceSuccessProcess pid "gpg" params' - closeFd frompipe - return ret + closeFd frompipe `after` + withBothHandles createProcessSuccess (proc "gpg" params') go + where + go (to, from) = do + L.hPut to =<< a + hClose to + b from {- Finds gpg public keys matching some string. (Could be an email address, - a key id, or a name. -} diff --git a/Utility/INotify.hs b/Utility/INotify.hs index 55233ef762..66c0ab23df 100644 --- a/Utility/INotify.hs +++ b/Utility/INotify.hs @@ -10,7 +10,6 @@ module Utility.INotify where import Common hiding (isDirectory) import Utility.ThreadLock import Utility.Types.DirWatcher -import System.Process import System.INotify import qualified System.Posix.Files as Files diff --git a/Utility/Lsof.hs b/Utility/Lsof.hs index ebd273b2e1..ce6a162832 100644 --- a/Utility/Lsof.hs +++ b/Utility/Lsof.hs @@ -12,7 +12,6 @@ module Utility.Lsof where import Common import System.Posix.Types -import System.Process data LsofOpenMode = OpenReadWrite | OpenReadOnly | OpenWriteOnly | OpenUnknown deriving (Show, Eq) @@ -34,9 +33,11 @@ queryDir path = query ["+d", path] - Note: If lsof is not available, this always returns [] ! -} query :: [String] -> IO [(FilePath, LsofOpenMode, ProcessInfo)] -query opts = do - (_, s, _) <- readProcessWithExitCode "lsof" ("-F0can" : opts) [] - return $ parse s +query opts = + withHandle StdoutHandle (createProcessChecked checkSuccessProcess) p $ \h -> do + parse <$> hGetContentsStrict h + where + p = proc "lsof" ("-F0can" : opts) {- Parsing null-delimited output like: - diff --git a/Utility/Process.hs b/Utility/Process.hs index 9f79efa813..9b57c3b7ab 100644 --- a/Utility/Process.hs +++ b/Utility/Process.hs @@ -1,40 +1,202 @@ -{- System.Process enhancements +{- System.Process enhancements, including additional ways of running + - processes, and logging. - - Copyright 2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} -module Utility.Process where +{-# LANGUAGE Rank2Types #-} -import System.Process +module Utility.Process ( + module X, + CreateProcess, + StdHandle(..), + readProcessEnv, + forceSuccessProcess, + checkSuccessProcess, + createProcessSuccess, + createProcessChecked, + createBackgroundProcess, + withHandle, + withBothHandles, + createProcess, + runInteractiveProcess, + readProcess +) where + +import qualified System.Process +import System.Process as X hiding (CreateProcess(..), createProcess, runInteractiveProcess, readProcess, readProcessWithExitCode, system, rawSystem, runInteractiveCommand, runProcess) +import System.Process hiding (createProcess, runInteractiveProcess, readProcess, readProcessWithExitCode) import System.Exit import System.IO +import System.Log.Logger import Utility.Misc -{- Waits for a ProcessHandle, and throws an exception if the process - - did not exit successfully. -} -forceSuccessProcess :: ProcessHandle -> String -> [String] -> IO () -forceSuccessProcess pid cmd args = do - code <- waitForProcess pid - case code of - ExitSuccess -> return () - ExitFailure n -> error $ - cmd ++ " " ++ show args ++ " exited " ++ show n +type CreateProcessRunner = forall a. CreateProcess -> ((Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO a) -> IO a + +data StdHandle = StdinHandle | StdoutHandle | StderrHandle + deriving (Eq) {- Like readProcess, but allows specifying the environment, and does - not mess with stdin. -} readProcessEnv :: FilePath -> [String] -> Maybe [(String, String)] -> IO String -readProcessEnv cmd args environ = do - (_, Just h, _, pid) - <- createProcess (proc cmd args) - { std_in = Inherit - , std_out = CreatePipe - , std_err = Inherit +readProcessEnv cmd args environ = + withHandle StdoutHandle createProcessSuccess p $ \h -> do + output <- hGetContentsStrict h + hClose h + return output + where + p = (proc cmd args) + { std_out = CreatePipe , env = environ } - output <- hGetContentsStrict h - hClose h - forceSuccessProcess pid cmd args - return output + +{- Waits for a ProcessHandle, and throws an exception if the process + - did not exit successfully. -} +forceSuccessProcess :: CreateProcess -> ProcessHandle -> IO () +forceSuccessProcess p pid = do + code <- waitForProcess pid + case code of + ExitSuccess -> return () + ExitFailure n -> error $ showCmd p ++ " exited " ++ show n + +{- Waits for a ProcessHandle and returns True if it exited successfully. -} +checkSuccessProcess :: ProcessHandle -> IO Bool +checkSuccessProcess pid = do + code <- waitForProcess pid + return $ code == ExitSuccess + +{- Runs createProcess, then an action on its handles, and then + - forceSuccessProcess. -} +createProcessSuccess :: CreateProcessRunner +createProcessSuccess p a = createProcessChecked (forceSuccessProcess p) p a + +{- Runs createProcess, then an action on its handles, and then + - an action on its exit code. -} +createProcessChecked :: (ProcessHandle -> IO b) -> CreateProcessRunner +createProcessChecked checker p a = do + t@(_, _, _, pid) <- createProcess p + r <- a t + _ <- checker pid + return r + +{- Leaves the process running, suitable for lazy streaming. + - Note: Zombies will result, and must be waited on. -} +createBackgroundProcess :: CreateProcessRunner +createBackgroundProcess p a = a =<< createProcess p + +{- Runs a CreateProcessRunner, on a CreateProcess structure, that + - is adjusted to pipe only from/to a single StdHandle, and passes + - the resulting Handle to an action. -} +withHandle + :: StdHandle + -> CreateProcessRunner + -> CreateProcess + -> (Handle -> IO a) + -> IO a +withHandle h creator p a = creator p' $ a . select + where + base = p + { std_in = Inherit + , std_out = Inherit + , std_err = Inherit + } + (select, p') + | h == StdinHandle = + (stdinHandle, base { std_in = CreatePipe }) + | h == StdoutHandle = + (stdoutHandle, base { std_out = CreatePipe }) + | h == StderrHandle = + (stderrHandle, base { std_err = CreatePipe }) + +{- Like withHandle, but passes (stdin, stdout) handles to the action. -} +withBothHandles + :: CreateProcessRunner + -> CreateProcess + -> ((Handle, Handle) -> IO a) + -> IO a +withBothHandles creator p a = creator p' $ a . bothHandles + where + p' = p + { std_in = CreatePipe + , std_out = CreatePipe + , std_err = Inherit + } + +{- Extract a desired handle from createProcess's tuple. + - These partial functions are safe as long as createProcess is run + - with appropriate parameters to set up the desired handle. + - Get it wrong and the runtime crash will always happen, so should be + - easily noticed. -} +type HandleExtractor = (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> Handle +stdinHandle :: HandleExtractor +stdinHandle (Just h, _, _, _) = h +stdinHandle _ = error "expected stdinHandle" +stdoutHandle :: HandleExtractor +stdoutHandle (_, Just h, _, _) = h +stdoutHandle _ = error "expected stdoutHandle" +stderrHandle :: HandleExtractor +stderrHandle (_, _, Just h, _) = h +stderrHandle _ = error "expected stderrHandle" +bothHandles :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> (Handle, Handle) +bothHandles (Just hin, Just hout, _, _) = (hin, hout) +bothHandles _ = error "expected bothHandles" + +{- Debugging trace for a CreateProcess. -} +debugProcess :: CreateProcess -> IO () +debugProcess p = do + debugM "Utility.Process" $ unwords + [ action ++ ":" + , showCmd p + , maybe "" show (env p) + ] + where + action + | piped (std_in p) && piped (std_out p) = "chat" + | piped (std_in p) = "feed" + | piped (std_out p) = "read" + | otherwise = "call" + piped Inherit = False + piped _ = True + +{- Shows the command that a CreateProcess will run. -} +showCmd :: CreateProcess -> String +showCmd = go . cmdspec + where + go (ShellCommand s) = s + go (RawCommand c ps) = c ++ " " ++ show ps + +{- Wrappers for System.Process functions that do debug logging. + - + - More could be added, but these are the only ones I usually need. + -} + +createProcess :: CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) +createProcess p = do + debugProcess p + System.Process.createProcess p + +runInteractiveProcess + :: FilePath + -> [String] + -> Maybe FilePath + -> Maybe [(String, String)] + -> IO (Handle, Handle, Handle, ProcessHandle) +runInteractiveProcess f args c e = do + debugProcess $ (proc f args) + { std_in = CreatePipe + , std_out = CreatePipe + , std_err = CreatePipe + } + System.Process.runInteractiveProcess f args c e + +readProcess + :: FilePath + -> [String] + -> String + -> IO String +readProcess f args input = do + debugProcess $ (proc f args) { std_out = CreatePipe } + System.Process.readProcess f args input diff --git a/Utility/SafeCommand.hs b/Utility/SafeCommand.hs index 47280a40b1..19dd707b8d 100644 --- a/Utility/SafeCommand.hs +++ b/Utility/SafeCommand.hs @@ -8,7 +8,8 @@ module Utility.SafeCommand where import System.Exit -import System.Process +import Utility.Process +import System.Process (env) import Data.String.Utils import Control.Applicative From 9fc94d780b7331da13597208ba37a9f4d4ab6531 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 19 Jul 2012 00:57:40 -0400 Subject: [PATCH 071/331] better readProcess --- Annex/UUID.hs | 2 +- Backend/SHA.hs | 2 +- Config.hs | 4 ++-- Git/Command.hs | 2 +- Utility/INotify.hs | 2 +- Utility/Process.hs | 18 +++++++++++++++--- 6 files changed, 21 insertions(+), 9 deletions(-) diff --git a/Annex/UUID.hs b/Annex/UUID.hs index 13cee865d5..09862f9fc0 100644 --- a/Annex/UUID.hs +++ b/Annex/UUID.hs @@ -32,7 +32,7 @@ configkey = annexConfig "uuid" {- Generates a UUID. There is a library for this, but it's not packaged, - so use the command line tool. -} genUUID :: IO UUID -genUUID = gen . lines <$> readProcess command params [] +genUUID = gen . lines <$> readProcess command params where gen [] = error $ "no output from " ++ command gen (l:_) = toUUID l diff --git a/Backend/SHA.hs b/Backend/SHA.hs index 04b3e362aa..bb400a768b 100644 --- a/Backend/SHA.hs +++ b/Backend/SHA.hs @@ -54,7 +54,7 @@ shaN shasize file filesize = do case shaCommand shasize filesize of Left sha -> liftIO $ sha <$> L.readFile file Right command -> liftIO $ parse command . lines <$> - readProcess command (toCommand [File file]) "" + readProcess command (toCommand [File file]) where parse command [] = bad command parse command (l:_) diff --git a/Config.hs b/Config.hs index 1aa5a4ac50..2c26adc736 100644 --- a/Config.hs +++ b/Config.hs @@ -56,7 +56,7 @@ remoteCost r def = do cmd <- getRemoteConfig r "cost-command" "" (fromMaybe def . readish) <$> if not $ null cmd - then liftIO $ readProcess "sh" ["-c", cmd] "" + then liftIO $ readProcess "sh" ["-c", cmd] else getRemoteConfig r "cost" "" cheapRemoteCost :: Int @@ -116,4 +116,4 @@ getHttpHeaders = do cmd <- getConfig (annexConfig "http-headers-command") "" if null cmd then fromRepo $ Git.Config.getList "annex.http-headers" - else lines <$> liftIO (readProcess "sh" ["-c", cmd] "") + else lines <$> liftIO (readProcess "sh" ["-c", cmd]) diff --git a/Git/Command.hs b/Git/Command.hs index d7c9830649..cd6c98d339 100644 --- a/Git/Command.hs +++ b/Git/Command.hs @@ -52,7 +52,7 @@ pipeRead params repo = assertLocal repo $ - strictly. -} pipeWriteRead :: [CommandParam] -> String -> Repo -> IO String pipeWriteRead params s repo = assertLocal repo $ - readProcess "git" (toCommand $ gitCommandLine params repo) s + writeReadProcess "git" (toCommand $ gitCommandLine params repo) s {- Reads null terminated output of a git command (as enabled by the -z - parameter), and splits it. -} diff --git a/Utility/INotify.hs b/Utility/INotify.hs index 66c0ab23df..6af0228195 100644 --- a/Utility/INotify.hs +++ b/Utility/INotify.hs @@ -160,7 +160,7 @@ tooManyWatches hook dir = do querySysctl :: Read a => [CommandParam] -> IO (Maybe a) querySysctl ps = do - v <- catchMaybeIO $ readProcess "sysctl" (toCommand ps) [] + v <- catchMaybeIO $ readProcess "sysctl" (toCommand ps) case v of Nothing -> return Nothing Just s -> return $ parsesysctl s diff --git a/Utility/Process.hs b/Utility/Process.hs index 9b57c3b7ab..3b293df4f5 100644 --- a/Utility/Process.hs +++ b/Utility/Process.hs @@ -22,6 +22,7 @@ module Utility.Process ( withBothHandles, createProcess, runInteractiveProcess, + writeReadProcess, readProcess ) where @@ -192,11 +193,22 @@ runInteractiveProcess f args c e = do } System.Process.runInteractiveProcess f args c e -readProcess +{- I think this is a more descriptive name than System.Process.readProcess. -} +writeReadProcess :: FilePath -> [String] -> String -> IO String -readProcess f args input = do - debugProcess $ (proc f args) { std_out = CreatePipe } +writeReadProcess f args input = do + debugProcess $ (proc f args) { std_out = CreatePipe, std_in = CreatePipe } System.Process.readProcess f args input + +{- Normally, when reading from a process, it does not need to be fed any + - input. -} +readProcess + :: FilePath + -> [String] + -> IO String +readProcess f args = do + debugProcess $ (proc f args) { std_out = CreatePipe } + System.Process.readProcess f args [] From 1e0b7dda8cd66aca89ce3eb608dd2c568a77b141 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 19 Jul 2012 01:02:22 -0400 Subject: [PATCH 072/331] foo --- Utility/Process.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Utility/Process.hs b/Utility/Process.hs index 3b293df4f5..5c29bbdfb9 100644 --- a/Utility/Process.hs +++ b/Utility/Process.hs @@ -28,7 +28,7 @@ module Utility.Process ( import qualified System.Process import System.Process as X hiding (CreateProcess(..), createProcess, runInteractiveProcess, readProcess, readProcessWithExitCode, system, rawSystem, runInteractiveCommand, runProcess) -import System.Process hiding (createProcess, runInteractiveProcess, readProcess, readProcessWithExitCode) +import System.Process hiding (createProcess, runInteractiveProcess, readProcess) import System.Exit import System.IO import System.Log.Logger From e2c86a4b582bf222a51e9bb9066edce204d68ac8 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 19 Jul 2012 12:51:55 -0400 Subject: [PATCH 073/331] extacted Mounts.hsc from hsshellscript Converted from using c2hs to using hsc2hs, just because other code in git-annex uses hsc2hs. Various cleanups. This code is LGPLed, so I had to include that licence. --- .gitignore | 1 + Utility/Mounts.hsc | 81 ++++++++ debian/copyright | 7 + doc/LGPL | 502 +++++++++++++++++++++++++++++++++++++++++++++ 4 files changed, 591 insertions(+) create mode 100644 Utility/Mounts.hsc create mode 100644 doc/LGPL diff --git a/.gitignore b/.gitignore index afb5f314e4..4a18e7f26a 100644 --- a/.gitignore +++ b/.gitignore @@ -11,6 +11,7 @@ html *.tix .hpc Utility/Touch.hs +Utility/Mounts.hs Utility/*.o dist # Sandboxed builds diff --git a/Utility/Mounts.hsc b/Utility/Mounts.hsc new file mode 100644 index 0000000000..622ac877a2 --- /dev/null +++ b/Utility/Mounts.hsc @@ -0,0 +1,81 @@ +{- Interface to mtab (and fstab) + - + - Derived from hsshellscript, originally written by + - Volker Wysk + - + - Licensed under the GNU LGPL version 2.1 or higher. + -} + +{-# LANGUAGE ForeignFunctionInterface #-} + +module Utility.Mounts ( + Mntent(..), + read_mtab, + read_fstab, +) where + +import Control.Monad +import Foreign +import Foreign.C +import GHC.IO hiding (finally, bracket) +import Prelude hiding (catch) + +#include +#include + +data Mntent = Mntent + { mnt_fsname :: String + , mnt_dir :: String + , mnt_type :: String + , mnt_opts :: String + , mnt_freq :: Int + , mnt_passno :: Int + } deriving (Read, Show, Eq) + +read_mounts :: String -> IO [Mntent] +read_mounts path = do + h <- withCString path $ \cpath -> + withCString "r" $ \r -> + c_setmntent cpath r + when (h == nullPtr) $ + throwErrno "setmntent" + mntent <- getmntent h [] + _ <- c_endmntent h + return mntent + + where + getmntent h l = do + ptr <- c_getmntent h + if (ptr == nullPtr) + then return $ reverse l + else do + mnt_fsname_str <- #{peek struct mntent, mnt_fsname} ptr >>= peekCString + mnt_dir_str <- #{peek struct mntent, mnt_dir} ptr >>= peekCString + mnt_type_str <- #{peek struct mntent, mnt_type} ptr >>= peekCString + mnt_opts_str <- #{peek struct mntent, mnt_opts} ptr >>= peekCString + mnt_freq_int <- #{peek struct mntent, mnt_freq} ptr + mnt_passno_int <- #{peek struct mntent, mnt_passno} ptr + let ent = Mntent + { mnt_fsname = mnt_fsname_str + , mnt_dir = mnt_dir_str + , mnt_type = mnt_type_str + , mnt_opts = mnt_opts_str + , mnt_freq = mnt_freq_int + , mnt_passno = mnt_passno_int + } + getmntent h (ent:l) + +read_mtab :: IO [Mntent] +read_mtab = read_mounts "/etc/mtab" + +read_fstab :: IO [Mntent] +read_fstab = read_mounts "/etc/fstab" + +foreign import ccall safe "setmntent" + c_setmntent :: ((Ptr CChar) -> ((Ptr CChar) -> (IO (Ptr ())))) + +foreign import ccall safe "endmntent" + c_endmntent :: ((Ptr ()) -> (IO CInt)) + +foreign import ccall safe "getmntent" + c_getmntent :: ((Ptr ()) -> (IO (Ptr ()))) diff --git a/debian/copyright b/debian/copyright index de1e08e1cd..dcfbaf3e35 100644 --- a/debian/copyright +++ b/debian/copyright @@ -8,6 +8,13 @@ License: GPL-3+ this package's source, or in /usr/share/common-licenses/GPL-3 on Debian systems. +Files: Utility/Mtab.hcs +Copyright: Volker Wysk +License: LGPL-2.1+ + the full text of version 2.1 of the LGPL is distributed as doc/LGPL + in this package's source, or in /usr/share/common-licences/LGPL-2.1 + on Debian systems. + Files: doc/logo.png doc/logo_small.png doc/favicon.png Copyright: 2007 Henrik Nyh 2010 Joey Hess diff --git a/doc/LGPL b/doc/LGPL new file mode 100644 index 0000000000..4362b49151 --- /dev/null +++ b/doc/LGPL @@ -0,0 +1,502 @@ + GNU LESSER GENERAL PUBLIC LICENSE + Version 2.1, February 1999 + + Copyright (C) 1991, 1999 Free Software Foundation, Inc. + 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA + Everyone is permitted to copy and distribute verbatim copies + of this license document, but changing it is not allowed. + +[This is the first released version of the Lesser GPL. It also counts + as the successor of the GNU Library Public License, version 2, hence + the version number 2.1.] + + Preamble + + The licenses for most software are designed to take away your +freedom to share and change it. By contrast, the GNU General Public +Licenses are intended to guarantee your freedom to share and change +free software--to make sure the software is free for all its users. + + This license, the Lesser General Public License, applies to some +specially designated software packages--typically libraries--of the +Free Software Foundation and other authors who decide to use it. You +can use it too, but we suggest you first think carefully about whether +this license or the ordinary General Public License is the better +strategy to use in any particular case, based on the explanations below. + + When we speak of free software, we are referring to freedom of use, +not price. Our General Public Licenses are designed to make sure that +you have the freedom to distribute copies of free software (and charge +for this service if you wish); that you receive source code or can get +it if you want it; that you can change the software and use pieces of +it in new free programs; and that you are informed that you can do +these things. + + To protect your rights, we need to make restrictions that forbid +distributors to deny you these rights or to ask you to surrender these +rights. These restrictions translate to certain responsibilities for +you if you distribute copies of the library or if you modify it. + + For example, if you distribute copies of the library, whether gratis +or for a fee, you must give the recipients all the rights that we gave +you. You must make sure that they, too, receive or can get the source +code. If you link other code with the library, you must provide +complete object files to the recipients, so that they can relink them +with the library after making changes to the library and recompiling +it. And you must show them these terms so they know their rights. + + We protect your rights with a two-step method: (1) we copyright the +library, and (2) we offer you this license, which gives you legal +permission to copy, distribute and/or modify the library. + + To protect each distributor, we want to make it very clear that +there is no warranty for the free library. Also, if the library is +modified by someone else and passed on, the recipients should know +that what they have is not the original version, so that the original +author's reputation will not be affected by problems that might be +introduced by others. + + Finally, software patents pose a constant threat to the existence of +any free program. We wish to make sure that a company cannot +effectively restrict the users of a free program by obtaining a +restrictive license from a patent holder. Therefore, we insist that +any patent license obtained for a version of the library must be +consistent with the full freedom of use specified in this license. + + Most GNU software, including some libraries, is covered by the +ordinary GNU General Public License. This license, the GNU Lesser +General Public License, applies to certain designated libraries, and +is quite different from the ordinary General Public License. We use +this license for certain libraries in order to permit linking those +libraries into non-free programs. + + When a program is linked with a library, whether statically or using +a shared library, the combination of the two is legally speaking a +combined work, a derivative of the original library. The ordinary +General Public License therefore permits such linking only if the +entire combination fits its criteria of freedom. The Lesser General +Public License permits more lax criteria for linking other code with +the library. + + We call this license the "Lesser" General Public License because it +does Less to protect the user's freedom than the ordinary General +Public License. It also provides other free software developers Less +of an advantage over competing non-free programs. These disadvantages +are the reason we use the ordinary General Public License for many +libraries. However, the Lesser license provides advantages in certain +special circumstances. + + For example, on rare occasions, there may be a special need to +encourage the widest possible use of a certain library, so that it becomes +a de-facto standard. To achieve this, non-free programs must be +allowed to use the library. A more frequent case is that a free +library does the same job as widely used non-free libraries. In this +case, there is little to gain by limiting the free library to free +software only, so we use the Lesser General Public License. + + In other cases, permission to use a particular library in non-free +programs enables a greater number of people to use a large body of +free software. For example, permission to use the GNU C Library in +non-free programs enables many more people to use the whole GNU +operating system, as well as its variant, the GNU/Linux operating +system. + + Although the Lesser General Public License is Less protective of the +users' freedom, it does ensure that the user of a program that is +linked with the Library has the freedom and the wherewithal to run +that program using a modified version of the Library. + + The precise terms and conditions for copying, distribution and +modification follow. Pay close attention to the difference between a +"work based on the library" and a "work that uses the library". The +former contains code derived from the library, whereas the latter must +be combined with the library in order to run. + + GNU LESSER GENERAL PUBLIC LICENSE + TERMS AND CONDITIONS FOR COPYING, DISTRIBUTION AND MODIFICATION + + 0. This License Agreement applies to any software library or other +program which contains a notice placed by the copyright holder or +other authorized party saying it may be distributed under the terms of +this Lesser General Public License (also called "this License"). +Each licensee is addressed as "you". + + A "library" means a collection of software functions and/or data +prepared so as to be conveniently linked with application programs +(which use some of those functions and data) to form executables. + + The "Library", below, refers to any such software library or work +which has been distributed under these terms. A "work based on the +Library" means either the Library or any derivative work under +copyright law: that is to say, a work containing the Library or a +portion of it, either verbatim or with modifications and/or translated +straightforwardly into another language. (Hereinafter, translation is +included without limitation in the term "modification".) + + "Source code" for a work means the preferred form of the work for +making modifications to it. For a library, complete source code means +all the source code for all modules it contains, plus any associated +interface definition files, plus the scripts used to control compilation +and installation of the library. + + Activities other than copying, distribution and modification are not +covered by this License; they are outside its scope. The act of +running a program using the Library is not restricted, and output from +such a program is covered only if its contents constitute a work based +on the Library (independent of the use of the Library in a tool for +writing it). Whether that is true depends on what the Library does +and what the program that uses the Library does. + + 1. You may copy and distribute verbatim copies of the Library's +complete source code as you receive it, in any medium, provided that +you conspicuously and appropriately publish on each copy an +appropriate copyright notice and disclaimer of warranty; keep intact +all the notices that refer to this License and to the absence of any +warranty; and distribute a copy of this License along with the +Library. + + You may charge a fee for the physical act of transferring a copy, +and you may at your option offer warranty protection in exchange for a +fee. + + 2. You may modify your copy or copies of the Library or any portion +of it, thus forming a work based on the Library, and copy and +distribute such modifications or work under the terms of Section 1 +above, provided that you also meet all of these conditions: + + a) The modified work must itself be a software library. + + b) You must cause the files modified to carry prominent notices + stating that you changed the files and the date of any change. + + c) You must cause the whole of the work to be licensed at no + charge to all third parties under the terms of this License. + + d) If a facility in the modified Library refers to a function or a + table of data to be supplied by an application program that uses + the facility, other than as an argument passed when the facility + is invoked, then you must make a good faith effort to ensure that, + in the event an application does not supply such function or + table, the facility still operates, and performs whatever part of + its purpose remains meaningful. + + (For example, a function in a library to compute square roots has + a purpose that is entirely well-defined independent of the + application. Therefore, Subsection 2d requires that any + application-supplied function or table used by this function must + be optional: if the application does not supply it, the square + root function must still compute square roots.) + +These requirements apply to the modified work as a whole. If +identifiable sections of that work are not derived from the Library, +and can be reasonably considered independent and separate works in +themselves, then this License, and its terms, do not apply to those +sections when you distribute them as separate works. But when you +distribute the same sections as part of a whole which is a work based +on the Library, the distribution of the whole must be on the terms of +this License, whose permissions for other licensees extend to the +entire whole, and thus to each and every part regardless of who wrote +it. + +Thus, it is not the intent of this section to claim rights or contest +your rights to work written entirely by you; rather, the intent is to +exercise the right to control the distribution of derivative or +collective works based on the Library. + +In addition, mere aggregation of another work not based on the Library +with the Library (or with a work based on the Library) on a volume of +a storage or distribution medium does not bring the other work under +the scope of this License. + + 3. You may opt to apply the terms of the ordinary GNU General Public +License instead of this License to a given copy of the Library. To do +this, you must alter all the notices that refer to this License, so +that they refer to the ordinary GNU General Public License, version 2, +instead of to this License. (If a newer version than version 2 of the +ordinary GNU General Public License has appeared, then you can specify +that version instead if you wish.) Do not make any other change in +these notices. + + Once this change is made in a given copy, it is irreversible for +that copy, so the ordinary GNU General Public License applies to all +subsequent copies and derivative works made from that copy. + + This option is useful when you wish to copy part of the code of +the Library into a program that is not a library. + + 4. You may copy and distribute the Library (or a portion or +derivative of it, under Section 2) in object code or executable form +under the terms of Sections 1 and 2 above provided that you accompany +it with the complete corresponding machine-readable source code, which +must be distributed under the terms of Sections 1 and 2 above on a +medium customarily used for software interchange. + + If distribution of object code is made by offering access to copy +from a designated place, then offering equivalent access to copy the +source code from the same place satisfies the requirement to +distribute the source code, even though third parties are not +compelled to copy the source along with the object code. + + 5. A program that contains no derivative of any portion of the +Library, but is designed to work with the Library by being compiled or +linked with it, is called a "work that uses the Library". Such a +work, in isolation, is not a derivative work of the Library, and +therefore falls outside the scope of this License. + + However, linking a "work that uses the Library" with the Library +creates an executable that is a derivative of the Library (because it +contains portions of the Library), rather than a "work that uses the +library". The executable is therefore covered by this License. +Section 6 states terms for distribution of such executables. + + When a "work that uses the Library" uses material from a header file +that is part of the Library, the object code for the work may be a +derivative work of the Library even though the source code is not. +Whether this is true is especially significant if the work can be +linked without the Library, or if the work is itself a library. The +threshold for this to be true is not precisely defined by law. + + If such an object file uses only numerical parameters, data +structure layouts and accessors, and small macros and small inline +functions (ten lines or less in length), then the use of the object +file is unrestricted, regardless of whether it is legally a derivative +work. (Executables containing this object code plus portions of the +Library will still fall under Section 6.) + + Otherwise, if the work is a derivative of the Library, you may +distribute the object code for the work under the terms of Section 6. +Any executables containing that work also fall under Section 6, +whether or not they are linked directly with the Library itself. + + 6. As an exception to the Sections above, you may also combine or +link a "work that uses the Library" with the Library to produce a +work containing portions of the Library, and distribute that work +under terms of your choice, provided that the terms permit +modification of the work for the customer's own use and reverse +engineering for debugging such modifications. + + You must give prominent notice with each copy of the work that the +Library is used in it and that the Library and its use are covered by +this License. You must supply a copy of this License. If the work +during execution displays copyright notices, you must include the +copyright notice for the Library among them, as well as a reference +directing the user to the copy of this License. Also, you must do one +of these things: + + a) Accompany the work with the complete corresponding + machine-readable source code for the Library including whatever + changes were used in the work (which must be distributed under + Sections 1 and 2 above); and, if the work is an executable linked + with the Library, with the complete machine-readable "work that + uses the Library", as object code and/or source code, so that the + user can modify the Library and then relink to produce a modified + executable containing the modified Library. (It is understood + that the user who changes the contents of definitions files in the + Library will not necessarily be able to recompile the application + to use the modified definitions.) + + b) Use a suitable shared library mechanism for linking with the + Library. A suitable mechanism is one that (1) uses at run time a + copy of the library already present on the user's computer system, + rather than copying library functions into the executable, and (2) + will operate properly with a modified version of the library, if + the user installs one, as long as the modified version is + interface-compatible with the version that the work was made with. + + c) Accompany the work with a written offer, valid for at + least three years, to give the same user the materials + specified in Subsection 6a, above, for a charge no more + than the cost of performing this distribution. + + d) If distribution of the work is made by offering access to copy + from a designated place, offer equivalent access to copy the above + specified materials from the same place. + + e) Verify that the user has already received a copy of these + materials or that you have already sent this user a copy. + + For an executable, the required form of the "work that uses the +Library" must include any data and utility programs needed for +reproducing the executable from it. However, as a special exception, +the materials to be distributed need not include anything that is +normally distributed (in either source or binary form) with the major +components (compiler, kernel, and so on) of the operating system on +which the executable runs, unless that component itself accompanies +the executable. + + It may happen that this requirement contradicts the license +restrictions of other proprietary libraries that do not normally +accompany the operating system. Such a contradiction means you cannot +use both them and the Library together in an executable that you +distribute. + + 7. You may place library facilities that are a work based on the +Library side-by-side in a single library together with other library +facilities not covered by this License, and distribute such a combined +library, provided that the separate distribution of the work based on +the Library and of the other library facilities is otherwise +permitted, and provided that you do these two things: + + a) Accompany the combined library with a copy of the same work + based on the Library, uncombined with any other library + facilities. This must be distributed under the terms of the + Sections above. + + b) Give prominent notice with the combined library of the fact + that part of it is a work based on the Library, and explaining + where to find the accompanying uncombined form of the same work. + + 8. You may not copy, modify, sublicense, link with, or distribute +the Library except as expressly provided under this License. Any +attempt otherwise to copy, modify, sublicense, link with, or +distribute the Library is void, and will automatically terminate your +rights under this License. However, parties who have received copies, +or rights, from you under this License will not have their licenses +terminated so long as such parties remain in full compliance. + + 9. You are not required to accept this License, since you have not +signed it. However, nothing else grants you permission to modify or +distribute the Library or its derivative works. These actions are +prohibited by law if you do not accept this License. Therefore, by +modifying or distributing the Library (or any work based on the +Library), you indicate your acceptance of this License to do so, and +all its terms and conditions for copying, distributing or modifying +the Library or works based on it. + + 10. Each time you redistribute the Library (or any work based on the +Library), the recipient automatically receives a license from the +original licensor to copy, distribute, link with or modify the Library +subject to these terms and conditions. You may not impose any further +restrictions on the recipients' exercise of the rights granted herein. +You are not responsible for enforcing compliance by third parties with +this License. + + 11. If, as a consequence of a court judgment or allegation of patent +infringement or for any other reason (not limited to patent issues), +conditions are imposed on you (whether by court order, agreement or +otherwise) that contradict the conditions of this License, they do not +excuse you from the conditions of this License. If you cannot +distribute so as to satisfy simultaneously your obligations under this +License and any other pertinent obligations, then as a consequence you +may not distribute the Library at all. For example, if a patent +license would not permit royalty-free redistribution of the Library by +all those who receive copies directly or indirectly through you, then +the only way you could satisfy both it and this License would be to +refrain entirely from distribution of the Library. + +If any portion of this section is held invalid or unenforceable under any +particular circumstance, the balance of the section is intended to apply, +and the section as a whole is intended to apply in other circumstances. + +It is not the purpose of this section to induce you to infringe any +patents or other property right claims or to contest validity of any +such claims; this section has the sole purpose of protecting the +integrity of the free software distribution system which is +implemented by public license practices. Many people have made +generous contributions to the wide range of software distributed +through that system in reliance on consistent application of that +system; it is up to the author/donor to decide if he or she is willing +to distribute software through any other system and a licensee cannot +impose that choice. + +This section is intended to make thoroughly clear what is believed to +be a consequence of the rest of this License. + + 12. If the distribution and/or use of the Library is restricted in +certain countries either by patents or by copyrighted interfaces, the +original copyright holder who places the Library under this License may add +an explicit geographical distribution limitation excluding those countries, +so that distribution is permitted only in or among countries not thus +excluded. In such case, this License incorporates the limitation as if +written in the body of this License. + + 13. The Free Software Foundation may publish revised and/or new +versions of the Lesser General Public License from time to time. +Such new versions will be similar in spirit to the present version, +but may differ in detail to address new problems or concerns. + +Each version is given a distinguishing version number. If the Library +specifies a version number of this License which applies to it and +"any later version", you have the option of following the terms and +conditions either of that version or of any later version published by +the Free Software Foundation. If the Library does not specify a +license version number, you may choose any version ever published by +the Free Software Foundation. + + 14. If you wish to incorporate parts of the Library into other free +programs whose distribution conditions are incompatible with these, +write to the author to ask for permission. For software which is +copyrighted by the Free Software Foundation, write to the Free +Software Foundation; we sometimes make exceptions for this. Our +decision will be guided by the two goals of preserving the free status +of all derivatives of our free software and of promoting the sharing +and reuse of software generally. + + NO WARRANTY + + 15. BECAUSE THE LIBRARY IS LICENSED FREE OF CHARGE, THERE IS NO +WARRANTY FOR THE LIBRARY, TO THE EXTENT PERMITTED BY APPLICABLE LAW. +EXCEPT WHEN OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR +OTHER PARTIES PROVIDE THE LIBRARY "AS IS" WITHOUT WARRANTY OF ANY +KIND, EITHER EXPRESSED OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE +IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR +PURPOSE. THE ENTIRE RISK AS TO THE QUALITY AND PERFORMANCE OF THE +LIBRARY IS WITH YOU. SHOULD THE LIBRARY PROVE DEFECTIVE, YOU ASSUME +THE COST OF ALL NECESSARY SERVICING, REPAIR OR CORRECTION. + + 16. IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN +WRITING WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MAY MODIFY +AND/OR REDISTRIBUTE THE LIBRARY AS PERMITTED ABOVE, BE LIABLE TO YOU +FOR DAMAGES, INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR +CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OR INABILITY TO USE THE +LIBRARY (INCLUDING BUT NOT LIMITED TO LOSS OF DATA OR DATA BEING +RENDERED INACCURATE OR LOSSES SUSTAINED BY YOU OR THIRD PARTIES OR A +FAILURE OF THE LIBRARY TO OPERATE WITH ANY OTHER SOFTWARE), EVEN IF +SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE POSSIBILITY OF SUCH +DAMAGES. + + END OF TERMS AND CONDITIONS + + How to Apply These Terms to Your New Libraries + + If you develop a new library, and you want it to be of the greatest +possible use to the public, we recommend making it free software that +everyone can redistribute and change. You can do so by permitting +redistribution under these terms (or, alternatively, under the terms of the +ordinary General Public License). + + To apply these terms, attach the following notices to the library. It is +safest to attach them to the start of each source file to most effectively +convey the exclusion of warranty; and each file should have at least the +"copyright" line and a pointer to where the full notice is found. + + + Copyright (C) + + This library is free software; you can redistribute it and/or + modify it under the terms of the GNU Lesser General Public + License as published by the Free Software Foundation; either + version 2.1 of the License, or (at your option) any later version. + + This library is distributed in the hope that it will be useful, + but WITHOUT ANY WARRANTY; without even the implied warranty of + MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU + Lesser General Public License for more details. + + You should have received a copy of the GNU Lesser General Public + License along with this library; if not, write to the Free Software + Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA + +Also add information on how to contact you by electronic and paper mail. + +You should also get your employer (if you work as a programmer) or your +school, if any, to sign a "copyright disclaimer" for the library, if +necessary. Here is a sample; alter the names: + + Yoyodyne, Inc., hereby disclaims all copyright interest in the + library `Frob' (a library for tweaking knobs) written by James Random Hacker. + + , 1 April 1990 + Ty Coon, President of Vice + +That's all there is to it! From f20a40f9d4a4574c9f88dac8fd02b73d7f594b8b Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 19 Jul 2012 13:01:41 -0400 Subject: [PATCH 074/331] MountWatcher thread Currently only prints mount points when mounts happen. --- Assistant.hs | 7 +++ Assistant/Threads/MountWatcher.hs | 89 +++++++++++++++++++++++++++++++ Assistant/Threads/Watcher.hs | 2 - Makefile | 4 +- debian/control | 1 + git-annex.cabal | 11 +++- 6 files changed, 108 insertions(+), 6 deletions(-) create mode 100644 Assistant/Threads/MountWatcher.hs diff --git a/Assistant.hs b/Assistant.hs index 06484b0862..51639584c9 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -46,6 +46,11 @@ - Wakes up periodically and records the daemon's status to disk. - Thread 12: sanity checker - Wakes up periodically (rarely) and does sanity checks. + - Thread 13: mount watcher + - Either uses dbus to watch for drive mount events, or, when + - there's no dbus, polls to find newly mounted filesystems. + - Once a filesystem that contains a remote is mounted, syncs + - with it. - - ThreadState: (MVar) - The Annex state is stored here, which allows resuscitating the @@ -92,6 +97,7 @@ import Assistant.Threads.Merger import Assistant.Threads.TransferWatcher import Assistant.Threads.Transferrer import Assistant.Threads.SanityChecker +import Assistant.Threads.MountWatcher import qualified Utility.Daemon import Utility.LogFile import Utility.ThreadScheduler @@ -127,6 +133,7 @@ startDaemon assistant foreground , transfererThread st dstatus transferqueue transferslots , daemonStatusThread st dstatus , sanityCheckerThread st dstatus transferqueue changechan + , mountWatcherThread st dstatus , watchThread st dstatus transferqueue changechan ] waitForTermination diff --git a/Assistant/Threads/MountWatcher.hs b/Assistant/Threads/MountWatcher.hs new file mode 100644 index 0000000000..f3b9c0a3a7 --- /dev/null +++ b/Assistant/Threads/MountWatcher.hs @@ -0,0 +1,89 @@ +{- git-annex assistant mount watcher, using either dbus or mtab polling + - + - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +{-# LANGUAGE CPP #-} +{-# LANGUAGE OverloadedStrings #-} + +module Assistant.Threads.MountWatcher where + +import Common.Annex +import Assistant.ThreadedMonad +import Assistant.DaemonStatus +import Utility.ThreadScheduler +import Utility.Mounts + +import Control.Concurrent +import qualified Data.Set as S + +#if WITH_DBUS +import DBus.Client +#else +#warning Building without dbus support; will use mtab polling +#endif + +mountWatcherThread :: ThreadState -> DaemonStatusHandle -> IO () +mountWatcherThread st handle = +#if WITH_DBUS + dbusThread st handle +#else + pollingThread st handle +#endif + +#if WITH_DBUS +dbusThread :: ThreadState -> DaemonStatusHandle -> IO () +dbusThread st handle = do + r <- tryIO connectSession + case r of + Left e -> do + print $ "Failed to connect to dbus; falling back to mtab polling (" ++ show e ++ ")" + pollingThread st handle + Right client -> do + {- Store the current mount points in an mvar, + - to be compared later. We could in theory work + - out the mount point from the dbus message, but + - this is easier. -} + mvar <- newMVar =<< currentMountPoints + -- Spawn a listener thread, and returns. + listen client mountadded (go mvar) + where + mountadded = matchAny + { matchInterface = Just "org.gtk.Private.RemoteVolumeMonitor" + , matchMember = Just "MountAdded" + } + go mvar event = do + nowmounted <- currentMountPoints + wasmounted <- swapMVar mvar nowmounted + handleMounts st handle wasmounted nowmounted + +#endif + +pollingThread :: ThreadState -> DaemonStatusHandle -> IO () +pollingThread st handle = go =<< currentMountPoints + where + go wasmounted = do + threadDelaySeconds (Seconds 10) + nowmounted <- currentMountPoints + handleMounts st handle wasmounted nowmounted + go nowmounted + +handleMounts :: ThreadState -> DaemonStatusHandle -> MountPoints -> MountPoints -> IO () +handleMounts st handle wasmounted nowmounted = mapM_ (handleMount st handle) $ + S.toList $ newMountPoints wasmounted nowmounted + +handleMount :: ThreadState -> DaemonStatusHandle -> FilePath -> IO () +handleMount st handle mountpoint = do + putStrLn $ "mounted: " ++ mountpoint + +type MountPoints = S.Set FilePath + +{- Reads mtab, getting the current set of mount points. -} +currentMountPoints :: IO MountPoints +currentMountPoints = S.fromList . map mnt_dir <$> read_mtab + +{- Finds new mount points, given an old and a new set. -} +newMountPoints :: MountPoints -> MountPoints -> MountPoints +newMountPoints old new = S.difference new old diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs index 9f0eba74e9..ae4fafb78f 100644 --- a/Assistant/Threads/Watcher.hs +++ b/Assistant/Threads/Watcher.hs @@ -5,8 +5,6 @@ - Licensed under the GNU GPL version 3 or higher. -} -{-# LANGUAGE CPP #-} - module Assistant.Threads.Watcher where import Common.Annex diff --git a/Makefile b/Makefile index 0afb10a7bb..1791d43396 100644 --- a/Makefile +++ b/Makefile @@ -1,11 +1,11 @@ bins=git-annex mans=git-annex.1 git-annex-shell.1 -sources=Build/SysConfig.hs Utility/Touch.hs +sources=Build/SysConfig.hs Utility/Touch.hs Utility/Mounts.hs all=$(bins) $(mans) docs OS:=$(shell uname | sed 's/[-_].*//') ifeq ($(OS),Linux) -BASEFLAGS_OPTS+=-DWITH_INOTIFY +BASEFLAGS_OPTS+=-DWITH_INOTIFY -DWITH_DBUS clibs=Utility/libdiskfree.o else BASEFLAGS_OPTS+=-DWITH_KQUEUE diff --git a/debian/control b/debian/control index 79702ed29a..35cbfde054 100644 --- a/debian/control +++ b/debian/control @@ -22,6 +22,7 @@ Build-Depends: libghc-edit-distance-dev, libghc-hinotify-dev [linux-any], libghc-stm-dev (>= 2.3), + libghc-dbus-dev, ikiwiki, perlmagick, git, diff --git a/git-annex.cabal b/git-annex.cabal index e58bd4d957..00f57319d6 100644 --- a/git-annex.cabal +++ b/git-annex.cabal @@ -31,6 +31,9 @@ Flag S3 Flag Inotify Description: Enable inotify support +Flag Dbus + Description: Enable dbus support + Flag Assistant Description: Enable git-annex assistant and watch command @@ -41,8 +44,8 @@ Executable git-annex pcre-light, extensible-exceptions, dataenc, SHA, process, json, HTTP, base == 4.5.*, monad-control, transformers-base, lifted-base, IfElse, text, QuickCheck >= 2.1, bloomfilter, edit-distance, process - -- Need to list this because it's generated from a .hsc file. - Other-Modules: Utility.Touch + -- Need to list these because they're generated from .hsc files. + Other-Modules: Utility.Touch Utility.Mounts C-Sources: Utility/libdiskfree.c Extensions: CPP GHC-Options: -threaded @@ -59,6 +62,10 @@ Executable git-annex Build-Depends: hinotify CPP-Options: -DWITH_INOTIFY + if flag(Dbus) + Build-Depends: dbus + CPP-Options: -DWITH_DBUS + Test-Suite test Type: exitcode-stdio-1.0 Main-Is: test.hs From d5051ec088a443d0fbc0979d0421e62c60ec13f8 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 19 Jul 2012 16:29:22 -0400 Subject: [PATCH 075/331] update --- doc/install.mdwn | 2 ++ 1 file changed, 2 insertions(+) diff --git a/doc/install.mdwn b/doc/install.mdwn index 3168976f47..4eb7b179b6 100644 --- a/doc/install.mdwn +++ b/doc/install.mdwn @@ -46,6 +46,8 @@ To build and use git-annex, you will need: (optional; version 2.3 or newer) * [hinotify](http://hackage.haskell.org/package/hinotify) (optional; Linux only) + * [dbus](http://hackage.haskell.org/package/dbus) + (optional) * Shell commands * [git](http://git-scm.com/) * [uuid](http://www.ossp.org/pkg/lib/uuid/) From 107a7b9388077a2b7fe9ce107da3a4a5fa396e2e Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 19 Jul 2012 20:38:58 -0400 Subject: [PATCH 076/331] try to make Utility.Mounts portable This is an unholy mashup, but it just might work. It works on Linux, that's all I've tested. :) --- Assistant/Threads/MountWatcher.hs | 2 +- Makefile | 4 +- Utility/Mounts.hsc | 58 +++++++---------- Utility/libmounts.c | 105 ++++++++++++++++++++++++++++++ Utility/libmounts.h | 48 ++++++++++++++ debian/copyright | 13 +++- git-annex.cabal | 2 +- 7 files changed, 190 insertions(+), 42 deletions(-) create mode 100644 Utility/libmounts.c create mode 100644 Utility/libmounts.h diff --git a/Assistant/Threads/MountWatcher.hs b/Assistant/Threads/MountWatcher.hs index f3b9c0a3a7..cc62c294d2 100644 --- a/Assistant/Threads/MountWatcher.hs +++ b/Assistant/Threads/MountWatcher.hs @@ -82,7 +82,7 @@ type MountPoints = S.Set FilePath {- Reads mtab, getting the current set of mount points. -} currentMountPoints :: IO MountPoints -currentMountPoints = S.fromList . map mnt_dir <$> read_mtab +currentMountPoints = S.fromList . map mnt_dir <$> getMounts {- Finds new mount points, given an old and a new set. -} newMountPoints :: MountPoints -> MountPoints -> MountPoints diff --git a/Makefile b/Makefile index 1791d43396..a6030efa1d 100644 --- a/Makefile +++ b/Makefile @@ -6,10 +6,10 @@ all=$(bins) $(mans) docs OS:=$(shell uname | sed 's/[-_].*//') ifeq ($(OS),Linux) BASEFLAGS_OPTS+=-DWITH_INOTIFY -DWITH_DBUS -clibs=Utility/libdiskfree.o +clibs=Utility/libdiskfree.o Utility/libmounts.o else BASEFLAGS_OPTS+=-DWITH_KQUEUE -clibs=Utility/libdiskfree.o Utility/libkqueue.o +clibs=Utility/libdiskfree.o Utility/libmounts.o Utility/libkqueue.o endif PREFIX=/usr diff --git a/Utility/Mounts.hsc b/Utility/Mounts.hsc index 622ac877a2..6bcb03f2c4 100644 --- a/Utility/Mounts.hsc +++ b/Utility/Mounts.hsc @@ -2,6 +2,9 @@ - - Derived from hsshellscript, originally written by - Volker Wysk + - + - Modified to support BSD and Mac OS X by + - Joey Hess - - Licensed under the GNU LGPL version 2.1 or higher. -} @@ -10,8 +13,7 @@ module Utility.Mounts ( Mntent(..), - read_mtab, - read_fstab, + getMounts ) where import Control.Monad @@ -20,62 +22,46 @@ import Foreign.C import GHC.IO hiding (finally, bracket) import Prelude hiding (catch) -#include -#include +#include "libmounts.h" +{- This is a stripped down mntent, containing only + - fields available everywhere. -} data Mntent = Mntent { mnt_fsname :: String , mnt_dir :: String , mnt_type :: String - , mnt_opts :: String - , mnt_freq :: Int - , mnt_passno :: Int } deriving (Read, Show, Eq) -read_mounts :: String -> IO [Mntent] -read_mounts path = do - h <- withCString path $ \cpath -> - withCString "r" $ \r -> - c_setmntent cpath r +getMounts :: IO [Mntent] +getMounts = do + h <- c_mounts_start when (h == nullPtr) $ - throwErrno "setmntent" + throwErrno "getMounts" mntent <- getmntent h [] - _ <- c_endmntent h + _ <- c_mounts_end h return mntent where - getmntent h l = do - ptr <- c_getmntent h + getmntent h c = do + ptr <- c_mounts_next h if (ptr == nullPtr) - then return $ reverse l + then return $ reverse c else do mnt_fsname_str <- #{peek struct mntent, mnt_fsname} ptr >>= peekCString mnt_dir_str <- #{peek struct mntent, mnt_dir} ptr >>= peekCString mnt_type_str <- #{peek struct mntent, mnt_type} ptr >>= peekCString - mnt_opts_str <- #{peek struct mntent, mnt_opts} ptr >>= peekCString - mnt_freq_int <- #{peek struct mntent, mnt_freq} ptr - mnt_passno_int <- #{peek struct mntent, mnt_passno} ptr let ent = Mntent { mnt_fsname = mnt_fsname_str , mnt_dir = mnt_dir_str , mnt_type = mnt_type_str - , mnt_opts = mnt_opts_str - , mnt_freq = mnt_freq_int - , mnt_passno = mnt_passno_int } - getmntent h (ent:l) + getmntent h (ent:c) -read_mtab :: IO [Mntent] -read_mtab = read_mounts "/etc/mtab" +foreign import ccall unsafe "libmounts.h mounts_start" c_mounts_start + :: IO (Ptr ()) -read_fstab :: IO [Mntent] -read_fstab = read_mounts "/etc/fstab" +foreign import ccall unsafe "libmounts.h mounts_next" c_mounts_next + :: Ptr () -> IO (Ptr ()) -foreign import ccall safe "setmntent" - c_setmntent :: ((Ptr CChar) -> ((Ptr CChar) -> (IO (Ptr ())))) - -foreign import ccall safe "endmntent" - c_endmntent :: ((Ptr ()) -> (IO CInt)) - -foreign import ccall safe "getmntent" - c_getmntent :: ((Ptr ()) -> (IO (Ptr ()))) +foreign import ccall unsafe "libmounts.h mounts_end" c_mounts_end + :: Ptr () -> IO CInt diff --git a/Utility/libmounts.c b/Utility/libmounts.c new file mode 100644 index 0000000000..00755c577d --- /dev/null +++ b/Utility/libmounts.c @@ -0,0 +1,105 @@ +/* mounted filesystems, C mini-library + * + * Copyright (c) 1980, 1989, 1993, 1994 + * The Regents of the University of California. All rights reserved. + * Copyright (c) 2001 + * David Rufino + * Copyright 2012 + * Joey Hess + * + * Redistribution and use in source and binary forms, with or without + * modification, are permitted provided that the following conditions + * are met: + * 1. Redistributions of source code must retain the above copyright + * notice, this list of conditions and the following disclaimer. + * 2. Redistributions in binary form must reproduce the above copyright + * notice, this list of conditions and the following disclaimer in the + * documentation and/or other materials provided with the distribution. + * 3. Neither the name of the University nor the names of its contributors + * may be used to endorse or promote products derived from this software + * without specific prior written permission. + * + * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND + * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE + * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE + * ARE DISCLAIMED. IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE + * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL + * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS + * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) + * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT + * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY + * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF + * SUCH DAMAGE. + */ + +#include "libmounts.h" + +#include +#include + +#ifdef GETMNTENT +/* direct passthrough the getmntent */ +FILE *mounts_start (void) { + return setmntent("/etc/mtab", "r"); +} +int mounts_end (FILE *fp) { + return endmntent(fp); +} +struct mntent *mounts_next (FILE *fp) { + return getmntent(fp); +} +#endif + +#ifdef GETMNTINFOCALL +/* getmntent emulation using getmntinfo */ +FILE *mounts_start (void) { + return ((FILE *)0x1) /* dummy non-NULL FILE pointer, not used */ +} +int mounts_end (FILE *fp) { + return 1; +} + +static struct mntent _mntent; + +static struct mntent *statfs_to_mntent (struct MNTINFOSTRUCT *mntbuf) { + _mntent.mnt_fsname = mntbuf->f_mntfromname; + _mntent.mnt_dir = mntbuf->f_mntonname; + _mntent.mnt_type = mntbuf->f_fstypename; + + _mntent.mnt_opts = '\0'; + _mntent.mnt_freq = 0; + _mntent.mnt_passno = 0; + + return (&_mntent); +} + +static int pos = -1; +static int mntsize = -1; + +struct mntent *mounts_next (FILE *fp) { + struct MNTINFOSTRUCT *mntbuf; + + if (pos == -1 || mntsize == -1) + mntsize = GETMNTINFOCALL(&mntbuf, MNT_NOWAIT); + ++pos; + if (pos == mntsize) { + pos = mntsize = -1; + return NULL; + } + + return (statfs_to_mntent(&mntbuf[pos])); +} +#endif + +#ifdef UNKNOWN +/* dummy, do-nothing version */ +FILE *mounts_start (void) { + return ((FILE *)0x1); +} +int mounts_end (FILE *fp) { + return 1; +} +struct mntent *mounts_next (FILE *fp) { + return NULL; +} +#endif diff --git a/Utility/libmounts.h b/Utility/libmounts.h new file mode 100644 index 0000000000..0bd52e3230 --- /dev/null +++ b/Utility/libmounts.h @@ -0,0 +1,48 @@ +/* Include appropriate headers for the OS, and define what will be used. */ +#if defined(__APPLE__) +# include +# include +# include +/* In newer OSX versions, statfs64 is deprecated, in favor of statfs, + * which is 64 bit only with a build option -- but statfs64 still works, + * and this keeps older OSX also supported. */ +# define GETMNTINFOCALL getmntinfo64 +# define MNTINFOSTRUCT statfs64 +#else +#if defined (__FreeBSD__) +# include +# include +# include +# define GETMNTINFOCALL getmntinfo64 +# define MNTINFOSTRUCT statfs64 +#else +#if defined (__linux__) || defined (__FreeBSD_kernel__) +/* Linux or Debian kFreeBSD */ +#include +# define GETMNTENT +#else +# warning mounts listing code not available for this OS +# define UNKNOWN +#endif +#endif +#endif + +#include +#include +#include + +#ifndef GETMNTENT +#warning "boo" +struct mntent { + char *mnt_fsname; + char *mnt_dir; + char *mnt_type; + char *mnt_opts; /* not filled in */ + int mnt_freq; /* not filled in */ + int mnt_passno; /* not filled in */ +}; +#endif + +FILE *mounts_start (void); +int mounts_end (FILE *fp); +struct mntent *mounts_next (FILE *fp); diff --git a/debian/copyright b/debian/copyright index dcfbaf3e35..26a559cc51 100644 --- a/debian/copyright +++ b/debian/copyright @@ -8,13 +8,22 @@ License: GPL-3+ this package's source, or in /usr/share/common-licenses/GPL-3 on Debian systems. -Files: Utility/Mtab.hcs +Files: Utility/Mounts.hsc Copyright: Volker Wysk License: LGPL-2.1+ - the full text of version 2.1 of the LGPL is distributed as doc/LGPL + The full text of version 2.1 of the LGPL is distributed as doc/LGPL in this package's source, or in /usr/share/common-licences/LGPL-2.1 on Debian systems. +Files: Utility/libmounts.c +Copyright: 1980, 1989, 1993, 1994 The Regents of the University of California + 2001 David Rufino + 2012 Joey Hess +License: BSD-3-clause + The full test of the 3 clause BSD license is distributed inside + Utility/libmounts.c in this package's source, or in + /usr/share/common-licenses/BSD on Debian systems. + Files: doc/logo.png doc/logo_small.png doc/favicon.png Copyright: 2007 Henrik Nyh 2010 Joey Hess diff --git a/git-annex.cabal b/git-annex.cabal index 00f57319d6..be752f844e 100644 --- a/git-annex.cabal +++ b/git-annex.cabal @@ -46,7 +46,7 @@ Executable git-annex IfElse, text, QuickCheck >= 2.1, bloomfilter, edit-distance, process -- Need to list these because they're generated from .hsc files. Other-Modules: Utility.Touch Utility.Mounts - C-Sources: Utility/libdiskfree.c + C-Sources: Utility/libdiskfree.c Utility/libmounts.c Extensions: CPP GHC-Options: -threaded From f768cddf3a7048334f76fff1a2c895b33fea18af Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 19 Jul 2012 20:44:58 -0400 Subject: [PATCH 077/331] fix build on OSX --- Utility/libmounts.c | 5 +---- Utility/libmounts.h | 5 +---- 2 files changed, 2 insertions(+), 8 deletions(-) diff --git a/Utility/libmounts.c b/Utility/libmounts.c index 00755c577d..d29c6ee6a4 100644 --- a/Utility/libmounts.c +++ b/Utility/libmounts.c @@ -34,9 +34,6 @@ #include "libmounts.h" -#include -#include - #ifdef GETMNTENT /* direct passthrough the getmntent */ FILE *mounts_start (void) { @@ -53,7 +50,7 @@ struct mntent *mounts_next (FILE *fp) { #ifdef GETMNTINFOCALL /* getmntent emulation using getmntinfo */ FILE *mounts_start (void) { - return ((FILE *)0x1) /* dummy non-NULL FILE pointer, not used */ + return ((FILE *)0x1); /* dummy non-NULL FILE pointer, not used */ } int mounts_end (FILE *fp) { return 1; diff --git a/Utility/libmounts.h b/Utility/libmounts.h index 0bd52e3230..12f5564b5b 100644 --- a/Utility/libmounts.h +++ b/Utility/libmounts.h @@ -27,12 +27,9 @@ #endif #endif -#include -#include -#include +#include #ifndef GETMNTENT -#warning "boo" struct mntent { char *mnt_fsname; char *mnt_dir; From 4bcc92abd72e060e073eaf0a9d988ae3a015d39c Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 19 Jul 2012 21:19:29 -0400 Subject: [PATCH 078/331] now working on OSX While this seems to work fine when used in a simple program, when I load it in ghci, it segfaults about half the time. Don't know why, and seems ghci specific, but if I get reports of crashes, I'll need to look into that. --- Utility/libmounts.c | 12 ++++++++---- Utility/libmounts.h | 16 ++-------------- 2 files changed, 10 insertions(+), 18 deletions(-) diff --git a/Utility/libmounts.c b/Utility/libmounts.c index d29c6ee6a4..be18fe0c28 100644 --- a/Utility/libmounts.c +++ b/Utility/libmounts.c @@ -34,6 +34,9 @@ #include "libmounts.h" +#include +#include + #ifdef GETMNTENT /* direct passthrough the getmntent */ FILE *mounts_start (void) { @@ -47,7 +50,7 @@ struct mntent *mounts_next (FILE *fp) { } #endif -#ifdef GETMNTINFOCALL +#ifdef GETMNTINFO /* getmntent emulation using getmntinfo */ FILE *mounts_start (void) { return ((FILE *)0x1); /* dummy non-NULL FILE pointer, not used */ @@ -58,7 +61,7 @@ int mounts_end (FILE *fp) { static struct mntent _mntent; -static struct mntent *statfs_to_mntent (struct MNTINFOSTRUCT *mntbuf) { +static struct mntent *statfs_to_mntent (struct statfs *mntbuf) { _mntent.mnt_fsname = mntbuf->f_mntfromname; _mntent.mnt_dir = mntbuf->f_mntonname; _mntent.mnt_type = mntbuf->f_fstypename; @@ -72,15 +75,16 @@ static struct mntent *statfs_to_mntent (struct MNTINFOSTRUCT *mntbuf) { static int pos = -1; static int mntsize = -1; +struct statfs *mntbuf = NULL; struct mntent *mounts_next (FILE *fp) { - struct MNTINFOSTRUCT *mntbuf; if (pos == -1 || mntsize == -1) - mntsize = GETMNTINFOCALL(&mntbuf, MNT_NOWAIT); + mntsize = getmntinfo(&mntbuf, MNT_NOWAIT); ++pos; if (pos == mntsize) { pos = mntsize = -1; + mntbuf = NULL; return NULL; } diff --git a/Utility/libmounts.h b/Utility/libmounts.h index 12f5564b5b..b659786291 100644 --- a/Utility/libmounts.h +++ b/Utility/libmounts.h @@ -1,20 +1,9 @@ /* Include appropriate headers for the OS, and define what will be used. */ -#if defined(__APPLE__) +#if defined (__FreeBSD__) || defined (__APPLE__) # include # include # include -/* In newer OSX versions, statfs64 is deprecated, in favor of statfs, - * which is 64 bit only with a build option -- but statfs64 still works, - * and this keeps older OSX also supported. */ -# define GETMNTINFOCALL getmntinfo64 -# define MNTINFOSTRUCT statfs64 -#else -#if defined (__FreeBSD__) -# include -# include -# include -# define GETMNTINFOCALL getmntinfo64 -# define MNTINFOSTRUCT statfs64 +# define GETMNTINFO #else #if defined (__linux__) || defined (__FreeBSD_kernel__) /* Linux or Debian kFreeBSD */ @@ -25,7 +14,6 @@ # define UNKNOWN #endif #endif -#endif #include From ac044de486331462ce2a815db45f62399fd2cf2e Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 19 Jul 2012 21:20:38 -0400 Subject: [PATCH 079/331] cleanup --- Utility/libmounts.c | 3 --- 1 file changed, 3 deletions(-) diff --git a/Utility/libmounts.c b/Utility/libmounts.c index be18fe0c28..8669f33ea9 100644 --- a/Utility/libmounts.c +++ b/Utility/libmounts.c @@ -34,9 +34,6 @@ #include "libmounts.h" -#include -#include - #ifdef GETMNTENT /* direct passthrough the getmntent */ FILE *mounts_start (void) { From 0496a3971d4679e6a482a5eb277091980383f831 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 19 Jul 2012 21:25:26 -0400 Subject: [PATCH 080/331] store whole Mntents This way, if a mount point was already mounted, but something else gets mounted there, it'll be seen as a new mount. --- Assistant/Threads/MountWatcher.hs | 10 +++++----- Utility/Mounts.hsc | 2 +- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/Assistant/Threads/MountWatcher.hs b/Assistant/Threads/MountWatcher.hs index cc62c294d2..b55e3284bc 100644 --- a/Assistant/Threads/MountWatcher.hs +++ b/Assistant/Threads/MountWatcher.hs @@ -74,15 +74,15 @@ handleMounts :: ThreadState -> DaemonStatusHandle -> MountPoints -> MountPoints handleMounts st handle wasmounted nowmounted = mapM_ (handleMount st handle) $ S.toList $ newMountPoints wasmounted nowmounted -handleMount :: ThreadState -> DaemonStatusHandle -> FilePath -> IO () -handleMount st handle mountpoint = do - putStrLn $ "mounted: " ++ mountpoint +handleMount :: ThreadState -> DaemonStatusHandle -> Mntent -> IO () +handleMount st handle mntent = do + putStrLn $ "mounted: " ++ mnt_dir mntent -type MountPoints = S.Set FilePath +type MountPoints = S.Set Mntent {- Reads mtab, getting the current set of mount points. -} currentMountPoints :: IO MountPoints -currentMountPoints = S.fromList . map mnt_dir <$> getMounts +currentMountPoints = S.fromList <$> getMounts {- Finds new mount points, given an old and a new set. -} newMountPoints :: MountPoints -> MountPoints -> MountPoints diff --git a/Utility/Mounts.hsc b/Utility/Mounts.hsc index 6bcb03f2c4..4994c5e180 100644 --- a/Utility/Mounts.hsc +++ b/Utility/Mounts.hsc @@ -30,7 +30,7 @@ data Mntent = Mntent { mnt_fsname :: String , mnt_dir :: String , mnt_type :: String - } deriving (Read, Show, Eq) + } deriving (Read, Show, Eq, Ord) getMounts :: IO [Mntent] getMounts = do From 6b4fe507f68427e0cb37e22f278c375151e8e89f Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 19 Jul 2012 23:34:33 -0400 Subject: [PATCH 081/331] only use dbus when there's a client connected we know will send mount events --- Assistant/Threads/MountWatcher.hs | 66 ++++++++++++++++++++----------- 1 file changed, 44 insertions(+), 22 deletions(-) diff --git a/Assistant/Threads/MountWatcher.hs b/Assistant/Threads/MountWatcher.hs index b55e3284bc..f1e33a99fa 100644 --- a/Assistant/Threads/MountWatcher.hs +++ b/Assistant/Threads/MountWatcher.hs @@ -21,6 +21,7 @@ import qualified Data.Set as S #if WITH_DBUS import DBus.Client +import DBus #else #warning Building without dbus support; will use mtab polling #endif @@ -34,30 +35,51 @@ mountWatcherThread st handle = #endif #if WITH_DBUS + dbusThread :: ThreadState -> DaemonStatusHandle -> IO () -dbusThread st handle = do - r <- tryIO connectSession - case r of - Left e -> do - print $ "Failed to connect to dbus; falling back to mtab polling (" ++ show e ++ ")" - pollingThread st handle - Right client -> do - {- Store the current mount points in an mvar, - - to be compared later. We could in theory work - - out the mount point from the dbus message, but - - this is easier. -} - mvar <- newMVar =<< currentMountPoints - -- Spawn a listener thread, and returns. - listen client mountadded (go mvar) +dbusThread st handle = (go =<< connectSession) `catchIO` onerr where - mountadded = matchAny - { matchInterface = Just "org.gtk.Private.RemoteVolumeMonitor" - , matchMember = Just "MountAdded" - } - go mvar event = do - nowmounted <- currentMountPoints - wasmounted <- swapMVar mvar nowmounted - handleMounts st handle wasmounted nowmounted + go client = ifM (checkMountMonitor client) + ( do + {- Store the current mount points in an mvar, + - to be compared later. We could in theory + - work out the mount point from the dbus + - message, but this is easier. -} + mvar <- newMVar =<< currentMountPoints + listen client mountAdded $ \_event -> do + nowmounted <- currentMountPoints + wasmounted <- swapMVar mvar nowmounted + handleMounts st handle wasmounted nowmounted + , do + runThreadState st $ + warning "No known volume monitor available through dbus; falling back to mtab polling" + pollinstead + ) + onerr e = do + runThreadState st $ + warning $ "Failed to use dbus; falling back to mtab polling (" ++ show e ++ ")" + pollinstead + pollinstead = pollingThread st handle + +listClientNames :: Client -> IO [String] +listClientNames client = do + reply <- call_ client (methodCall "/org/freedesktop/DBus" "org.freedesktop.DBus" "ListNames") + { methodCallDestination = Just "org.freedesktop.DBus" } + return $ fromMaybe [] $ fromVariant (methodReturnBody reply !! 0) + +{- Examine the list of clients connected to dbus, to see if there + - are any we can use to monitor mounts. -} +checkMountMonitor :: Client -> IO Bool +checkMountMonitor client = any (`elem` knownclients) <$> listClientNames client + where + knownclients = ["org.gtk.Private.GduVolumeMonitor"] + +{- Filter matching events recieved when drives are mounted. -} +mountAdded ::MatchRule +mountAdded = matchAny + { matchInterface = Just "org.gtk.Private.RemoteVolumeMonitor" + , matchMember = Just "MountAdded" + } #endif From d9f26115c32c8df6865afc291d55b83b142c8428 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 20 Jul 2012 01:59:21 -0400 Subject: [PATCH 082/331] use dbus to activate GduVolumeMonitor if it's not already running --- Assistant/Threads/MountWatcher.hs | 27 +++++++++++++++++++++++---- 1 file changed, 23 insertions(+), 4 deletions(-) diff --git a/Assistant/Threads/MountWatcher.hs b/Assistant/Threads/MountWatcher.hs index f1e33a99fa..a6c15540a6 100644 --- a/Assistant/Threads/MountWatcher.hs +++ b/Assistant/Threads/MountWatcher.hs @@ -22,6 +22,7 @@ import qualified Data.Set as S #if WITH_DBUS import DBus.Client import DBus +import Data.Word (Word32) #else #warning Building without dbus support; will use mtab polling #endif @@ -63,16 +64,34 @@ dbusThread st handle = (go =<< connectSession) `catchIO` onerr listClientNames :: Client -> IO [String] listClientNames client = do - reply <- call_ client (methodCall "/org/freedesktop/DBus" "org.freedesktop.DBus" "ListNames") - { methodCallDestination = Just "org.freedesktop.DBus" } + reply <- callDBus client "ListNames" [] return $ fromMaybe [] $ fromVariant (methodReturnBody reply !! 0) +callDBus :: Client -> MemberName -> [Variant] -> IO MethodReturn +callDBus client name params = call_ client $ + (methodCall "/org/freedesktop/DBus" "org.freedesktop.DBus" name) + { methodCallDestination = Just "org.freedesktop.DBus" + , methodCallBody = params + } + {- Examine the list of clients connected to dbus, to see if there - - are any we can use to monitor mounts. -} + - are any we can use to monitor mounts. If not, will attempt to start one. -} checkMountMonitor :: Client -> IO Bool -checkMountMonitor client = any (`elem` knownclients) <$> listClientNames client +checkMountMonitor client = ifM isrunning + ( return True + , startclient knownclients + ) where + isrunning = any (`elem` knownclients) <$> listClientNames client knownclients = ["org.gtk.Private.GduVolumeMonitor"] + startclient [] = return False + startclient (c:cs) = do + _ <- callDBus client "StartServiceByName" + [toVariant c, toVariant (0 :: Word32)] + ifM isrunning + ( return True + , startclient cs + ) {- Filter matching events recieved when drives are mounted. -} mountAdded ::MatchRule From 2fce3940b506a7671f622e872e049008df8ef4ad Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 20 Jul 2012 02:16:09 -0400 Subject: [PATCH 083/331] catch all errors --- Assistant/Threads/MountWatcher.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/Assistant/Threads/MountWatcher.hs b/Assistant/Threads/MountWatcher.hs index a6c15540a6..1cf854d0aa 100644 --- a/Assistant/Threads/MountWatcher.hs +++ b/Assistant/Threads/MountWatcher.hs @@ -17,6 +17,7 @@ import Utility.ThreadScheduler import Utility.Mounts import Control.Concurrent +import qualified Control.Exception as E import qualified Data.Set as S #if WITH_DBUS @@ -38,7 +39,7 @@ mountWatcherThread st handle = #if WITH_DBUS dbusThread :: ThreadState -> DaemonStatusHandle -> IO () -dbusThread st handle = (go =<< connectSession) `catchIO` onerr +dbusThread st handle = E.catch (go =<< connectSession) onerr where go client = ifM (checkMountMonitor client) ( do @@ -56,6 +57,7 @@ dbusThread st handle = (go =<< connectSession) `catchIO` onerr warning "No known volume monitor available through dbus; falling back to mtab polling" pollinstead ) + onerr :: E.SomeException -> IO () onerr e = do runThreadState st $ warning $ "Failed to use dbus; falling back to mtab polling (" ++ show e ++ ")" From 833bd24a33f2f13051439865464918821ba5c65c Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 20 Jul 2012 12:01:28 -0400 Subject: [PATCH 084/331] tweak --- Assistant.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Assistant.hs b/Assistant.hs index 51639584c9..dc36957da7 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -124,7 +124,7 @@ startDaemon assistant foreground pushmap <- newFailedPushMap transferqueue <- newTransferQueue transferslots <- newTransferSlots - mapM_ (void . forkIO) + mapM_ forkIO [ commitThread st changechan commitchan transferqueue dstatus , pushThread st dstatus commitchan pushmap , pushRetryThread st pushmap From da4c506d61115236f3e43dd0bd17f30cd54df950 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 20 Jul 2012 15:03:24 -0400 Subject: [PATCH 085/331] use safe FFI imports This avoids blocking all threads when calling waitchange_kqueue, which blocks. --- Utility/Kqueue.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/Utility/Kqueue.hs b/Utility/Kqueue.hs index c1a0a5cd60..f44893195c 100644 --- a/Utility/Kqueue.hs +++ b/Utility/Kqueue.hs @@ -142,11 +142,11 @@ findDirContents dirmap dir = concatMap absolutecontents $ search search = map snd $ M.toList $ M.filter (\i -> dirName i == dir) dirmap -foreign import ccall unsafe "libkqueue.h init_kqueue" c_init_kqueue +foreign import ccall safe "libkqueue.h init_kqueue" c_init_kqueue :: IO Fd -foreign import ccall unsafe "libkqueue.h addfds_kqueue" c_addfds_kqueue +foreign import ccall safe "libkqueue.h addfds_kqueue" c_addfds_kqueue :: Fd -> CInt -> Ptr Fd -> IO () -foreign import ccall unsafe "libkqueue.h waitchange_kqueue" c_waitchange_kqueue +foreign import ccall safe "libkqueue.h waitchange_kqueue" c_waitchange_kqueue :: Fd -> IO Fd {- Initializes a Kqueue to watch a directory, and all its subdirectories. -} From 9d26b532abfd04bc97f9b922ddb7c14e545a0073 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 20 Jul 2012 15:03:58 -0400 Subject: [PATCH 086/331] use safe FFI imports for diskfree There's a minor performance overhead to doing this, but this way I don't have to worry about a situation where statfs might block for a long time. For example, when it's on a network filesystem. --- Utility/DiskFree.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Utility/DiskFree.hs b/Utility/DiskFree.hs index ff70705621..18c7f2ee61 100644 --- a/Utility/DiskFree.hs +++ b/Utility/DiskFree.hs @@ -15,7 +15,7 @@ import Foreign.C.Types import Foreign.C.String import Foreign.C.Error -foreign import ccall unsafe "libdiskfree.h diskfree" c_diskfree +foreign import ccall safe "libdiskfree.h diskfree" c_diskfree :: CString -> IO CULLong getDiskFree :: FilePath -> IO (Maybe Integer) From f6d4786b860c92dffd855a90a070212324ff69dc Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 20 Jul 2012 15:07:48 -0400 Subject: [PATCH 087/331] left unsafe imports here; added a comment with a rationalle --- Utility/Mounts.hsc | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/Utility/Mounts.hsc b/Utility/Mounts.hsc index 4994c5e180..6b69e844a3 100644 --- a/Utility/Mounts.hsc +++ b/Utility/Mounts.hsc @@ -57,11 +57,13 @@ getMounts = do } getmntent h (ent:c) +{- Using unsafe imports because the C functions are belived to never block. + - Note that getmntinfo is called with MNT_NOWAIT to avoid possibly blocking; + - while getmntent only accesses a file in /etc (or /proc) that should not + - block. -} foreign import ccall unsafe "libmounts.h mounts_start" c_mounts_start :: IO (Ptr ()) - foreign import ccall unsafe "libmounts.h mounts_next" c_mounts_next :: Ptr () -> IO (Ptr ()) - foreign import ccall unsafe "libmounts.h mounts_end" c_mounts_end :: Ptr () -> IO CInt From 42e73537d1977eac2da2760647e9131f5c9b9eed Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 20 Jul 2012 18:14:57 -0400 Subject: [PATCH 088/331] detect KDE automounting Best dbus events I could find were setupDone from org.kde.Solid.Device. There may be some spurious events, but that's ok, the code will only check to see if new mounts are available. It does not try to auto-start this service if it's not running. --- Assistant/Threads/MountWatcher.hs | 83 +++++++++++++++++++++---------- 1 file changed, 56 insertions(+), 27 deletions(-) diff --git a/Assistant/Threads/MountWatcher.hs b/Assistant/Threads/MountWatcher.hs index 1cf854d0aa..8636533517 100644 --- a/Assistant/Threads/MountWatcher.hs +++ b/Assistant/Threads/MountWatcher.hs @@ -19,6 +19,7 @@ import Utility.Mounts import Control.Concurrent import qualified Control.Exception as E import qualified Data.Set as S +import System.Log.Logger #if WITH_DBUS import DBus.Client @@ -48,10 +49,11 @@ dbusThread st handle = E.catch (go =<< connectSession) onerr - work out the mount point from the dbus - message, but this is easier. -} mvar <- newMVar =<< currentMountPoints - listen client mountAdded $ \_event -> do - nowmounted <- currentMountPoints - wasmounted <- swapMVar mvar nowmounted - handleMounts st handle wasmounted nowmounted + forM_ mountAdded $ \matcher -> + listen client matcher $ \_event -> do + nowmounted <- currentMountPoints + wasmounted <- swapMVar mvar nowmounted + handleMounts st handle wasmounted nowmounted , do runThreadState st $ warning "No known volume monitor available through dbus; falling back to mtab polling" @@ -64,8 +66,10 @@ dbusThread st handle = E.catch (go =<< connectSession) onerr pollinstead pollinstead = pollingThread st handle -listClientNames :: Client -> IO [String] -listClientNames client = do +type ServiceName = String + +listServiceNames :: Client -> IO [ServiceName] +listServiceNames client = do reply <- callDBus client "ListNames" [] return $ fromMaybe [] $ fromVariant (methodReturnBody reply !! 0) @@ -76,31 +80,53 @@ callDBus client name params = call_ client $ , methodCallBody = params } -{- Examine the list of clients connected to dbus, to see if there +{- Examine the list of services connected to dbus, to see if there - are any we can use to monitor mounts. If not, will attempt to start one. -} checkMountMonitor :: Client -> IO Bool -checkMountMonitor client = ifM isrunning - ( return True - , startclient knownclients - ) +checkMountMonitor client = do + running <- filter (`elem` usableservices) + <$> listServiceNames client + if null running + then startOneService client startableservices + else do + myDebug [ "Using running DBUS service" + , Prelude.head running + , "to monitor mount events." + ] + return True where - isrunning = any (`elem` knownclients) <$> listClientNames client - knownclients = ["org.gtk.Private.GduVolumeMonitor"] - startclient [] = return False - startclient (c:cs) = do - _ <- callDBus client "StartServiceByName" - [toVariant c, toVariant (0 :: Word32)] - ifM isrunning - ( return True - , startclient cs - ) + startableservices = [gvfs] + usableservices = startableservices ++ [kde] + gvfs = "org.gtk.Private.GduVolumeMonitor" + kde = "org.kde.DeviceNotifications" + +startOneService :: Client -> [ServiceName] -> IO Bool +startOneService _ [] = return False +startOneService client (x:xs) = do + _ <- callDBus client "StartServiceByName" + [toVariant x, toVariant (0 :: Word32)] + ifM (elem x <$> listServiceNames client) + ( do + myDebug [ "Started DBUS service" + , x + , "to monitor mount events." + ] + return True + , startOneService client xs + ) {- Filter matching events recieved when drives are mounted. -} -mountAdded ::MatchRule -mountAdded = matchAny - { matchInterface = Just "org.gtk.Private.RemoteVolumeMonitor" - , matchMember = Just "MountAdded" - } +mountAdded :: [MatchRule] +mountAdded = [gvfs, kde] + where + gvfs = matchAny + { matchInterface = Just "org.gtk.Private.RemoteVolumeMonitor" + , matchMember = Just "MountAdded" + } + kde = matchAny + { matchInterface = Just "org.kde.Solid.Device" + , matchMember = Just "setupDone" + } #endif @@ -119,7 +145,7 @@ handleMounts st handle wasmounted nowmounted = mapM_ (handleMount st handle) $ handleMount :: ThreadState -> DaemonStatusHandle -> Mntent -> IO () handleMount st handle mntent = do - putStrLn $ "mounted: " ++ mnt_dir mntent + myDebug ["detected mount of", mnt_dir mntent] type MountPoints = S.Set Mntent @@ -130,3 +156,6 @@ currentMountPoints = S.fromList <$> getMounts {- Finds new mount points, given an old and a new set. -} newMountPoints :: MountPoints -> MountPoints -> MountPoints newMountPoints old new = S.difference new old + +myDebug :: [String] -> IO () +myDebug ms = debugM "MountWatcher" $ unwords ("MountWatcher:":ms) From b48d7747a3ac8bea7d58e8fff8faf791f98699c0 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 20 Jul 2012 19:29:59 -0400 Subject: [PATCH 089/331] debugging improvements add timestamps to debug messages Add lots of debug output in the assistant's threads. --- Assistant.hs | 4 ++- Assistant/Common.hs | 21 +++++++++++++ Assistant/Threads/Committer.hs | 23 ++++++++++++-- Assistant/Threads/Merger.hs | 17 ++++++++-- Assistant/Threads/MountWatcher.hs | 15 +++++---- Assistant/Threads/Pusher.hs | 28 +++++++++++++++-- Assistant/Threads/SanityChecker.hs | 15 +++++++-- Assistant/Threads/TransferWatcher.hs | 25 ++++++++++++--- Assistant/Threads/Transferrer.hs | 13 ++++++-- Assistant/Threads/Watcher.hs | 46 +++++++++++++++++++--------- Option.hs | 12 ++++++-- 11 files changed, 175 insertions(+), 44 deletions(-) create mode 100644 Assistant/Common.hs diff --git a/Assistant.hs b/Assistant.hs index dc36957da7..4bb1ed4cea 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -82,7 +82,7 @@ module Assistant where -import Common.Annex +import Assistant.Common import Assistant.ThreadedMonad import Assistant.DaemonStatus import Assistant.Changes @@ -136,6 +136,8 @@ startDaemon assistant foreground , mountWatcherThread st dstatus , watchThread st dstatus transferqueue changechan ] + debug "assistant" + ["all git-annex assistant threads started"] waitForTermination stopDaemon :: Annex () diff --git a/Assistant/Common.hs b/Assistant/Common.hs new file mode 100644 index 0000000000..c1a346e75c --- /dev/null +++ b/Assistant/Common.hs @@ -0,0 +1,21 @@ +{- Common infrastructure for the git-annex assistant threads. + - + - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Assistant.Common ( + module X, + ThreadName, + debug +) where + +import Common.Annex as X + +import System.Log.Logger + +type ThreadName = String + +debug :: ThreadName -> [String] -> IO () +debug threadname ws = debugM threadname $ unwords $ (threadname ++ ":") : ws diff --git a/Assistant/Threads/Committer.hs b/Assistant/Threads/Committer.hs index ff5cc9eabc..ffb2494041 100644 --- a/Assistant/Threads/Committer.hs +++ b/Assistant/Threads/Committer.hs @@ -7,7 +7,7 @@ module Assistant.Threads.Committer where -import Common.Annex +import Assistant.Common import Assistant.Changes import Assistant.Commits import Assistant.ThreadedMonad @@ -31,6 +31,9 @@ import Data.Tuple.Utils import qualified Data.Set as S import Data.Either +thisThread :: ThreadName +thisThread = "Committer" + {- This thread makes git commits at appropriate times. -} commitThread :: ThreadState -> ChangeChan -> CommitChan -> TransferQueue -> DaemonStatusHandle -> IO () commitThread st changechan commitchan transferqueue dstatus = runEvery (Seconds 1) $ do @@ -45,10 +48,24 @@ commitThread st changechan commitchan transferqueue dstatus = runEvery (Seconds readychanges <- handleAdds st changechan transferqueue dstatus changes if shouldCommit time readychanges then do + debug thisThread + [ "committing" + , show (length readychanges) + , "changes" + ] void $ tryIO $ runThreadState st commitStaged recordCommit commitchan (Commit time) - else refillChanges changechan readychanges - else refillChanges changechan changes + else refill readychanges + else refill changes + where + refill cs = do + debug thisThread + [ "delaying commit of" + , show (length cs) + , "changes" + ] + refillChanges changechan cs + commitStaged :: Annex () commitStaged = do diff --git a/Assistant/Threads/Merger.hs b/Assistant/Threads/Merger.hs index c7da86a8d3..10ea34692b 100644 --- a/Assistant/Threads/Merger.hs +++ b/Assistant/Threads/Merger.hs @@ -5,9 +5,12 @@ - Licensed under the GNU GPL version 3 or higher. -} -module Assistant.Threads.Merger where +module Assistant.Threads.Merger ( + mergeThread, + manualPull, +) where -import Common.Annex +import Assistant.Common import Assistant.ThreadedMonad import Utility.DirWatcher import Utility.Types.DirWatcher @@ -19,6 +22,9 @@ import qualified Git.Branch import qualified Command.Sync import qualified Remote +thisThread :: ThreadName +thisThread = "Merger" + {- This thread watches for changes to .git/refs/heads/synced/*, - which indicate incoming pushes. It merges those pushes into the - currently checked out branch. -} @@ -33,6 +39,7 @@ mergeThread st = do , errHook = hook onErr } void $ watchDir dir (const False) hooks id + debug thisThread ["watching", dir] type Handler = Git.Repo -> FilePath -> Maybe FileStatus -> IO () @@ -68,7 +75,11 @@ onAdd g file _ let changedbranch = Git.Ref $ "refs" "heads" takeFileName file current <- Git.Branch.current g - when (Just changedbranch == current) $ + when (Just changedbranch == current) $ do + liftIO $ debug thisThread + [ "merging changes into" + , show current + ] void $ mergeBranch changedbranch g mergeBranch :: Git.Ref -> Git.Repo -> IO Bool diff --git a/Assistant/Threads/MountWatcher.hs b/Assistant/Threads/MountWatcher.hs index 8636533517..52614c32a4 100644 --- a/Assistant/Threads/MountWatcher.hs +++ b/Assistant/Threads/MountWatcher.hs @@ -10,7 +10,7 @@ module Assistant.Threads.MountWatcher where -import Common.Annex +import Assistant.Common import Assistant.ThreadedMonad import Assistant.DaemonStatus import Utility.ThreadScheduler @@ -19,7 +19,6 @@ import Utility.Mounts import Control.Concurrent import qualified Control.Exception as E import qualified Data.Set as S -import System.Log.Logger #if WITH_DBUS import DBus.Client @@ -29,6 +28,9 @@ import Data.Word (Word32) #warning Building without dbus support; will use mtab polling #endif +thisThread :: ThreadName +thisThread = "MountWatcher" + mountWatcherThread :: ThreadState -> DaemonStatusHandle -> IO () mountWatcherThread st handle = #if WITH_DBUS @@ -89,7 +91,7 @@ checkMountMonitor client = do if null running then startOneService client startableservices else do - myDebug [ "Using running DBUS service" + debug thisThread [ "Using running DBUS service" , Prelude.head running , "to monitor mount events." ] @@ -107,7 +109,7 @@ startOneService client (x:xs) = do [toVariant x, toVariant (0 :: Word32)] ifM (elem x <$> listServiceNames client) ( do - myDebug [ "Started DBUS service" + debug thisThread [ "Started DBUS service" , x , "to monitor mount events." ] @@ -145,7 +147,7 @@ handleMounts st handle wasmounted nowmounted = mapM_ (handleMount st handle) $ handleMount :: ThreadState -> DaemonStatusHandle -> Mntent -> IO () handleMount st handle mntent = do - myDebug ["detected mount of", mnt_dir mntent] + debug thisThread ["detected mount of", mnt_dir mntent] type MountPoints = S.Set Mntent @@ -156,6 +158,3 @@ currentMountPoints = S.fromList <$> getMounts {- Finds new mount points, given an old and a new set. -} newMountPoints :: MountPoints -> MountPoints -> MountPoints newMountPoints old new = S.difference new old - -myDebug :: [String] -> IO () -myDebug ms = debugM "MountWatcher" $ unwords ("MountWatcher:":ms) diff --git a/Assistant/Threads/Pusher.hs b/Assistant/Threads/Pusher.hs index 6d6836120e..e5191109cb 100644 --- a/Assistant/Threads/Pusher.hs +++ b/Assistant/Threads/Pusher.hs @@ -7,7 +7,7 @@ module Assistant.Threads.Pusher where -import Common.Annex +import Assistant.Common import Assistant.Commits import Assistant.Pushes import Assistant.DaemonStatus @@ -20,6 +20,9 @@ import Utility.Parallel import Data.Time.Clock import qualified Data.Map as M +thisThread :: ThreadName +thisThread = "Pusher" + {- This thread retries pushes that failed before. -} pushRetryThread :: ThreadState -> FailedPushMap -> IO () pushRetryThread st pushmap = runEvery (Seconds halfhour) $ do @@ -27,6 +30,11 @@ pushRetryThread st pushmap = runEvery (Seconds halfhour) $ do -- pushes to retry. topush <- getFailedPushesBefore pushmap (fromIntegral halfhour) unless (null topush) $ do + debug thisThread + [ "retrying" + , show (length topush) + , "failed pushes" + ] now <- getCurrentTime pushToRemotes now st pushmap topush where @@ -46,7 +54,13 @@ pushThread st daemonstatus commitchan pushmap = do remotes <- runThreadState st $ knownRemotes <$> getDaemonStatus daemonstatus pushToRemotes now st pushmap remotes - else refillCommits commitchan commits + else do + debug thisThread + [ "delaying push of" + , show (length commits) + , "commits" + ] + refillCommits commitchan commits {- Decide if now is a good time to push to remotes. - @@ -71,11 +85,20 @@ pushToRemotes now st pushmap remotes = do go True branch g remotes where go shouldretry branch g rs = do + debug thisThread + [ "pushing to" + , show rs + ] Command.Sync.updateBranch (Command.Sync.syncBranch branch) g (succeeded, failed) <- inParallel (push g branch) rs changeFailedPushMap pushmap $ \m -> M.union (makemap failed) $ M.difference m (makemap succeeded) + unless (null failed) $ + debug thisThread + [ "failed to push to" + , show failed + ] unless (null failed || not shouldretry) $ retry branch g failed @@ -86,5 +109,6 @@ pushToRemotes now st pushmap remotes = do ( exitSuccess, exitFailure) retry branch g rs = do + debug thisThread [ "trying manual pull to resolve failed pushes" ] runThreadState st $ manualPull branch rs go False branch g rs diff --git a/Assistant/Threads/SanityChecker.hs b/Assistant/Threads/SanityChecker.hs index c5b99863e3..09aee0797c 100644 --- a/Assistant/Threads/SanityChecker.hs +++ b/Assistant/Threads/SanityChecker.hs @@ -9,22 +9,27 @@ module Assistant.Threads.SanityChecker ( sanityCheckerThread ) where -import Common.Annex -import qualified Git.LsFiles +import Assistant.Common import Assistant.DaemonStatus import Assistant.ThreadedMonad import Assistant.Changes import Assistant.TransferQueue +import qualified Git.LsFiles import Utility.ThreadScheduler import qualified Assistant.Threads.Watcher as Watcher import Data.Time.Clock.POSIX +thisThread :: ThreadName +thisThread = "SanityChecker" + {- This thread wakes up occasionally to make sure the tree is in good shape. -} sanityCheckerThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> ChangeChan -> IO () sanityCheckerThread st status transferqueue changechan = forever $ do waitForNextCheck st status + debug thisThread ["starting sanity check"] + runThreadState st $ modifyDaemonStatus_ status $ \s -> s { sanityCheckRunning = True } @@ -38,6 +43,9 @@ sanityCheckerThread st status transferqueue changechan = forever $ do { sanityCheckRunning = False , lastSanityCheck = Just now } + + debug thisThread ["sanity check complete"] + {- Only run one check per day, from the time of the last check. -} waitForNextCheck :: ThreadState -> DaemonStatusHandle -> IO () @@ -80,5 +88,6 @@ check st status transferqueue changechan = do insanity m = runThreadState st $ warning m addsymlink file s = do insanity $ "found unstaged symlink: " ++ file - Watcher.runHandler st status transferqueue changechan + Watcher.runHandler thisThread st status + transferqueue changechan Watcher.onAddSymlink file s diff --git a/Assistant/Threads/TransferWatcher.hs b/Assistant/Threads/TransferWatcher.hs index 364ce04689..be520aaf93 100644 --- a/Assistant/Threads/TransferWatcher.hs +++ b/Assistant/Threads/TransferWatcher.hs @@ -7,7 +7,7 @@ module Assistant.Threads.TransferWatcher where -import Common.Annex +import Assistant.Common import Assistant.ThreadedMonad import Assistant.DaemonStatus import Logs.Transfer @@ -16,6 +16,9 @@ import Utility.Types.DirWatcher import Data.Map as M +thisThread :: ThreadName +thisThread = "TransferWatcher" + {- This thread watches for changes to the gitAnnexTransferDir, - and updates the DaemonStatus's map of ongoing transfers. -} transferWatcherThread :: ThreadState -> DaemonStatusHandle -> IO () @@ -30,6 +33,7 @@ transferWatcherThread st dstatus = do , errHook = hook onErr } void $ watchDir dir (const False) hooks id + debug thisThread ["watching for transfers"] type Handler = ThreadState -> DaemonStatusHandle -> FilePath -> Maybe FileStatus -> IO () @@ -51,11 +55,17 @@ onErr _ _ msg _ = error msg onAdd :: Handler onAdd st dstatus file _ = case parseTransferFile file of Nothing -> noop - Just t -> runThreadState st $ go t =<< checkTransfer t + Just t -> do + runThreadState st $ go t =<< checkTransfer t where go _ Nothing = noop -- transfer already finished - go t (Just info) = adjustTransfers dstatus $ - M.insertWith' merge t info + go t (Just info) = do + liftIO $ debug thisThread + [ "transfer starting:" + , show t + ] + adjustTransfers dstatus $ + M.insertWith' merge t info -- preseve transferTid, which is not written to disk merge new old = new { transferTid = transferTid old } @@ -63,4 +73,9 @@ onAdd st dstatus file _ = case parseTransferFile file of onDel :: Handler onDel st dstatus file _ = case parseTransferFile file of Nothing -> noop - Just t -> void $ runThreadState st $ removeTransfer dstatus t + Just t -> do + debug thisThread + [ "transfer finishing:" + , show t + ] + void $ runThreadState st $ removeTransfer dstatus t diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs index c439d8b7ed..4ee5290e1c 100644 --- a/Assistant/Threads/Transferrer.hs +++ b/Assistant/Threads/Transferrer.hs @@ -7,7 +7,7 @@ module Assistant.Threads.Transferrer where -import Common.Annex +import Assistant.Common import Assistant.ThreadedMonad import Assistant.DaemonStatus import Assistant.TransferQueue @@ -22,6 +22,9 @@ import Data.Time.Clock.POSIX import Data.Time.Clock import qualified Data.Map as M +thisThread :: ThreadName +thisThread = "Transferrer" + {- For now only one transfer is run at a time. -} maxTransfers :: Int maxTransfers = 1 @@ -32,8 +35,12 @@ transfererThread st dstatus transferqueue slots = go where go = do (t, info) <- getNextTransfer transferqueue - whenM (runThreadState st $ shouldTransfer dstatus t info) $ - runTransfer st dstatus slots t info + ifM (runThreadState st $ shouldTransfer dstatus t info) + ( do + debug thisThread [ "Transferring:" , show t ] + runTransfer st dstatus slots t info + , debug thisThread [ "Skipping unnecessary transfer:" , show t ] + ) go {- Checks if the requested transfer is already running, or diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs index ae4fafb78f..617e6d77c5 100644 --- a/Assistant/Threads/Watcher.hs +++ b/Assistant/Threads/Watcher.hs @@ -5,9 +5,16 @@ - Licensed under the GNU GPL version 3 or higher. -} -module Assistant.Threads.Watcher where +module Assistant.Threads.Watcher ( + watchThread, + checkCanWatch, + needLsof, + stageSymlink, + onAddSymlink, + runHandler, +) where -import Common.Annex +import Assistant.Common import Assistant.ThreadedMonad import Assistant.DaemonStatus import Assistant.Changes @@ -30,6 +37,9 @@ import Git.Types import Data.Bits.Utils import qualified Data.ByteString.Lazy as L +thisThread :: ThreadName +thisThread = "Watcher" + checkCanWatch :: Annex () checkCanWatch | canWatch = @@ -46,10 +56,12 @@ needLsof = error $ unlines ] watchThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> ChangeChan -> IO () -watchThread st dstatus transferqueue changechan = void $ watchDir "." ignored hooks startup +watchThread st dstatus transferqueue changechan = do + void $ watchDir "." ignored hooks startup + debug thisThread [ "watching", "."] where startup = statupScan st dstatus - hook a = Just $ runHandler st dstatus transferqueue changechan a + hook a = Just $ runHandler thisThread st dstatus transferqueue changechan a hooks = WatchHooks { addHook = hook onAdd , delHook = hook onDel @@ -82,22 +94,22 @@ ignored = ig . takeFileName ig ".gitattributes" = True ig _ = False -type Handler = FilePath -> Maybe FileStatus -> DaemonStatusHandle -> TransferQueue -> Annex (Maybe Change) +type Handler = ThreadName -> FilePath -> Maybe FileStatus -> DaemonStatusHandle -> TransferQueue -> Annex (Maybe Change) {- Runs an action handler, inside the Annex monad, and if there was a - change, adds it to the ChangeChan. - - Exceptions are ignored, otherwise a whole watcher thread could be crashed. -} -runHandler :: ThreadState -> DaemonStatusHandle -> TransferQueue -> ChangeChan -> Handler -> FilePath -> Maybe FileStatus -> IO () -runHandler st dstatus transferqueue changechan handler file filestatus = void $ do +runHandler :: ThreadName -> ThreadState -> DaemonStatusHandle -> TransferQueue -> ChangeChan -> Handler -> FilePath -> Maybe FileStatus -> IO () +runHandler threadname st dstatus transferqueue changechan handler file filestatus = void $ do r <- tryIO go case r of Left e -> print e Right Nothing -> noop Right (Just change) -> recordChange changechan change where - go = runThreadState st $ handler file filestatus dstatus transferqueue + go = runThreadState st $ handler threadname file filestatus dstatus transferqueue {- During initial directory scan, this will be run for any regular files - that are already checked into git. We don't want to turn those into @@ -118,7 +130,7 @@ runHandler st dstatus transferqueue changechan handler file filestatus = void $ - the add. -} onAdd :: Handler -onAdd file filestatus dstatus _ +onAdd threadname file filestatus dstatus _ | maybe False isRegularFile filestatus = do ifM (scanComplete <$> getDaemonStatus dstatus) ( go @@ -129,14 +141,16 @@ onAdd file filestatus dstatus _ ) | otherwise = noChange where - go = pendingAddChange =<< Command.Add.lockDown file + go = do + liftIO $ debug threadname ["file added", file] + pendingAddChange =<< Command.Add.lockDown file {- A symlink might be an arbitrary symlink, which is just added. - Or, if it is a git-annex symlink, ensure it points to the content - before adding it. -} onAddSymlink :: Handler -onAddSymlink file filestatus dstatus transferqueue = go =<< Backend.lookupFile file +onAddSymlink threadname file filestatus dstatus transferqueue = go =<< Backend.lookupFile file where go (Just (key, _)) = do link <- calcGitLink file key @@ -146,6 +160,7 @@ onAddSymlink file filestatus dstatus transferqueue = go =<< Backend.lookupFile f checkcontent key s ensurestaged link s , do + liftIO $ debug threadname ["fix symlink", file] liftIO $ removeFile file liftIO $ createSymbolicLink link file addlink link @@ -175,6 +190,7 @@ onAddSymlink file filestatus dstatus transferqueue = go =<< Backend.lookupFile f {- For speed, tries to reuse the existing blob for - the symlink target. -} addlink link = do + liftIO $ debug threadname ["add symlink", file] v <- catObjectDetails $ Ref $ ':':file case v of Just (currlink, sha) @@ -195,7 +211,8 @@ onAddSymlink file filestatus dstatus transferqueue = go =<< Backend.lookupFile f | otherwise = noop onDel :: Handler -onDel file _ _dstatus _ = do +onDel threadname file _ _dstatus _ = do + liftIO $ debug threadname ["file deleted", file] Annex.Queue.addUpdateIndex =<< inRepo (Git.UpdateIndex.unstageFile file) madeChange file RmChange @@ -208,14 +225,15 @@ onDel file _ _dstatus _ = do - command to get the recursive list of files in the directory, so rm is - just as good. -} onDelDir :: Handler -onDelDir dir _ _dstatus _ = do +onDelDir threadname dir _ _dstatus _ = do + liftIO $ debug threadname ["directory deleted", dir] Annex.Queue.addCommand "rm" [Params "--quiet -r --cached --ignore-unmatch --"] [dir] madeChange dir RmDirChange {- Called when there's an error with inotify. -} onErr :: Handler -onErr msg _ _dstatus _ = do +onErr _ msg _ _dstatus _ = do warning msg return Nothing diff --git a/Option.hs b/Option.hs index 967cd3e07b..ff70fb6859 100644 --- a/Option.hs +++ b/Option.hs @@ -17,6 +17,9 @@ module Option ( import System.Console.GetOpt import System.Log.Logger +import System.Log.Formatter +import System.Log.Handler (setFormatter, LogHandler) +import System.Log.Handler.Simple import Common.Annex import qualified Annex @@ -48,8 +51,13 @@ common = setfast v = Annex.changeState $ \s -> s { Annex.fast = v } setauto v = Annex.changeState $ \s -> s { Annex.auto = v } setforcebackend v = Annex.changeState $ \s -> s { Annex.forcebackend = Just v } - setdebug = liftIO $ updateGlobalLogger rootLoggerName $ - setLevel DEBUG + setdebug = liftIO $ do + s <- simpledebug + updateGlobalLogger rootLoggerName + (setLevel DEBUG . setHandlers [s]) + simpledebug = setFormatter + <$> streamHandler stderr DEBUG + <*> pure (simpleLogFormatter "[$time] $msg") matcher :: [Option] matcher = From 4ec9244f1af85b95d014103d93de913026b20fe3 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sun, 22 Jul 2012 13:48:50 -0400 Subject: [PATCH 090/331] add a path field to remotes Also broke out some helper functions around constructing remotes, to be used later. --- Remote/Bup.hs | 33 +++++++++++---------- Remote/Directory.hs | 1 + Remote/Git.hs | 70 +++++++++++++++++++++++++------------------- Remote/Hook.hs | 1 + Remote/List.hs | 14 +++++---- Remote/Rsync.hs | 33 +++++++++++---------- Remote/S3.hs | 1 + Remote/Web.hs | 1 + Types/Remote.hs | 2 ++ Utility/RsyncFile.hs | 6 ++++ 10 files changed, 97 insertions(+), 65 deletions(-) diff --git a/Remote/Bup.hs b/Remote/Bup.hs index 8a2c1afefe..83739a3e15 100644 --- a/Remote/Bup.hs +++ b/Remote/Bup.hs @@ -46,21 +46,24 @@ gen r u c = do return $ encryptableRemote c (storeEncrypted r buprepo) (retrieveEncrypted buprepo) - Remote { - uuid = u', - cost = cst, - name = Git.repoDescribe r, - storeKey = store r buprepo, - retrieveKeyFile = retrieve buprepo, - retrieveKeyFileCheap = retrieveCheap buprepo, - removeKey = remove, - hasKey = checkPresent r bupr', - hasKeyCheap = bupLocal buprepo, - whereisKey = Nothing, - config = c, - repo = r, - remotetype = remote - } + Remote + { uuid = u' + , cost = cst + , name = Git.repoDescribe r + , storeKey = store r buprepo + , retrieveKeyFile = retrieve buprepo + , retrieveKeyFileCheap = retrieveCheap buprepo + , removeKey = remove + , hasKey = checkPresent r bupr' + , hasKeyCheap = bupLocal buprepo + , whereisKey = Nothing + , config = c + , repo = r + , path = if bupLocal buprepo && not (null buprepo) + then Just buprepo + else Nothing + , remotetype = remote + } bupSetup :: UUID -> RemoteConfig -> Annex RemoteConfig bupSetup u c = do diff --git a/Remote/Directory.hs b/Remote/Directory.hs index 6b158730e8..1b75b937f7 100644 --- a/Remote/Directory.hs +++ b/Remote/Directory.hs @@ -53,6 +53,7 @@ gen r u c = do whereisKey = Nothing, config = Nothing, repo = r, + path = Just dir, remotetype = remote } where diff --git a/Remote/Git.hs b/Remote/Git.hs index 3412de89b4..f42a1d5366 100644 --- a/Remote/Git.hs +++ b/Remote/Git.hs @@ -5,7 +5,11 @@ - Licensed under the GNU GPL version 3 or higher. -} -module Remote.Git (remote, repoAvail) where +module Remote.Git ( + remote, + configRead, + repoAvail, +) where import qualified Data.Map as M import Control.Exception.Extensible @@ -45,7 +49,7 @@ list :: Annex [Git.Repo] list = do c <- fromRepo Git.config rs <- mapM (tweakurl c) =<< fromRepo Git.remotes - mapM configread rs + mapM configRead rs where annexurl n = "remote." ++ n ++ ".annexurl" tweakurl c r = do @@ -55,19 +59,21 @@ list = do Just url -> inRepo $ \g -> Git.Construct.remoteNamed n $ Git.Construct.fromRemoteLocation url g - {- It's assumed to be cheap to read the config of non-URL - - remotes, so this is done each time git-annex is run - - in a way that uses remotes. - - Conversely, the config of an URL remote is only read - - when there is no cached UUID value. -} - configread r = do - notignored <- repoNotIgnored r - u <- getRepoUUID r - case (repoCheap r, notignored, u) of - (_, False, _) -> return r - (True, _, _) -> tryGitConfigRead r - (False, _, NoUUID) -> tryGitConfigRead r - _ -> return r + +{- It's assumed to be cheap to read the config of non-URL remotes, so this is + - done each time git-annex is run in a way that uses remotes. + - + - Conversely, the config of an URL remote is only read when there is no + - cached UUID value. -} +configRead :: Git.Repo -> Annex Git.Repo +configRead r = do + notignored <- repoNotIgnored r + u <- getRepoUUID r + case (repoCheap r, notignored, u) of + (_, False, _) -> return r + (True, _, _) -> tryGitConfigRead r + (False, _, NoUUID) -> tryGitConfigRead r + _ -> return r repoCheap :: Git.Repo -> Bool repoCheap = not . Git.repoIsUrl @@ -76,21 +82,25 @@ gen :: Git.Repo -> UUID -> Maybe RemoteConfig -> Annex Remote gen r u _ = new <$> remoteCost r defcst where defcst = if repoCheap r then cheapRemoteCost else expensiveRemoteCost - new cst = Remote { - uuid = u, - cost = cst, - name = Git.repoDescribe r, - storeKey = copyToRemote r, - retrieveKeyFile = copyFromRemote r, - retrieveKeyFileCheap = copyFromRemoteCheap r, - removeKey = dropKey r, - hasKey = inAnnex r, - hasKeyCheap = repoCheap r, - whereisKey = Nothing, - config = Nothing, - repo = r, - remotetype = remote - } + new cst = Remote + { uuid = u + , cost = cst + , name = Git.repoDescribe r + , storeKey = copyToRemote r + , retrieveKeyFile = copyFromRemote r + , retrieveKeyFileCheap = copyFromRemoteCheap r + , removeKey = dropKey r + , hasKey = inAnnex r + , hasKeyCheap = repoCheap r + , whereisKey = Nothing + , config = Nothing + , path = if Git.repoIsLocal r || Git.repoIsLocalUnknown r + then Just $ Git.repoPath r + else Nothing + , repo = r + , remotetype = remote + } + {- Checks relatively inexpensively if a repository is available for use. -} repoAvail :: Git.Repo -> Annex Bool diff --git a/Remote/Hook.hs b/Remote/Hook.hs index cad6e2fc94..9af851d149 100644 --- a/Remote/Hook.hs +++ b/Remote/Hook.hs @@ -47,6 +47,7 @@ gen r u c = do hasKeyCheap = False, whereisKey = Nothing, config = Nothing, + path = Nothing, repo = r, remotetype = remote } diff --git a/Remote/List.hs b/Remote/List.hs index 14a1771b48..4127cf24b0 100644 --- a/Remote/List.hs +++ b/Remote/List.hs @@ -2,7 +2,7 @@ {- git-annex remote list - - - Copyright 2011 Joey Hess + - Copyright 2011,2012 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} @@ -18,6 +18,7 @@ import Types.Remote import Annex.UUID import Config import Remote.Helper.Hooks +import qualified Git import qualified Remote.Git #ifdef WITH_S3 @@ -55,10 +56,13 @@ remoteList = do return rs' else return rs where - process m t = enumerate t >>= mapM (gen m t) - gen m t r = do - u <- getRepoUUID r - addHooks =<< generate t r u (M.lookup u m) + process m t = enumerate t >>= mapM (remoteGen m t) + +{- Generates a Remote. -} +remoteGen :: (M.Map UUID RemoteConfig) -> RemoteType -> Git.Repo -> Annex Remote +remoteGen m t r = do + u <- getRepoUUID r + addHooks =<< generate t r u (M.lookup u m) {- All remotes that are not ignored. -} enabledRemoteList :: Annex [Remote] diff --git a/Remote/Rsync.hs b/Remote/Rsync.hs index ee516a8a59..1ed73e119f 100644 --- a/Remote/Rsync.hs +++ b/Remote/Rsync.hs @@ -45,21 +45,24 @@ gen r u c = do return $ encryptableRemote c (storeEncrypted o) (retrieveEncrypted o) - Remote { - uuid = u, - cost = cst, - name = Git.repoDescribe r, - storeKey = store o, - retrieveKeyFile = retrieve o, - retrieveKeyFileCheap = retrieveCheap o, - removeKey = remove o, - hasKey = checkPresent r o, - hasKeyCheap = False, - whereisKey = Nothing, - config = Nothing, - repo = r, - remotetype = remote - } + Remote + { uuid = u + , cost = cst + , name = Git.repoDescribe r + , storeKey = store o + , retrieveKeyFile = retrieve o + , retrieveKeyFileCheap = retrieveCheap o + , removeKey = remove o + , hasKey = checkPresent r o + , hasKeyCheap = False + , whereisKey = Nothing + , config = Nothing + , repo = r + , path = if rsyncUrlIsPath $ rsyncUrl o + then Just $ rsyncUrl o + else Nothing + , remotetype = remote + } genRsyncOpts :: Git.Repo -> Maybe RemoteConfig -> Annex RsyncOpts genRsyncOpts r c = do diff --git a/Remote/S3.hs b/Remote/S3.hs index dca08fff8b..6e249ec4d5 100644 --- a/Remote/S3.hs +++ b/Remote/S3.hs @@ -60,6 +60,7 @@ gen' r u c cst = whereisKey = Nothing, config = c, repo = r, + path = Nothing, remotetype = remote } diff --git a/Remote/Web.hs b/Remote/Web.hs index 2516240ab3..02a2b5ab44 100644 --- a/Remote/Web.hs +++ b/Remote/Web.hs @@ -47,6 +47,7 @@ gen r _ _ = hasKeyCheap = False, whereisKey = Just getUrls, config = Nothing, + path = Nothing, repo = r, remotetype = remote } diff --git a/Types/Remote.hs b/Types/Remote.hs index c7628165c7..814be9febd 100644 --- a/Types/Remote.hs +++ b/Types/Remote.hs @@ -64,6 +64,8 @@ data RemoteA a = Remote { config :: Maybe RemoteConfig, -- git configuration for the remote repo :: Git.Repo, + -- a Remote can be assocated with a specific filesystem path + path :: Maybe FilePath, -- the type of the remote remotetype :: RemoteTypeA a } diff --git a/Utility/RsyncFile.hs b/Utility/RsyncFile.hs index 075e91d239..5a9a256a98 100644 --- a/Utility/RsyncFile.hs +++ b/Utility/RsyncFile.hs @@ -61,3 +61,9 @@ rsyncUrlIsShell s | c == '/' = False -- got to directory with no colon | c == ':' = not $ ":" `isPrefixOf` cs | otherwise = go cs + +{- Checks if a rsync url is really just a local path. -} +rsyncUrlIsPath :: String -> Bool +rsyncUrlIsPath s + | rsyncUrlIsShell s = False + | otherwise = ':' `notElem` s From e4f714d1be7b4341d08e10f1305b24c25da6d70e Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sun, 22 Jul 2012 15:06:18 -0400 Subject: [PATCH 091/331] pull from newly mounted git remotes --- Assistant/DaemonStatus.hs | 8 ++++ Assistant/Threads/MountWatcher.hs | 70 ++++++++++++++++++++++++++----- 2 files changed, 68 insertions(+), 10 deletions(-) diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs index 64c441ceee..88306a6363 100644 --- a/Assistant/DaemonStatus.hs +++ b/Assistant/DaemonStatus.hs @@ -60,6 +60,14 @@ modifyDaemonStatus_ handle a = liftIO $ modifyMVar_ handle (return . a) modifyDaemonStatus :: DaemonStatusHandle -> (DaemonStatus -> (DaemonStatus, b)) -> Annex b modifyDaemonStatus handle a = liftIO $ modifyMVar handle (return . a) +{- Updates the cached ordered list of remotes from the list in Annex + - state. -} +updateKnownRemotes :: DaemonStatusHandle -> Annex () +updateKnownRemotes dstatus = do + remotes <- Command.Sync.syncRemotes [] + modifyDaemonStatus_ dstatus $ + \s -> s { knownRemotes = remotes } + {- Load any previous daemon status file, and store it in the MVar for this - process to use as its DaemonStatus. Also gets current transfer status. -} startDaemonStatus :: Annex DaemonStatusHandle diff --git a/Assistant/Threads/MountWatcher.hs b/Assistant/Threads/MountWatcher.hs index 52614c32a4..f32e043147 100644 --- a/Assistant/Threads/MountWatcher.hs +++ b/Assistant/Threads/MountWatcher.hs @@ -13,8 +13,16 @@ module Assistant.Threads.MountWatcher where import Assistant.Common import Assistant.ThreadedMonad import Assistant.DaemonStatus +import qualified Annex +import qualified Git import Utility.ThreadScheduler import Utility.Mounts +import Remote.List +import qualified Types.Remote as Remote +import qualified Remote.Git +import qualified Command.Sync +import Assistant.Threads.Merger +import Logs.Remote import Control.Concurrent import qualified Control.Exception as E @@ -42,7 +50,7 @@ mountWatcherThread st handle = #if WITH_DBUS dbusThread :: ThreadState -> DaemonStatusHandle -> IO () -dbusThread st handle = E.catch (go =<< connectSession) onerr +dbusThread st dstatus = E.catch (go =<< connectSession) onerr where go client = ifM (checkMountMonitor client) ( do @@ -55,7 +63,7 @@ dbusThread st handle = E.catch (go =<< connectSession) onerr listen client matcher $ \_event -> do nowmounted <- currentMountPoints wasmounted <- swapMVar mvar nowmounted - handleMounts st handle wasmounted nowmounted + handleMounts st dstatus wasmounted nowmounted , do runThreadState st $ warning "No known volume monitor available through dbus; falling back to mtab polling" @@ -66,7 +74,7 @@ dbusThread st handle = E.catch (go =<< connectSession) onerr runThreadState st $ warning $ "Failed to use dbus; falling back to mtab polling (" ++ show e ++ ")" pollinstead - pollinstead = pollingThread st handle + pollinstead = pollingThread st dstatus type ServiceName = String @@ -133,28 +141,70 @@ mountAdded = [gvfs, kde] #endif pollingThread :: ThreadState -> DaemonStatusHandle -> IO () -pollingThread st handle = go =<< currentMountPoints +pollingThread st dstatus = go =<< currentMountPoints where go wasmounted = do threadDelaySeconds (Seconds 10) nowmounted <- currentMountPoints - handleMounts st handle wasmounted nowmounted + handleMounts st dstatus wasmounted nowmounted go nowmounted handleMounts :: ThreadState -> DaemonStatusHandle -> MountPoints -> MountPoints -> IO () -handleMounts st handle wasmounted nowmounted = mapM_ (handleMount st handle) $ +handleMounts st dstatus wasmounted nowmounted = mapM_ (handleMount st dstatus) $ S.toList $ newMountPoints wasmounted nowmounted handleMount :: ThreadState -> DaemonStatusHandle -> Mntent -> IO () -handleMount st handle mntent = do - debug thisThread ["detected mount of", mnt_dir mntent] +handleMount st dstatus mntent = do + debug thisThread ["detected mount of", mnt_dir mntent] + rs <- remotesUnder st dstatus mntent + unless (null rs) $ do + branch <- runThreadState st $ Command.Sync.currentBranch + debug thisThread ["pulling from", show rs] + runThreadState st $ manualPull branch rs + -- TODO queue transfers for new files in both directions + where + +{- Finds remotes located underneath the mount point. + - + - Updates state to include the remotes. + - + - The config of git remotes is re-read, as it may not have been available + - at startup time, or may have changed (it could even be a different + - repository at the same remote location..) + -} +remotesUnder :: ThreadState -> DaemonStatusHandle -> Mntent -> IO [Remote] +remotesUnder st dstatus mntent = runThreadState st $ do + repotop <- fromRepo Git.repoPath + rs <- remoteList + pairs <- mapM (checkremote repotop) rs + let (waschanged, rs') = unzip pairs + when (any id waschanged) $ do + Annex.changeState $ \s -> s { Annex.remotes = rs' } + updateKnownRemotes dstatus + return $ map snd $ filter fst pairs + where + checkremote repotop r = case Remote.path r of + Just p | under mntent (absPathFrom repotop p) -> + (,) <$> pure True <*> updateremote r + _ -> return (False, r) + updateremote r = do + liftIO $ debug thisThread ["updating", show r] + m <- readRemoteLog + repo <- updaterepo $ Remote.repo r + remoteGen m (Remote.remotetype r) repo + updaterepo repo + | Git.repoIsLocal repo || Git.repoIsLocalUnknown repo = + Remote.Git.configRead repo + | otherwise = return repo type MountPoints = S.Set Mntent -{- Reads mtab, getting the current set of mount points. -} currentMountPoints :: IO MountPoints currentMountPoints = S.fromList <$> getMounts -{- Finds new mount points, given an old and a new set. -} newMountPoints :: MountPoints -> MountPoints -> MountPoints newMountPoints old new = S.difference new old + +{- Checks if a mount point contains a path. The path must be absolute. -} +under :: Mntent -> FilePath -> Bool +under = dirContains . mnt_dir From 26e4e65307436e4cc9a2db448141652b79d0f582 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sun, 22 Jul 2012 15:09:40 -0400 Subject: [PATCH 092/331] filter out special remotes when pulling --- Assistant/Threads/MountWatcher.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/Assistant/Threads/MountWatcher.hs b/Assistant/Threads/MountWatcher.hs index f32e043147..bfdfe0ebbd 100644 --- a/Assistant/Threads/MountWatcher.hs +++ b/Assistant/Threads/MountWatcher.hs @@ -159,8 +159,9 @@ handleMount st dstatus mntent = do rs <- remotesUnder st dstatus mntent unless (null rs) $ do branch <- runThreadState st $ Command.Sync.currentBranch - debug thisThread ["pulling from", show rs] - runThreadState st $ manualPull branch rs + let pullrs = filter Git.repoIsLocal rs + debug thisThread ["pulling from", show pullrs] + runThreadState st $ manualPull branch pullrs -- TODO queue transfers for new files in both directions where From 522f568450a005ae81b24f63bb37e75320b51219 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sun, 22 Jul 2012 23:16:56 -0400 Subject: [PATCH 093/331] add TransferScanner thread Efficiently finding transfers that need to be done to get two repos back in sync seems like an interesting problem. --- Assistant.hs | 22 ++++++++++---- Assistant/ScanRemotes.hs | 41 +++++++++++++++++++++++++ Assistant/Threads/MountWatcher.hs | 45 +++++++++++++++------------- Assistant/Threads/Pusher.hs | 25 +++++++++------- Assistant/Threads/TransferScanner.hs | 34 +++++++++++++++++++++ Assistant/TransferQueue.hs | 14 ++++----- 6 files changed, 138 insertions(+), 43 deletions(-) create mode 100644 Assistant/ScanRemotes.hs create mode 100644 Assistant/Threads/TransferScanner.hs diff --git a/Assistant.hs b/Assistant.hs index 4bb1ed4cea..0049d31777 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -36,8 +36,7 @@ - inotify threads associated with it, too.) - Thread 9: transfer watcher - Watches for transfer information files being created and removed, - - and maintains the DaemonStatus currentTransfers map and the - - TransferSlots QSemN. + - and maintains the DaemonStatus currentTransfers map. - (This uses inotify on .git/annex/transfer/, so there are - additional inotify threads associated with it, too.) - Thread 10: transferrer @@ -49,8 +48,14 @@ - Thread 13: mount watcher - Either uses dbus to watch for drive mount events, or, when - there's no dbus, polls to find newly mounted filesystems. - - Once a filesystem that contains a remote is mounted, syncs - - with it. + - Once a filesystem that contains a remote is mounted, updates + - state about that remote, pulls from it, and queues a push to it, + - as well as an update, and queues it onto the + - ConnectedRemoteChan + - Thread 14: transfer scanner + - Does potentially expensive checks to find data that needs to be + - transferred from or to remotes, and queues Transfers. + - Uses the ScanRemotes map. - - ThreadState: (MVar) - The Annex state is stored here, which allows resuscitating the @@ -78,6 +83,9 @@ - to block until a slot is available. - This MVar should only be manipulated from inside the Annex monad, - which ensures it's accessed only after the ThreadState MVar. + - ScanRemotes (STM TMVar) + - Remotes that have been disconnected, and should be scanned + - are indicated by writing to this TMVar. -} module Assistant where @@ -88,6 +96,7 @@ import Assistant.DaemonStatus import Assistant.Changes import Assistant.Commits import Assistant.Pushes +import Assistant.ScanRemotes import Assistant.TransferQueue import Assistant.TransferSlots import Assistant.Threads.Watcher @@ -98,6 +107,7 @@ import Assistant.Threads.TransferWatcher import Assistant.Threads.Transferrer import Assistant.Threads.SanityChecker import Assistant.Threads.MountWatcher +import Assistant.Threads.TransferScanner import qualified Utility.Daemon import Utility.LogFile import Utility.ThreadScheduler @@ -124,6 +134,7 @@ startDaemon assistant foreground pushmap <- newFailedPushMap transferqueue <- newTransferQueue transferslots <- newTransferSlots + scanremotes <- newScanRemoteMap mapM_ forkIO [ commitThread st changechan commitchan transferqueue dstatus , pushThread st dstatus commitchan pushmap @@ -133,7 +144,8 @@ startDaemon assistant foreground , transfererThread st dstatus transferqueue transferslots , daemonStatusThread st dstatus , sanityCheckerThread st dstatus transferqueue changechan - , mountWatcherThread st dstatus + , mountWatcherThread st dstatus scanremotes + , transferScannerThread st scanremotes transferqueue , watchThread st dstatus transferqueue changechan ] debug "assistant" diff --git a/Assistant/ScanRemotes.hs b/Assistant/ScanRemotes.hs new file mode 100644 index 0000000000..05b2a2ca9f --- /dev/null +++ b/Assistant/ScanRemotes.hs @@ -0,0 +1,41 @@ +{- git-annex assistant remotes needing scanning + - + - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Assistant.ScanRemotes where + +import Common.Annex +import Data.Function + +import Control.Concurrent.STM +import Data.Time.Clock +import qualified Data.Map as M + +type ScanRemoteMap = TMVar (M.Map Remote UTCTime) + +{- The TMVar starts empty, and is left empty when there are no remotes + - to scan. -} +newScanRemoteMap :: IO ScanRemoteMap +newScanRemoteMap = atomically newEmptyTMVar + +{- Blocks until there is a remote that needs to be scanned. + - Processes remotes added most recently first. -} +getScanRemote :: ScanRemoteMap -> IO Remote +getScanRemote v = atomically $ do + m <- takeTMVar v + let newest = Prelude.head $ reverse $ + map fst $ sortBy (compare `on` snd) $ M.toList m + putTMVar v $ M.delete newest m + return newest + +{- Adds new remotes that need scanning to the map. -} +addScanRemotes :: ScanRemoteMap -> [Remote] -> IO () +addScanRemotes _ [] = return () +addScanRemotes v rs = do + now <- getCurrentTime + atomically $ do + m <- fromMaybe M.empty <$> tryTakeTMVar v + putTMVar v $ foldr (`M.insert` now) m rs diff --git a/Assistant/Threads/MountWatcher.hs b/Assistant/Threads/MountWatcher.hs index bfdfe0ebbd..853d96d51c 100644 --- a/Assistant/Threads/MountWatcher.hs +++ b/Assistant/Threads/MountWatcher.hs @@ -13,6 +13,8 @@ module Assistant.Threads.MountWatcher where import Assistant.Common import Assistant.ThreadedMonad import Assistant.DaemonStatus +import Assistant.ScanRemotes +import Assistant.Threads.Pusher (pushToRemotes) import qualified Annex import qualified Git import Utility.ThreadScheduler @@ -27,6 +29,7 @@ import Logs.Remote import Control.Concurrent import qualified Control.Exception as E import qualified Data.Set as S +import Data.Time.Clock #if WITH_DBUS import DBus.Client @@ -39,18 +42,18 @@ import Data.Word (Word32) thisThread :: ThreadName thisThread = "MountWatcher" -mountWatcherThread :: ThreadState -> DaemonStatusHandle -> IO () -mountWatcherThread st handle = +mountWatcherThread :: ThreadState -> DaemonStatusHandle -> ScanRemoteMap -> IO () +mountWatcherThread st handle scanremotes = #if WITH_DBUS - dbusThread st handle + dbusThread st handle scanremotes #else - pollingThread st handle + pollingThread st handle scanremotes #endif #if WITH_DBUS -dbusThread :: ThreadState -> DaemonStatusHandle -> IO () -dbusThread st dstatus = E.catch (go =<< connectSession) onerr +dbusThread :: ThreadState -> DaemonStatusHandle -> ScanRemoteMap -> IO () +dbusThread st dstatus scanremotes = E.catch (go =<< connectSession) onerr where go client = ifM (checkMountMonitor client) ( do @@ -63,7 +66,7 @@ dbusThread st dstatus = E.catch (go =<< connectSession) onerr listen client matcher $ \_event -> do nowmounted <- currentMountPoints wasmounted <- swapMVar mvar nowmounted - handleMounts st dstatus wasmounted nowmounted + handleMounts st dstatus scanremotes wasmounted nowmounted , do runThreadState st $ warning "No known volume monitor available through dbus; falling back to mtab polling" @@ -74,7 +77,7 @@ dbusThread st dstatus = E.catch (go =<< connectSession) onerr runThreadState st $ warning $ "Failed to use dbus; falling back to mtab polling (" ++ show e ++ ")" pollinstead - pollinstead = pollingThread st dstatus + pollinstead = pollingThread st dstatus scanremotes type ServiceName = String @@ -140,30 +143,32 @@ mountAdded = [gvfs, kde] #endif -pollingThread :: ThreadState -> DaemonStatusHandle -> IO () -pollingThread st dstatus = go =<< currentMountPoints +pollingThread :: ThreadState -> DaemonStatusHandle -> ScanRemoteMap -> IO () +pollingThread st dstatus scanremotes = go =<< currentMountPoints where go wasmounted = do threadDelaySeconds (Seconds 10) nowmounted <- currentMountPoints - handleMounts st dstatus wasmounted nowmounted + handleMounts st dstatus scanremotes wasmounted nowmounted go nowmounted -handleMounts :: ThreadState -> DaemonStatusHandle -> MountPoints -> MountPoints -> IO () -handleMounts st dstatus wasmounted nowmounted = mapM_ (handleMount st dstatus) $ +handleMounts :: ThreadState -> DaemonStatusHandle -> ScanRemoteMap -> MountPoints -> MountPoints -> IO () +handleMounts st dstatus scanremotes wasmounted nowmounted = mapM_ (handleMount st dstatus scanremotes) $ S.toList $ newMountPoints wasmounted nowmounted -handleMount :: ThreadState -> DaemonStatusHandle -> Mntent -> IO () -handleMount st dstatus mntent = do +handleMount :: ThreadState -> DaemonStatusHandle -> ScanRemoteMap -> Mntent -> IO () +handleMount st dstatus scanremotes mntent = do debug thisThread ["detected mount of", mnt_dir mntent] rs <- remotesUnder st dstatus mntent unless (null rs) $ do branch <- runThreadState st $ Command.Sync.currentBranch - let pullrs = filter Git.repoIsLocal rs - debug thisThread ["pulling from", show pullrs] - runThreadState st $ manualPull branch pullrs - -- TODO queue transfers for new files in both directions - where + let nonspecial = filter (Git.repoIsLocal . Remote.repo) rs + unless (null nonspecial) $ do + debug thisThread ["pulling from", show nonspecial] + runThreadState st $ manualPull branch nonspecial + now <- getCurrentTime + pushToRemotes thisThread now st Nothing nonspecial + addScanRemotes scanremotes rs {- Finds remotes located underneath the mount point. - diff --git a/Assistant/Threads/Pusher.hs b/Assistant/Threads/Pusher.hs index e5191109cb..cba53af233 100644 --- a/Assistant/Threads/Pusher.hs +++ b/Assistant/Threads/Pusher.hs @@ -1,4 +1,4 @@ -{- git-annex assistant git pushing threads +{- git-annex assistant git pushing thread - - Copyright 2012 Joey Hess - @@ -36,7 +36,7 @@ pushRetryThread st pushmap = runEvery (Seconds halfhour) $ do , "failed pushes" ] now <- getCurrentTime - pushToRemotes now st pushmap topush + pushToRemotes thisThread now st (Just pushmap) topush where halfhour = 1800 @@ -53,7 +53,7 @@ pushThread st daemonstatus commitchan pushmap = do then do remotes <- runThreadState st $ knownRemotes <$> getDaemonStatus daemonstatus - pushToRemotes now st pushmap remotes + pushToRemotes thisThread now st (Just pushmap) remotes else do debug thisThread [ "delaying push of" @@ -78,24 +78,27 @@ shouldPush _now commits - - Avoids running possibly long-duration commands in the Annex monad, so - as not to block other threads. -} -pushToRemotes :: UTCTime -> ThreadState -> FailedPushMap -> [Remote] -> IO () -pushToRemotes now st pushmap remotes = do +pushToRemotes :: ThreadName -> UTCTime -> ThreadState -> (Maybe FailedPushMap) -> [Remote] -> IO () +pushToRemotes threadname now st mpushmap remotes = do (g, branch) <- runThreadState st $ (,) <$> fromRepo id <*> Command.Sync.currentBranch go True branch g remotes where go shouldretry branch g rs = do - debug thisThread + debug threadname [ "pushing to" , show rs ] Command.Sync.updateBranch (Command.Sync.syncBranch branch) g (succeeded, failed) <- inParallel (push g branch) rs - changeFailedPushMap pushmap $ \m -> - M.union (makemap failed) $ - M.difference m (makemap succeeded) + case mpushmap of + Nothing -> noop + Just pushmap -> + changeFailedPushMap pushmap $ \m -> + M.union (makemap failed) $ + M.difference m (makemap succeeded) unless (null failed) $ - debug thisThread + debug threadname [ "failed to push to" , show failed ] @@ -109,6 +112,6 @@ pushToRemotes now st pushmap remotes = do ( exitSuccess, exitFailure) retry branch g rs = do - debug thisThread [ "trying manual pull to resolve failed pushes" ] + debug threadname [ "trying manual pull to resolve failed pushes" ] runThreadState st $ manualPull branch rs go False branch g rs diff --git a/Assistant/Threads/TransferScanner.hs b/Assistant/Threads/TransferScanner.hs new file mode 100644 index 0000000000..0a40f7ead2 --- /dev/null +++ b/Assistant/Threads/TransferScanner.hs @@ -0,0 +1,34 @@ +{- git-annex assistant thread to scan remotes to find needed transfers + - + - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Assistant.Threads.TransferScanner where + +import Assistant.Common +import Assistant.ScanRemotes +import Assistant.TransferQueue +import Assistant.ThreadedMonad +import Logs.Transfer +import Types.Remote +import Utility.ThreadScheduler + +thisThread :: ThreadName +thisThread = "TransferScanner" + +{- This thread scans remotes, to find transfers that need to be made to + - keep their data in sync. The transfers are queued with lot priority. -} +transferScannerThread :: ThreadState -> ScanRemoteMap -> TransferQueue -> IO () +transferScannerThread st scanremotes transferqueue = do + runEvery (Seconds 2) $ do + r <- getScanRemote scanremotes + needtransfer <- scan st r + forM_ needtransfer $ \(f, t) -> + queueLaterTransfer transferqueue f t + +scan :: ThreadState -> Remote -> IO [(AssociatedFile, Transfer)] +scan st r = do + debug thisThread ["scanning", show r] + return [] -- TODO diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs index b0eca96c84..f8104914c1 100644 --- a/Assistant/TransferQueue.hs +++ b/Assistant/TransferQueue.hs @@ -38,19 +38,19 @@ queueTransfers q daemonstatus k f direction = do mapM_ (\r -> queue r $ gentransfer r) =<< sufficientremotes rs where - sufficientremotes l + sufficientremotes rs -- Queue downloads from all remotes that -- have the key, with the cheapest ones first. -- More expensive ones will only be tried if -- downloading from a cheap one fails. | direction == Download = do uuids <- Remote.keyLocations k - return $ filter (\r -> uuid r `elem` uuids) l + return $ filter (\r -> uuid r `elem` uuids) rs -- TODO: Determine a smaller set of remotes that -- can be uploaded to, in order to ensure all -- remotes can access the content. Currently, -- send to every remote we can. - | otherwise = return l + | otherwise = return rs gentransfer r = Transfer { transferDirection = direction , transferKey = k @@ -60,12 +60,12 @@ queueTransfers q daemonstatus k f direction = do let info = (stubInfo f) { transferRemote = Just r } writeTChan q (t, info) -{- Adds a pending transfer to the end of the queue. -} -queueTransfer :: TransferQueue -> AssociatedFile -> Transfer -> IO () -queueTransfer q f t = void $ atomically $ +{- Adds a transfer to the end of the queue, to be processed later. -} +queueLaterTransfer :: TransferQueue -> AssociatedFile -> Transfer -> IO () +queueLaterTransfer q f t = void $ atomically $ writeTChan q (t, stubInfo f) -{- Adds a pending transfer to the start of the queue, to be processed next. -} +{- Adds a transfer to the start of the queue, to be processed next. -} queueNextTransfer :: TransferQueue -> AssociatedFile -> Transfer -> IO () queueNextTransfer q f t = void $ atomically $ unGetTChan q (t, stubInfo f) From 6107328a6b981ec8130e4154be1ebe7bc11979df Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 25 Jul 2012 12:07:30 -0400 Subject: [PATCH 094/331] avoid spawning new transfer thread until a slot becomes available --- Assistant/Threads/TransferScanner.hs | 2 +- Assistant/TransferSlots.hs | 5 +++-- 2 files changed, 4 insertions(+), 3 deletions(-) diff --git a/Assistant/Threads/TransferScanner.hs b/Assistant/Threads/TransferScanner.hs index 0a40f7ead2..485506e7d3 100644 --- a/Assistant/Threads/TransferScanner.hs +++ b/Assistant/Threads/TransferScanner.hs @@ -19,7 +19,7 @@ thisThread :: ThreadName thisThread = "TransferScanner" {- This thread scans remotes, to find transfers that need to be made to - - keep their data in sync. The transfers are queued with lot priority. -} + - keep their data in sync. The transfers are queued with low priority. -} transferScannerThread :: ThreadState -> ScanRemoteMap -> TransferQueue -> IO () transferScannerThread st scanremotes transferqueue = do runEvery (Seconds 2) $ do diff --git a/Assistant/TransferSlots.hs b/Assistant/TransferSlots.hs index dc077254d9..710a188840 100644 --- a/Assistant/TransferSlots.hs +++ b/Assistant/TransferSlots.hs @@ -29,9 +29,10 @@ newTransferSlots = newQSemN numSlots {- Waits until a transfer slot becomes available, and runs a transfer - action in the slot, in its own thread. -} inTransferSlot :: TransferSlots -> ThreadState -> Annex a -> IO ThreadId -inTransferSlot s st a = forkIO $ bracket_ start done run +inTransferSlot s st a = do + waitQSemN s 1 + forkIO $ bracket_ noop done run where - start = waitQSemN s 1 done = transferComplete s run = unsafeRunThreadState st a From a9dbfdf28d6c97c636e58be85f68d2a3f6efef77 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 25 Jul 2012 13:12:34 -0400 Subject: [PATCH 095/331] better transfer queue management Allow transfers to be added with blocking until the queue is sufficiently small. Better control over which end of the queue to add a transfer to. --- Assistant/Threads/Committer.hs | 2 +- Assistant/Threads/TransferScanner.hs | 13 ++++-- Assistant/Threads/Watcher.hs | 2 +- Assistant/TransferQueue.hs | 60 ++++++++++++++++++---------- 4 files changed, 52 insertions(+), 25 deletions(-) diff --git a/Assistant/Threads/Committer.hs b/Assistant/Threads/Committer.hs index ffb2494041..33b92c7e53 100644 --- a/Assistant/Threads/Committer.hs +++ b/Assistant/Threads/Committer.hs @@ -161,7 +161,7 @@ handleAdds st changechan transferqueue dstatus cs = returnWhen (null pendingadds sha <- inRepo $ Git.HashObject.hashObject BlobObject link stageSymlink file sha - queueTransfers transferqueue dstatus key (Just file) Upload + queueTransfers Next transferqueue dstatus key (Just file) Upload showEndOk return $ Just change diff --git a/Assistant/Threads/TransferScanner.hs b/Assistant/Threads/TransferScanner.hs index 485506e7d3..3c2e8dfabc 100644 --- a/Assistant/Threads/TransferScanner.hs +++ b/Assistant/Threads/TransferScanner.hs @@ -18,16 +18,23 @@ import Utility.ThreadScheduler thisThread :: ThreadName thisThread = "TransferScanner" -{- This thread scans remotes, to find transfers that need to be made to - - keep their data in sync. The transfers are queued with low priority. -} +{- This thread waits until a remote needs to be scanned, to find transfers + - that need to be made, to keep data in sync. + - + - Remotes are scanned in the background; the scan is blocked when the + - transfer queue gets too large. + -} transferScannerThread :: ThreadState -> ScanRemoteMap -> TransferQueue -> IO () transferScannerThread st scanremotes transferqueue = do runEvery (Seconds 2) $ do r <- getScanRemote scanremotes needtransfer <- scan st r forM_ needtransfer $ \(f, t) -> - queueLaterTransfer transferqueue f t + queueTransferAt smallsize Later transferqueue f t + where + smallsize = 10 +{- -} scan :: ThreadState -> Remote -> IO [(AssociatedFile, Transfer)] scan st r = do debug thisThread ["scanning", show r] diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs index 617e6d77c5..31025361be 100644 --- a/Assistant/Threads/Watcher.hs +++ b/Assistant/Threads/Watcher.hs @@ -206,7 +206,7 @@ onAddSymlink threadname file filestatus dstatus transferqueue = go =<< Backend.l - try to get the key's content. -} checkcontent key daemonstatus | scanComplete daemonstatus = unlessM (inAnnex key) $ - queueTransfers transferqueue dstatus + queueTransfers Next transferqueue dstatus key (Just file) Download | otherwise = noop diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs index f8104914c1..1fb0bfa37f 100644 --- a/Assistant/TransferQueue.hs +++ b/Assistant/TransferQueue.hs @@ -15,10 +15,18 @@ import qualified Remote import Control.Concurrent.STM -type TransferQueue = TChan (Transfer, TransferInfo) +{- The transfer queue consists of a channel listing the transfers to make; + - the size of the queue is also tracked -} +data TransferQueue = TransferQueue + { queue :: TChan (Transfer, TransferInfo) + , queuesize :: TVar Integer + } + +data Schedule = Next | Later + deriving (Eq) newTransferQueue :: IO TransferQueue -newTransferQueue = atomically newTChan +newTransferQueue = atomically $ TransferQueue <$> newTChan <*> newTVar 0 stubInfo :: AssociatedFile -> TransferInfo stubInfo f = TransferInfo @@ -30,13 +38,11 @@ stubInfo f = TransferInfo , associatedFile = f } -{- Adds pending transfers to the end of the queue for some of the known - - remotes. -} -queueTransfers :: TransferQueue -> DaemonStatusHandle -> Key -> AssociatedFile -> Direction -> Annex () -queueTransfers q daemonstatus k f direction = do +{- Adds pending transfers to queue for some of the known remotes. -} +queueTransfers :: Schedule -> TransferQueue -> DaemonStatusHandle -> Key -> AssociatedFile -> Direction -> Annex () +queueTransfers schedule q daemonstatus k f direction = do rs <- knownRemotes <$> getDaemonStatus daemonstatus - mapM_ (\r -> queue r $ gentransfer r) - =<< sufficientremotes rs + mapM_ go =<< sufficientremotes rs where sufficientremotes rs -- Queue downloads from all remotes that @@ -56,20 +62,34 @@ queueTransfers q daemonstatus k f direction = do , transferKey = k , transferUUID = Remote.uuid r } - queue r t = liftIO $ void $ atomically $ do + go r = liftIO $ atomically $ do let info = (stubInfo f) { transferRemote = Just r } - writeTChan q (t, info) + enqueue schedule q (gentransfer r) info -{- Adds a transfer to the end of the queue, to be processed later. -} -queueLaterTransfer :: TransferQueue -> AssociatedFile -> Transfer -> IO () -queueLaterTransfer q f t = void $ atomically $ - writeTChan q (t, stubInfo f) +enqueue :: Schedule -> TransferQueue -> Transfer -> TransferInfo -> STM () +enqueue schedule q t info + | schedule == Next = go unGetTChan + | otherwise = go writeTChan + where + go a = do + void $ a (queue q) (t, info) + void $ modifyTVar' (queuesize q) succ -{- Adds a transfer to the start of the queue, to be processed next. -} -queueNextTransfer :: TransferQueue -> AssociatedFile -> Transfer -> IO () -queueNextTransfer q f t = void $ atomically $ - unGetTChan q (t, stubInfo f) +{- Adds a transfer to the queue. -} +queueTransfer :: Schedule -> TransferQueue -> AssociatedFile -> Transfer -> IO () +queueTransfer schedule q f t = atomically $ enqueue schedule q t (stubInfo f) -{- Blocks until a pending transfer is available in the queue. -} +{- Blocks until the queue is no larger than a given size, and then adds a + - transfer to the queue. -} +queueTransferAt :: Integer -> Schedule -> TransferQueue -> AssociatedFile -> Transfer -> IO () +queueTransferAt wantsz schedule q f t = atomically $ do + sz <- readTVar (queuesize q) + if sz <= wantsz + then enqueue schedule q t (stubInfo f) + else retry -- blocks until queuesize changes + +{- Blocks until a pending transfer is available from the queue. -} getNextTransfer :: TransferQueue -> IO (Transfer, TransferInfo) -getNextTransfer = atomically . readTChan +getNextTransfer q = atomically $ do + void $ modifyTVar' (queuesize q) pred + readTChan (queue q) From 2b7f9c8442aea97d93011814b7ce6b05e0d576b6 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 25 Jul 2012 14:02:50 -0400 Subject: [PATCH 096/331] fix including of remote in TransferInfo when queueing new transfers --- Assistant/TransferQueue.hs | 24 ++++++++++++------------ 1 file changed, 12 insertions(+), 12 deletions(-) diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs index 1fb0bfa37f..a01c85405a 100644 --- a/Assistant/TransferQueue.hs +++ b/Assistant/TransferQueue.hs @@ -28,17 +28,17 @@ data Schedule = Next | Later newTransferQueue :: IO TransferQueue newTransferQueue = atomically $ TransferQueue <$> newTChan <*> newTVar 0 -stubInfo :: AssociatedFile -> TransferInfo -stubInfo f = TransferInfo +stubInfo :: AssociatedFile -> Remote -> TransferInfo +stubInfo f r = TransferInfo { startedTime = Nothing , transferPid = Nothing , transferTid = Nothing - , transferRemote = Nothing + , transferRemote = Just r , bytesComplete = Nothing , associatedFile = f } -{- Adds pending transfers to queue for some of the known remotes. -} +{- Adds transfers to queue for some of the known remotes. -} queueTransfers :: Schedule -> TransferQueue -> DaemonStatusHandle -> Key -> AssociatedFile -> Direction -> Annex () queueTransfers schedule q daemonstatus k f direction = do rs <- knownRemotes <$> getDaemonStatus daemonstatus @@ -62,9 +62,8 @@ queueTransfers schedule q daemonstatus k f direction = do , transferKey = k , transferUUID = Remote.uuid r } - go r = liftIO $ atomically $ do - let info = (stubInfo f) { transferRemote = Just r } - enqueue schedule q (gentransfer r) info + go r = liftIO $ atomically $ + enqueue schedule q (gentransfer r) (stubInfo f r) enqueue :: Schedule -> TransferQueue -> Transfer -> TransferInfo -> STM () enqueue schedule q t info @@ -76,16 +75,17 @@ enqueue schedule q t info void $ modifyTVar' (queuesize q) succ {- Adds a transfer to the queue. -} -queueTransfer :: Schedule -> TransferQueue -> AssociatedFile -> Transfer -> IO () -queueTransfer schedule q f t = atomically $ enqueue schedule q t (stubInfo f) +queueTransfer :: Schedule -> TransferQueue -> AssociatedFile -> Transfer -> Remote -> IO () +queueTransfer schedule q f t remote = atomically $ + enqueue schedule q t (stubInfo f remote) {- Blocks until the queue is no larger than a given size, and then adds a - transfer to the queue. -} -queueTransferAt :: Integer -> Schedule -> TransferQueue -> AssociatedFile -> Transfer -> IO () -queueTransferAt wantsz schedule q f t = atomically $ do +queueTransferAt :: Integer -> Schedule -> TransferQueue -> AssociatedFile -> Transfer -> Remote -> IO () +queueTransferAt wantsz schedule q f t remote = atomically $ do sz <- readTVar (queuesize q) if sz <= wantsz - then enqueue schedule q t (stubInfo f) + then enqueue schedule q t (stubInfo f remote) else retry -- blocks until queuesize changes {- Blocks until a pending transfer is available from the queue. -} From b665ffe36f83587624e98dfe58cb75ac068525b7 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 25 Jul 2012 14:15:09 -0400 Subject: [PATCH 097/331] implement simple working copy based scan Works.. could be more efficient. --- Assistant/Threads/TransferScanner.hs | 44 +++++++++++++++++++++++----- 1 file changed, 37 insertions(+), 7 deletions(-) diff --git a/Assistant/Threads/TransferScanner.hs b/Assistant/Threads/TransferScanner.hs index 3c2e8dfabc..c2685ae825 100644 --- a/Assistant/Threads/TransferScanner.hs +++ b/Assistant/Threads/TransferScanner.hs @@ -12,8 +12,13 @@ import Assistant.ScanRemotes import Assistant.TransferQueue import Assistant.ThreadedMonad import Logs.Transfer +import Logs.Location import Types.Remote +import qualified Remote import Utility.ThreadScheduler +import qualified Git.LsFiles as LsFiles +import Command +import Annex.Content thisThread :: ThreadName thisThread = "TransferScanner" @@ -28,14 +33,39 @@ transferScannerThread :: ThreadState -> ScanRemoteMap -> TransferQueue -> IO () transferScannerThread st scanremotes transferqueue = do runEvery (Seconds 2) $ do r <- getScanRemote scanremotes - needtransfer <- scan st r + liftIO $ debug thisThread ["starting scan of", show r] + needtransfer <- runThreadState st $ scan r forM_ needtransfer $ \(f, t) -> - queueTransferAt smallsize Later transferqueue f t + queueTransferAt smallsize Later transferqueue f t r + liftIO $ debug thisThread ["finished scan of", show r] where smallsize = 10 -{- -} -scan :: ThreadState -> Remote -> IO [(AssociatedFile, Transfer)] -scan st r = do - debug thisThread ["scanning", show r] - return [] -- TODO +{- This is a naive scan through the git work tree. -} +scan :: Remote -> Annex [(AssociatedFile, Transfer)] +scan r = do + files <- inRepo $ LsFiles.inRepo [] + catMaybes <$> forM files (whenAnnexed go) + where + u = Remote.uuid r + + go file (key, _) = + ifM (inAnnex key) + ( check Upload False =<< remotehas key + , check Download True =<< remotehas key + ) + where + check direction x y + | x == y = return $ + Just (Just file, Transfer direction u key) + | otherwise = return Nothing + + {- Look directly in remote for the key when it's cheap; + - otherwise rely on the location log. -} + remotehas key + | Remote.hasKeyCheap r = (==) + <$> pure (Right True) + <*> Remote.hasKey r key + | otherwise = elem + <$> pure u + <*> loggedLocations key From 95c80b644046f6fabe445972de68be40285f1841 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 25 Jul 2012 14:54:09 -0400 Subject: [PATCH 098/331] laziness fix Now scanning runs fully interleaved with transferring. --- Assistant/Threads/TransferScanner.hs | 50 ++++++++++++++++------------ Assistant/TransferQueue.hs | 10 +++++- 2 files changed, 37 insertions(+), 23 deletions(-) diff --git a/Assistant/Threads/TransferScanner.hs b/Assistant/Threads/TransferScanner.hs index c2685ae825..e76cbe81d3 100644 --- a/Assistant/Threads/TransferScanner.hs +++ b/Assistant/Threads/TransferScanner.hs @@ -13,7 +13,6 @@ import Assistant.TransferQueue import Assistant.ThreadedMonad import Logs.Transfer import Logs.Location -import Types.Remote import qualified Remote import Utility.ThreadScheduler import qualified Git.LsFiles as LsFiles @@ -25,40 +24,47 @@ thisThread = "TransferScanner" {- This thread waits until a remote needs to be scanned, to find transfers - that need to be made, to keep data in sync. - - - - Remotes are scanned in the background; the scan is blocked when the - - transfer queue gets too large. -} transferScannerThread :: ThreadState -> ScanRemoteMap -> TransferQueue -> IO () transferScannerThread st scanremotes transferqueue = do runEvery (Seconds 2) $ do r <- getScanRemote scanremotes liftIO $ debug thisThread ["starting scan of", show r] - needtransfer <- runThreadState st $ scan r - forM_ needtransfer $ \(f, t) -> - queueTransferAt smallsize Later transferqueue f t r + scan st transferqueue r liftIO $ debug thisThread ["finished scan of", show r] where - smallsize = 10 -{- This is a naive scan through the git work tree. -} -scan :: Remote -> Annex [(AssociatedFile, Transfer)] -scan r = do - files <- inRepo $ LsFiles.inRepo [] - catMaybes <$> forM files (whenAnnexed go) +{- This is a naive scan through the git work tree. + - + - The scan is blocked when the transfer queue gets too large. -} +scan :: ThreadState -> TransferQueue -> Remote -> IO () +scan st transferqueue r = do + g <- runThreadState st $ fromRepo id + files <- LsFiles.inRepo [] g + go files where - u = Remote.uuid r - - go file (key, _) = - ifM (inAnnex key) - ( check Upload False =<< remotehas key - , check Download True =<< remotehas key - ) + go [] = return () + go (f:fs) = do + v <- runThreadState st $ whenAnnexed check f + case v of + Nothing -> noop + Just t -> do + debug thisThread ["queuing", show t] + enqueue f t + go fs where - check direction x y + check _ (key, _) = ifM (inAnnex key) + ( helper key Upload False =<< remotehas key + , helper key Download True =<< remotehas key + ) + helper key direction x y | x == y = return $ - Just (Just file, Transfer direction u key) + Just $ Transfer direction u key | otherwise = return Nothing + + u = Remote.uuid r + enqueue f t = queueTransferAt smallsize Later transferqueue (Just f) t r + smallsize = 10 {- Look directly in remote for the key when it's cheap; - otherwise rely on the location log. -} diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs index a01c85405a..9f0ea5cbe1 100644 --- a/Assistant/TransferQueue.hs +++ b/Assistant/TransferQueue.hs @@ -5,7 +5,15 @@ - Licensed under the GNU GPL version 3 or higher. -} -module Assistant.TransferQueue where +module Assistant.TransferQueue ( + TransferQueue, + Schedule(..), + newTransferQueue, + queueTransfers, + queueTransfer, + queueTransferAt, + getNextTransfer +) where import Common.Annex import Assistant.DaemonStatus From 32d3cffc4cf075d7c20fee8addc556f402e94cd2 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 25 Jul 2012 21:26:13 -0400 Subject: [PATCH 099/331] run yesod, and launch webapp on startup --- Assistant.hs | 8 +++ Assistant/Threads/WebApp.hs | 43 +++++++++++++ Makefile | 20 +++--- Utility/WebApp.hs | 104 +++++++++++++++++++++++++++++++ debian/control | 1 + doc/design/assistant/webapp.mdwn | 2 +- doc/git-annex.mdwn | 6 ++ doc/install.mdwn | 2 + git-annex.cabal | 13 ++++ 9 files changed, 189 insertions(+), 10 deletions(-) create mode 100644 Assistant/Threads/WebApp.hs create mode 100644 Utility/WebApp.hs diff --git a/Assistant.hs b/Assistant.hs index 0049d31777..de996aa741 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -88,6 +88,8 @@ - are indicated by writing to this TMVar. -} +{-# LANGUAGE CPP #-} + module Assistant where import Assistant.Common @@ -108,6 +110,9 @@ import Assistant.Threads.Transferrer import Assistant.Threads.SanityChecker import Assistant.Threads.MountWatcher import Assistant.Threads.TransferScanner +#ifdef WITH_WEBAPP +import Assistant.Threads.WebApp +#endif import qualified Utility.Daemon import Utility.LogFile import Utility.ThreadScheduler @@ -146,6 +151,9 @@ startDaemon assistant foreground , sanityCheckerThread st dstatus transferqueue changechan , mountWatcherThread st dstatus scanremotes , transferScannerThread st scanremotes transferqueue +#ifdef WITH_WEBAPP + , webAppThread dstatus +#endif , watchThread st dstatus transferqueue changechan ] debug "assistant" diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs new file mode 100644 index 0000000000..1d9d3cc2fc --- /dev/null +++ b/Assistant/Threads/WebApp.hs @@ -0,0 +1,43 @@ +{- git-annex assistant webapp + - + - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings #-} + +module Assistant.Threads.WebApp where + +import Assistant.Common +import Assistant.DaemonStatus +import Utility.WebApp + +import Yesod + +data WebApp = WebApp DaemonStatusHandle + +mkYesod "WebApp" [parseRoutes| +/ HomeR GET +/config ConfigR GET +|] + +instance Yesod WebApp + +getHomeR :: Handler RepHtml +getHomeR = defaultLayout [whamlet|Hello, World

config|] + +getConfigR :: Handler RepHtml +getConfigR = defaultLayout [whamlet|main|] + +webAppThread :: DaemonStatusHandle -> IO () +webAppThread dstatus = do + app <- toWaiApp (WebApp dstatus) + app' <- ifM debugEnabled + ( return $ httpDebugLogger app + , return app + ) + runWebApp app' browser + where + browser p = void $ + runBrowser $ "http://" ++ localhost ++ ":" ++ show p diff --git a/Makefile b/Makefile index 8b9b35bdd6..9f312dc49c 100644 --- a/Makefile +++ b/Makefile @@ -1,19 +1,23 @@ +CFLAGS=-Wall +IGNORE=-ignore-package monads-fd -ignore-package monads-tf +BASEFLAGS=-threaded -Wall $(IGNORE) -outputdir tmp -IUtility +FEATURES=-DWITH_ASSISTANT -DWITH_S3 -DWITH_WEBAPP + bins=git-annex mans=git-annex.1 git-annex-shell.1 sources=Build/SysConfig.hs Utility/Touch.hs Utility/Mounts.hs all=$(bins) $(mans) docs -CFLAGS=-Wall - OS:=$(shell uname | sed 's/[-_].*//') ifeq ($(OS),Linux) -BASEFLAGS_OPTS=-DWITH_INOTIFY -DWITH_DBUS +OPTFLAGS=-DWITH_INOTIFY -DWITH_DBUS clibs=Utility/libdiskfree.o Utility/libmounts.o else # BSD system -BASEFLAGS_OPTS=-DWITH_KQUEUE +OPTFLAGS=-DWITH_KQUEUE clibs=Utility/libdiskfree.o Utility/libmounts.o Utility/libkqueue.o ifeq ($(OS),Darwin) +OPTFLAGS=-DWITH_KQUEUE -DOSX # Ensure OSX compiler builds for 32 bit when using 32 bit ghc GHCARCH:=$(shell ghc -e 'print System.Info.arch') ifeq ($(GHCARCH),i386) @@ -23,12 +27,10 @@ endif endif PREFIX=/usr -IGNORE=-ignore-package monads-fd -ignore-package monads-tf -BASEFLAGS=-threaded -Wall $(IGNORE) -outputdir tmp -IUtility -DWITH_ASSISTANT -DWITH_S3 $(BASEFLAGS_OPTS) -GHCFLAGS=-O2 $(BASEFLAGS) +GHCFLAGS=-O2 $(BASEFLAGS) $(FEATURES) ifdef PROFILE -GHCFLAGS=-prof -auto-all -rtsopts -caf-all -fforce-recomp $(BASEFLAGS) +GHCFLAGS=-prof -auto-all -rtsopts -caf-all -fforce-recomp $(BASEFLAGS) $(FEATURES) $(OPTFLAGS) endif GHCMAKE=ghc $(GHCFLAGS) --make @@ -43,7 +45,7 @@ all: $(all) sources: $(sources) # Disables optimisation. Not for production use. -fast: GHCFLAGS=$(BASEFLAGS) +fast: GHCFLAGS=$(BASEFLAGS) $(FEATURES) $(OPTFLAGS) fast: $(bins) Build/SysConfig.hs: configure.hs Build/TestConfig.hs Build/Configure.hs diff --git a/Utility/WebApp.hs b/Utility/WebApp.hs new file mode 100644 index 0000000000..614a57cea5 --- /dev/null +++ b/Utility/WebApp.hs @@ -0,0 +1,104 @@ +{- WAI webapp + - + - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +{-# LANGUAGE OverloadedStrings, CPP #-} + +module Utility.WebApp where + +import Common + +import Network.Wai +import Network.Wai.Handler.Warp +import Network.Wai.Logger +import Control.Monad.IO.Class +import Network.HTTP.Types +import System.Log.Logger +import Data.ByteString.Lazy.UTF8 +import Data.ByteString.Lazy +import Data.CaseInsensitive as CI +import Network.Socket +import Control.Exception + +localhost :: String +localhost = "localhost" + +{- Runs a web browser on a given url. + - + - Note: The url *will* be visible to an attacker. -} +runBrowser :: String -> IO Bool +runBrowser url = boolSystem cmd [Param url] + where +#if MAC + cmd = "open" +#else + cmd = "xdg-open" +#endif + +{- Binds to a socket on localhost, and runs a webapp on it. + - + - An IO action can also be run, to do something with the port number, + - such as start a web browser to view the webapp. + -} +runWebApp :: Application -> (PortNumber -> IO ()) -> IO () +runWebApp app observer = do + sock <- localSocket + observer =<< socketPort sock + runSettingsSocket defaultSettings sock app + +{- Binds to a local socket, selecting any free port. + - + - As a (very weak) form of security, only connections from + - localhost are accepted. -} +localSocket :: IO Socket +localSocket = do + addrs <- getAddrInfo (Just hints) (Just localhost) Nothing + go $ Prelude.head addrs + where + hints = defaultHints + { addrFlags = [AI_ADDRCONFIG, AI_NUMERICSERV] + , addrSocketType = Stream + } + go addr = bracketOnError (open addr) close (use addr) + open addr = socket (addrFamily addr) (addrSocketType addr) (addrProtocol addr) + close = sClose + use addr sock = do + setSocketOption sock ReuseAddr 1 + bindSocket sock (addrAddress addr) + listen sock maxListenQueue + return sock + +{- Checks if debugging is actually enabled. -} +debugEnabled :: IO Bool +debugEnabled = do + l <- getRootLogger + return $ getLevel l <= Just DEBUG + +{- WAI middleware that logs using System.Log.Logger at debug level. + - + - Recommend only inserting this middleware when debugging is actually + - enabled, as it's not optimised at all. + -} +httpDebugLogger :: Middleware +httpDebugLogger waiApp req = do + logRequest req + waiApp req + +logRequest :: MonadIO m => Request -> m () +logRequest req = do + liftIO $ debugM "WebApp" $ unwords + [ showSockAddr $ remoteHost req + , frombs $ requestMethod req + , frombs $ rawPathInfo req + --, show $ httpVersion req + --, frombs $ lookupRequestField "referer" req + , frombs $ lookupRequestField "user-agent" req + ] + where + frombs v = toString $ fromChunks [v] + +lookupRequestField :: CI Ascii -> Request -> Ascii +lookupRequestField k req = fromMaybe "" . lookup k $ requestHeaders req diff --git a/debian/control b/debian/control index 35cbfde054..c7531cd3f1 100644 --- a/debian/control +++ b/debian/control @@ -23,6 +23,7 @@ Build-Depends: libghc-hinotify-dev [linux-any], libghc-stm-dev (>= 2.3), libghc-dbus-dev, + libghc-yesod-dev, ikiwiki, perlmagick, git, diff --git a/doc/design/assistant/webapp.mdwn b/doc/design/assistant/webapp.mdwn index 598c1ff3a4..cec766c579 100644 --- a/doc/design/assistant/webapp.mdwn +++ b/doc/design/assistant/webapp.mdwn @@ -2,7 +2,7 @@ The webapp is a web server that displays a shiny interface. ## security -* Listen only to localhost. +* Listen only to localhost. **done** * Instruct the user's web browser to open an url that contains a secret token. This guards against other users on the same system. * I would like to avoid passwords or other authentication methods, diff --git a/doc/git-annex.mdwn b/doc/git-annex.mdwn index 85a5a18f00..282b1fda50 100644 --- a/doc/git-annex.mdwn +++ b/doc/git-annex.mdwn @@ -188,6 +188,12 @@ subdirectories). * assistant Like watch, but also automatically syncs changes to other remotes. + Typically started at boot, or when you log in. + +* webapp + + Opens a web browser, viewing the git-annex assistant's web app. + (If the assistant is not already running, it will be automatically started.) # REPOSITORY SETUP COMMANDS diff --git a/doc/install.mdwn b/doc/install.mdwn index 54d6ecb6b5..058c3cf6e1 100644 --- a/doc/install.mdwn +++ b/doc/install.mdwn @@ -48,6 +48,8 @@ To build and use git-annex, you will need: (optional; Linux only) * [dbus](http://hackage.haskell.org/package/dbus) (optional) + * [yesod](http://hackage.haskell.org/package/yesod) + (optional; for webapp) * Shell commands * [git](http://git-scm.com/) * [uuid](http://www.ossp.org/pkg/lib/uuid/) diff --git a/git-annex.cabal b/git-annex.cabal index 2e312d4c38..11412d19ab 100644 --- a/git-annex.cabal +++ b/git-annex.cabal @@ -37,6 +37,9 @@ Flag Dbus Flag Assistant Description: Enable git-annex assistant and watch command +Flag Webapp + Description: Enable git-annex webapp + Executable git-annex Main-Is: git-annex.hs Build-Depends: MissingH, hslogger, directory, filepath, @@ -61,11 +64,21 @@ Executable git-annex if os(linux) && flag(Inotify) Build-Depends: hinotify CPP-Options: -DWITH_INOTIFY + else + if (! os(windows)) + CPP-Options: -DWITH_KQUEUE if flag(Dbus) Build-Depends: dbus CPP-Options: -DWITH_DBUS + if flag(Webapp) + Build-Depends: yesod + CPP-Options: -DWITH_WEBAPP + + if (os(darwin)) + CPP-Options: -DOSX + Test-Suite test Type: exitcode-stdio-1.0 Main-Is: test.hs From e6ce54de82c19999fb5adcd5fd1ea4001fd2059e Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 25 Jul 2012 22:04:10 -0400 Subject: [PATCH 100/331] build fixes --- Assistant/Threads/Merger.hs | 2 +- debian/control | 6 ++++++ doc/install.mdwn | 13 +++++++++---- git-annex.cabal | 5 ++++- 4 files changed, 20 insertions(+), 6 deletions(-) diff --git a/Assistant/Threads/Merger.hs b/Assistant/Threads/Merger.hs index 10ea34692b..c79566349d 100644 --- a/Assistant/Threads/Merger.hs +++ b/Assistant/Threads/Merger.hs @@ -25,7 +25,7 @@ import qualified Remote thisThread :: ThreadName thisThread = "Merger" -{- This thread watches for changes to .git/refs/heads/synced/*, +{- This thread watches for changes to .git/refs/heads/synced/, - which indicate incoming pushes. It merges those pushes into the - currently checked out branch. -} mergeThread :: ThreadState -> IO () diff --git a/debian/control b/debian/control index c7531cd3f1..65c666cde4 100644 --- a/debian/control +++ b/debian/control @@ -24,6 +24,12 @@ Build-Depends: libghc-stm-dev (>= 2.3), libghc-dbus-dev, libghc-yesod-dev, + libghc-case-insensitive-dev, + libghc-http-types-dev, + libghc-transformers-dev, + libghc-wai-dev, + libghc-wai-logger-dev, + libghc-warp-dev, ikiwiki, perlmagick, git, diff --git a/doc/install.mdwn b/doc/install.mdwn index 058c3cf6e1..619d5fa11d 100644 --- a/doc/install.mdwn +++ b/doc/install.mdwn @@ -42,14 +42,19 @@ To build and use git-annex, you will need: * [bloomfilter](http://hackage.haskell.org/package/bloomfilter) * [edit-distance](http://hackage.haskell.org/package/edit-distance) * [hS3](http://hackage.haskell.org/package/hS3) (optional) +* Optional haskell stuff, used by the assistant and webapp (edit Makefile to disable) * [stm](http://hackage.haskell.org/package/stm) - (optional; version 2.3 or newer) + (version 2.3 or newer) * [hinotify](http://hackage.haskell.org/package/hinotify) - (optional; Linux only) + (Linux only) * [dbus](http://hackage.haskell.org/package/dbus) - (optional) * [yesod](http://hackage.haskell.org/package/yesod) - (optional; for webapp) + * [case-insensitive](http://hackage.haskell.org/package/case-insensitive) + * [http-types](http://hackage.haskell.org/package/http-types) + * [transformers](http://hackage.haskell.org/package/transformers) + * [wai](http://hackage.haskell.org/package/wai) + * [wai-logger](http://hackage.haskell.org/package/wai-logger) + * [warp](http://hackage.haskell.org/package/warp) * Shell commands * [git](http://git-scm.com/) * [uuid](http://www.ossp.org/pkg/lib/uuid/) diff --git a/git-annex.cabal b/git-annex.cabal index 11412d19ab..086df31d29 100644 --- a/git-annex.cabal +++ b/git-annex.cabal @@ -46,9 +46,11 @@ Executable git-annex unix, containers, utf8-string, network, mtl, bytestring, old-locale, time, pcre-light, extensible-exceptions, dataenc, SHA, process, json, HTTP, base == 4.5.*, monad-control, transformers-base, lifted-base, - IfElse, text, QuickCheck >= 2.1, bloomfilter, edit-distance, process + IfElse, text, QuickCheck >= 2.1, bloomfilter, edit-distance, process, + case-insensitive, http-types, transformers, wai, wai-logger, warp -- Need to list these because they're generated from .hsc files. Other-Modules: Utility.Touch Utility.Mounts + Include-Dirs: Utility C-Sources: Utility/libdiskfree.c Utility/libmounts.c Extensions: CPP GHC-Options: -threaded @@ -88,6 +90,7 @@ Test-Suite test base == 4.5.*, monad-control, transformers-base, lifted-base, IfElse, text, QuickCheck >= 2.1, bloomfilter, edit-distance, process Other-Modules: Utility.Touch + Include-Dirs: Utility C-Sources: Utility/libdiskfree.c Extensions: CPP GHC-Options: -threaded From 1ffef3ad75e51b7f66c4ffdd0935a0495042e5ae Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 25 Jul 2012 23:13:01 -0400 Subject: [PATCH 101/331] git annex webapp now opens a browser to the webapp Also, starts the assistant if it wasn't already running. --- Assistant.hs | 2 +- Assistant/Threads/WebApp.hs | 31 ++++++++++++++++---- Command/WebApp.hs | 58 +++++++++++++++++++++++++++++++++++++ GitAnnex.hs | 6 ++++ Locations.hs | 5 ++++ Utility/Daemon.hs | 43 ++++++++++++++++----------- 6 files changed, 122 insertions(+), 23 deletions(-) create mode 100644 Command/WebApp.hs diff --git a/Assistant.hs b/Assistant.hs index de996aa741..c867529fdf 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -152,7 +152,7 @@ startDaemon assistant foreground , mountWatcherThread st dstatus scanremotes , transferScannerThread st scanremotes transferqueue #ifdef WITH_WEBAPP - , webAppThread dstatus + , webAppThread st dstatus #endif , watchThread st dstatus transferqueue changechan ] diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 1d9d3cc2fc..f3f13c5a09 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -10,10 +10,12 @@ module Assistant.Threads.WebApp where import Assistant.Common +import Assistant.ThreadedMonad import Assistant.DaemonStatus import Utility.WebApp import Yesod +import Network.Socket (PortNumber) data WebApp = WebApp DaemonStatusHandle @@ -30,14 +32,33 @@ getHomeR = defaultLayout [whamlet|Hello, World

config|] getConfigR :: Handler RepHtml getConfigR = defaultLayout [whamlet|main|] -webAppThread :: DaemonStatusHandle -> IO () -webAppThread dstatus = do +webAppThread :: ThreadState -> DaemonStatusHandle -> IO () +webAppThread st dstatus = do app <- toWaiApp (WebApp dstatus) app' <- ifM debugEnabled ( return $ httpDebugLogger app , return app ) - runWebApp app' browser + runWebApp app' $ \p -> runThreadState st $ writeHtmlShim p + +{- Creates a html shim file that's used to redirect into the webapp. -} +writeHtmlShim :: PortNumber -> Annex () +writeHtmlShim port = do + htmlshim <- fromRepo gitAnnexHtmlShim + liftIO $ writeFile htmlshim $ genHtmlShim port + +{- TODO: generate this static file using Yesod. -} +genHtmlShim :: PortNumber -> String +genHtmlShim port = unlines + [ "" + , "" + , "" + , "" + , "" + , "

" + , "Starting webapp..." + , "

" + , "" + ] where - browser p = void $ - runBrowser $ "http://" ++ localhost ++ ":" ++ show p + url = "http://localhost:" ++ show port ++ "/" diff --git a/Command/WebApp.hs b/Command/WebApp.hs new file mode 100644 index 0000000000..616a6512a8 --- /dev/null +++ b/Command/WebApp.hs @@ -0,0 +1,58 @@ +{- git-annex webapp launcher + - + - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Command.WebApp where + +import Common.Annex +import Command +import Assistant +import Utility.WebApp +import Utility.Daemon +import qualified Annex + +import Control.Concurrent +import System.Posix.Process + +def :: [Command] +def = [command "webapp" paramNothing seek "launch webapp"] + +seek :: [CommandSeek] +seek = [withNothing start] + +start :: CommandStart +start = notBareRepo $ do + r <- checkpid + when (r == Nothing) $ + startassistant + f <- liftIO . absPath =<< fromRepo gitAnnexHtmlShim + let url = "file://" ++ f + ifM (liftIO $ runBrowser url) + ( stop + , error $ "failed to start web browser on url " ++ url + ) + where + checkpid = do + pidfile <- fromRepo gitAnnexPidFile + liftIO $ checkDaemon pidfile + startassistant = do + {- Fork a separate process to run the assistant, + - with a copy of the Annex state. -} + state <- Annex.getState id + liftIO $ void $ forkProcess $ + Annex.eval state $ startDaemon True False + waitdaemon (100 :: Int) + waitdaemon 0 = error "failed to start git-annex assistant" + waitdaemon n = do + r <- checkpid + case r of + Just _ -> return () + Nothing -> do + liftIO $ + threadDelay 100000 -- 0.1 seconds + + +waitdaemon (n - 1) diff --git a/GitAnnex.hs b/GitAnnex.hs index 7b1fa59868..ce7a41a40f 100644 --- a/GitAnnex.hs +++ b/GitAnnex.hs @@ -63,6 +63,9 @@ import qualified Command.Version #ifdef WITH_ASSISTANT import qualified Command.Watch import qualified Command.Assistant +#ifdef WITH_WEBAPP +import qualified Command.WebApp +#endif #endif cmds :: [Command] @@ -108,6 +111,9 @@ cmds = concat #ifdef WITH_ASSISTANT , Command.Watch.def , Command.Assistant.def +#ifdef WITH_WEBAPP + , Command.WebApp.def +#endif #endif ] diff --git a/Locations.hs b/Locations.hs index 082a72a506..cbd1e11ae0 100644 --- a/Locations.hs +++ b/Locations.hs @@ -27,6 +27,7 @@ module Locations ( gitAnnexPidFile, gitAnnexDaemonStatusFile, gitAnnexLogFile, + gitAnnexHtmlShim, gitAnnexSshDir, gitAnnexRemotesDir, isLinkToAnnex, @@ -166,6 +167,10 @@ gitAnnexDaemonStatusFile r = gitAnnexDir r "daemon.status" gitAnnexLogFile :: Git.Repo -> FilePath gitAnnexLogFile r = gitAnnexDir r "daemon.log" +{- Html shim file used to launch the webapp. -} +gitAnnexHtmlShim :: Git.Repo -> FilePath +gitAnnexHtmlShim r = gitAnnexDir r "webapp.html" + {- .git/annex/ssh/ is used for ssh connection caching -} gitAnnexSshDir :: Git.Repo -> FilePath gitAnnexSshDir r = addTrailingPathSeparator $ gitAnnexDir r "ssh" diff --git a/Utility/Daemon.hs b/Utility/Daemon.hs index f36a761d00..8aa70d155c 100644 --- a/Utility/Daemon.hs +++ b/Utility/Daemon.hs @@ -62,24 +62,33 @@ lockPidFile onfailure file = do where newfile = file ++ ".new" -{- Stops the daemon. +{- Checks if the daemon is running, by checking that the pid file + - is locked by the same process that is listed in the pid file. - - - The pid file is used to get the daemon's pid. - - - - To guard against a stale pid, check the lock of the pid file, - - and compare the process that has it locked with the file content. - -} -stopDaemon :: FilePath -> IO () -stopDaemon pidfile = do - fd <- openFd pidfile ReadOnly (Just stdFileMode) defaultFileFlags - locked <- getLock fd (ReadLock, AbsoluteSeek, 0, 0) - p <- readish <$> readFile pidfile - case (locked, p) of - (Nothing, _) -> noop - (_, Nothing) -> noop - (Just (pid, _), Just pid') - | pid == pid' -> signalProcess sigTERM pid - | otherwise -> error $ + - If it's running, returns its pid. -} +checkDaemon :: FilePath -> IO (Maybe ProcessID) +checkDaemon pidfile = do + v <- catchMaybeIO $ + openFd pidfile ReadOnly (Just stdFileMode) defaultFileFlags + case v of + Just fd -> do + locked <- getLock fd (ReadLock, AbsoluteSeek, 0, 0) + p <- readish <$> readFile pidfile + return $ check locked p + Nothing -> return Nothing + where + check Nothing _ = Nothing + check _ Nothing = Nothing + check (Just (pid, _)) (Just pid') + | pid == pid' = Just pid + | otherwise = error $ "stale pid in " ++ pidfile ++ " (got " ++ show pid' ++ "; expected" ++ show pid ++ " )" + +{- Stops the daemon, safely. -} +stopDaemon :: FilePath -> IO () +stopDaemon pidfile = go =<< checkDaemon pidfile + where + go Nothing = noop + go (Just pid) = signalProcess sigTERM pid From 81b40cf882e50be4d996fd40d045039de94784ef Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 25 Jul 2012 23:50:14 -0400 Subject: [PATCH 102/331] fix editor damage --- Command/WebApp.hs | 8 +++----- 1 file changed, 3 insertions(+), 5 deletions(-) diff --git a/Command/WebApp.hs b/Command/WebApp.hs index 616a6512a8..0e01a07cd3 100644 --- a/Command/WebApp.hs +++ b/Command/WebApp.hs @@ -51,8 +51,6 @@ start = notBareRepo $ do case r of Just _ -> return () Nothing -> do - liftIO $ - threadDelay 100000 -- 0.1 seconds - - -waitdaemon (n - 1) + -- wait 0.1 seconds before retry + liftIO $ threadDelay 100000 + waitdaemon (n - 1) From 805d50c69d40be97baa28735371778df63b5fed6 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 25 Jul 2012 23:50:29 -0400 Subject: [PATCH 103/331] use hamlet at least for the static html --- Assistant/Threads/WebApp.hs | 27 ++++++++++++++------------- 1 file changed, 14 insertions(+), 13 deletions(-) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index f3f13c5a09..d475865dca 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -15,7 +15,10 @@ import Assistant.DaemonStatus import Utility.WebApp import Yesod +import Text.Hamlet import Network.Socket (PortNumber) +import Text.Blaze.Renderer.Utf8 +import Data.ByteString.Lazy as L data WebApp = WebApp DaemonStatusHandle @@ -45,20 +48,18 @@ webAppThread st dstatus = do writeHtmlShim :: PortNumber -> Annex () writeHtmlShim port = do htmlshim <- fromRepo gitAnnexHtmlShim - liftIO $ writeFile htmlshim $ genHtmlShim port + liftIO $ L.writeFile htmlshim $ genHtmlShim port {- TODO: generate this static file using Yesod. -} -genHtmlShim :: PortNumber -> String -genHtmlShim port = unlines - [ "" - , "" - , "" - , "" - , "" - , "

" - , "Starting webapp..." - , "

" - , "" - ] +genHtmlShim :: PortNumber -> L.ByteString +genHtmlShim port = renderHtml [shamlet| +!!! + + + + +

+ Starting webapp... +|] where url = "http://localhost:" ++ show port ++ "/" From 6a8540c1a2ae61d81e06eae2865ac00c6c759ed5 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 26 Jul 2012 00:39:25 -0400 Subject: [PATCH 104/331] tweak --- Assistant/Threads/WebApp.hs | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index d475865dca..d9b648831a 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -37,12 +37,14 @@ getConfigR = defaultLayout [whamlet|main|] webAppThread :: ThreadState -> DaemonStatusHandle -> IO () webAppThread st dstatus = do - app <- toWaiApp (WebApp dstatus) + app <- toWaiApp webapp app' <- ifM debugEnabled ( return $ httpDebugLogger app , return app ) - runWebApp app' $ \p -> runThreadState st $ writeHtmlShim p + runWebApp app' $ \port -> runThreadState st $ writeHtmlShim port + where + webapp = WebApp dstatus {- Creates a html shim file that's used to redirect into the webapp. -} writeHtmlShim :: PortNumber -> Annex () @@ -53,13 +55,13 @@ writeHtmlShim port = do {- TODO: generate this static file using Yesod. -} genHtmlShim :: PortNumber -> L.ByteString genHtmlShim port = renderHtml [shamlet| -!!! +$doctype 5

- Starting webapp... + Starting webapp... |] where url = "http://localhost:" ++ show port ++ "/" From 3ac2cf09e56cb1918312a31e0884d56829a14c32 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 26 Jul 2012 02:45:01 -0400 Subject: [PATCH 105/331] added a custom defaultLayout, static site, and favicon Broke hamlet out into standalone files. I don't like the favicon display; it should be served from /favicon.ico, but I could only get the static site to serve /static/favicon.ico, so I had to use a to pull it in. I looked at Yesod.Default.Handlers.getFaviconR, but it doesn't seem to embed the favicon into the binary? --- Assistant/Threads/WebApp.hs | 53 +++++++++++++++++++++++--------- Utility/Yesod.hs | 18 +++++++++++ static/favicon.ico | Bin 0 -> 405 bytes templates/default-layout.hamlet | 11 +++++++ templates/htmlshim.hamlet | 7 +++++ 5 files changed, 74 insertions(+), 15 deletions(-) create mode 100644 Utility/Yesod.hs create mode 100644 static/favicon.ico create mode 100644 templates/default-layout.hamlet create mode 100644 templates/htmlshim.hamlet diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index d9b648831a..4e6fea6b11 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -13,38 +13,69 @@ import Assistant.Common import Assistant.ThreadedMonad import Assistant.DaemonStatus import Utility.WebApp +import Utility.Yesod +import Git import Yesod +import Yesod.Static import Text.Hamlet import Network.Socket (PortNumber) import Text.Blaze.Renderer.Utf8 import Data.ByteString.Lazy as L -data WebApp = WebApp DaemonStatusHandle +data WebApp = WebApp + { daemonStatus :: DaemonStatusHandle + , baseTitle :: String + , getStatic :: Static + } + +staticFiles "static" mkYesod "WebApp" [parseRoutes| +/static StaticR Static getStatic / HomeR GET /config ConfigR GET |] -instance Yesod WebApp +instance Yesod WebApp where + defaultLayout contents = do + page <- widgetToPageContent contents + mmsg <- getMessage + webapp <- getYesod + hamletToRepHtml $(hamletFile $ hamletTemplate "default-layout") getHomeR :: Handler RepHtml -getHomeR = defaultLayout [whamlet|Hello, World

config|] +getHomeR = defaultLayout $ do + [whamlet|Hello, World

config|] getConfigR :: Handler RepHtml -getConfigR = defaultLayout [whamlet|main|] +getConfigR = defaultLayout $ do + setTitle "configuration" + [whamlet|main|] webAppThread :: ThreadState -> DaemonStatusHandle -> IO () webAppThread st dstatus = do + webapp <- mkWebApp st dstatus app <- toWaiApp webapp app' <- ifM debugEnabled ( return $ httpDebugLogger app , return app ) runWebApp app' $ \port -> runThreadState st $ writeHtmlShim port - where - webapp = WebApp dstatus + +mkWebApp :: ThreadState -> DaemonStatusHandle -> IO WebApp +mkWebApp st dstatus = do + dir <- absPath =<< runThreadState st (fromRepo repoPath) + home <- myHomeDir + let reldir = if dirContains home dir + then relPathDirToFile home dir + else dir + let s = $(embed "static") + return $ WebApp + { daemonStatus = dstatus + , baseTitle = reldir + , getStatic = s + } {- Creates a html shim file that's used to redirect into the webapp. -} writeHtmlShim :: PortNumber -> Annex () @@ -54,14 +85,6 @@ writeHtmlShim port = do {- TODO: generate this static file using Yesod. -} genHtmlShim :: PortNumber -> L.ByteString -genHtmlShim port = renderHtml [shamlet| -$doctype 5 - - - - -

- Starting webapp... -|] +genHtmlShim port = renderHtml $(shamletFile $ hamletTemplate "htmlshim") where url = "http://localhost:" ++ show port ++ "/" diff --git a/Utility/Yesod.hs b/Utility/Yesod.hs new file mode 100644 index 0000000000..05f684490a --- /dev/null +++ b/Utility/Yesod.hs @@ -0,0 +1,18 @@ +{- Yesod stuff + - + - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Utility.Yesod where + +import System.FilePath + +{- Filename of a template, in the templates/ directory. -} +template :: FilePath -> FilePath +template f = "templates" f + +{- A hamlet template file. -} +hamletTemplate :: FilePath -> FilePath +hamletTemplate f = template f ++ ".hamlet" diff --git a/static/favicon.ico b/static/favicon.ico new file mode 100644 index 0000000000000000000000000000000000000000..5bb405931fcc8f8194694e5d6cb728e50658891e GIT binary patch literal 405 zcmex=bI)35R>*e`CsU}f<4#mC*t-skh=9nPFAvL)f4AHU1X%imZ2>GMq7 z9Qkz8nG&C%#d}NA9x5}4Y=}=u%=tanUZi)Dv@7qlRhOEXZ#_NRE_mW`HTUk>SB@)n MY&muAb@%_9027yGs{jB1 literal 0 HcmV?d00001 diff --git a/templates/default-layout.hamlet b/templates/default-layout.hamlet new file mode 100644 index 0000000000..e07addc8e0 --- /dev/null +++ b/templates/default-layout.hamlet @@ -0,0 +1,11 @@ +$doctype 5 + + + #{baseTitle webapp} #{pageTitle page} + <link rel="icon" href=@{StaticR favicon_ico} type="image/x-icon"> + + ^{pageHead page} + <body> + $maybe msg <- mmsg + <div #message>#{msg} + ^{pageBody page} diff --git a/templates/htmlshim.hamlet b/templates/htmlshim.hamlet new file mode 100644 index 0000000000..c10042c999 --- /dev/null +++ b/templates/htmlshim.hamlet @@ -0,0 +1,7 @@ +$doctype 5 +<html> + <head> + <meta http-equiv="refresh" content="0; URL=#{url}"> + <body> + <p> + <a href=#{url}">Starting webapp... From b36804d6486b342bee7f5b4b621228bc193c4844 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 03:38:20 -0400 Subject: [PATCH 106/331] generate random token and launch webapp using it --- Assistant/Threads/WebApp.hs | 31 ++++++++++++++++++++----------- Utility/WebApp.hs | 13 +++++++++++++ 2 files changed, 33 insertions(+), 11 deletions(-) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 4e6fea6b11..06909fd531 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -14,17 +14,19 @@ import Assistant.ThreadedMonad import Assistant.DaemonStatus import Utility.WebApp import Utility.Yesod +import Utility.FileMode +import Utility.TempFile import Git import Yesod import Yesod.Static import Text.Hamlet import Network.Socket (PortNumber) -import Text.Blaze.Renderer.Utf8 -import Data.ByteString.Lazy as L +import Text.Blaze.Renderer.String data WebApp = WebApp { daemonStatus :: DaemonStatusHandle + , secretToken :: String , baseTitle :: String , getStatic :: Static } @@ -61,7 +63,7 @@ webAppThread st dstatus = do ( return $ httpDebugLogger app , return app ) - runWebApp app' $ \port -> runThreadState st $ writeHtmlShim port + runWebApp app' $ \port -> runThreadState st $ writeHtmlShim webapp port mkWebApp :: ThreadState -> DaemonStatusHandle -> IO WebApp mkWebApp st dstatus = do @@ -70,21 +72,28 @@ mkWebApp st dstatus = do let reldir = if dirContains home dir then relPathDirToFile home dir else dir - let s = $(embed "static") + token <- genRandomToken return $ WebApp { daemonStatus = dstatus + , secretToken = token , baseTitle = reldir - , getStatic = s + , getStatic = $(embed "static") } {- Creates a html shim file that's used to redirect into the webapp. -} -writeHtmlShim :: PortNumber -> Annex () -writeHtmlShim port = do +writeHtmlShim :: WebApp -> PortNumber -> Annex () +writeHtmlShim webapp port = do htmlshim <- fromRepo gitAnnexHtmlShim - liftIO $ L.writeFile htmlshim $ genHtmlShim port + liftIO $ viaTmp go htmlshim $ genHtmlShim webapp port + where + go file content = do + h <- openFile file WriteMode + modifyFileMode file $ removeModes [groupReadMode, otherReadMode] + hPutStr h content + hClose h {- TODO: generate this static file using Yesod. -} -genHtmlShim :: PortNumber -> L.ByteString -genHtmlShim port = renderHtml $(shamletFile $ hamletTemplate "htmlshim") +genHtmlShim :: WebApp -> PortNumber -> String +genHtmlShim webapp port = renderHtml $(shamletFile $ hamletTemplate "htmlshim") where - url = "http://localhost:" ++ show port ++ "/" + url = "http://localhost:" ++ show port ++ "/?" ++ secretToken webapp diff --git a/Utility/WebApp.hs b/Utility/WebApp.hs index 614a57cea5..cded83229e 100644 --- a/Utility/WebApp.hs +++ b/Utility/WebApp.hs @@ -22,6 +22,9 @@ import Data.ByteString.Lazy import Data.CaseInsensitive as CI import Network.Socket import Control.Exception +import Crypto.Random +import Data.Digest.Pure.SHA +import Data.ByteString.Lazy as L localhost :: String localhost = "localhost" @@ -102,3 +105,13 @@ logRequest req = do lookupRequestField :: CI Ascii -> Request -> Ascii lookupRequestField k req = fromMaybe "" . lookup k $ requestHeaders req + +{- Generates a 512 byte random token, suitable to be used for an + - authentication secret. -} +genRandomToken :: IO String +genRandomToken = do + g <- newGenIO :: IO SystemRandom + return $ + case genBytes 512 g of + Left e -> error $ "failed to generate secret token: " ++ show e + Right (s, _) -> showDigest $ sha512 $ L.fromChunks [s] From 9d6b59d0e21e5917d098a84b7b1654bd8d07efb3 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 04:50:09 -0400 Subject: [PATCH 107/331] use the secret token for authentication, and add to all dynamic urls --- Assistant/Threads/WebApp.hs | 25 +++++++++++-- Utility/WebApp.hs | 73 +++++++++++++++++++++++++++++-------- templates/htmlshim.hamlet | 2 +- 3 files changed, 80 insertions(+), 20 deletions(-) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 06909fd531..50add37354 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -23,10 +23,14 @@ import Yesod.Static import Text.Hamlet import Network.Socket (PortNumber) import Text.Blaze.Renderer.String +import Data.Text + +thisThread :: String +thisThread = "WebApp" data WebApp = WebApp { daemonStatus :: DaemonStatusHandle - , secretToken :: String + , secretToken :: Text , baseTitle :: String , getStatic :: Static } @@ -46,6 +50,16 @@ instance Yesod WebApp where webapp <- getYesod hamletToRepHtml $(hamletFile $ hamletTemplate "default-layout") + {- Require an auth token be set when accessing any (non-static route) -} + isAuthorized _ _ = checkAuthToken secretToken + + {- Add the auth token to every url generated, except static subsite + - urls (which can show up in Permission Denied pages). -} + joinPath = insertAuthToken secretToken excludeStatic + where + excludeStatic [] = True + excludeStatic (p:_) = p /= "static" + getHomeR :: Handler RepHtml getHomeR = defaultLayout $ do [whamlet|Hello, World<p><a href=@{ConfigR}>config|] @@ -75,14 +89,16 @@ mkWebApp st dstatus = do token <- genRandomToken return $ WebApp { daemonStatus = dstatus - , secretToken = token + , secretToken = pack token , baseTitle = reldir , getStatic = $(embed "static") } -{- Creates a html shim file that's used to redirect into the webapp. -} +{- Creates a html shim file that's used to redirect into the webapp, + - to avoid exposing the secretToken when launching the web browser. -} writeHtmlShim :: WebApp -> PortNumber -> Annex () writeHtmlShim webapp port = do + liftIO $ debug thisThread ["running on port", show port] htmlshim <- fromRepo gitAnnexHtmlShim liftIO $ viaTmp go htmlshim $ genHtmlShim webapp port where @@ -96,4 +112,5 @@ writeHtmlShim webapp port = do genHtmlShim :: WebApp -> PortNumber -> String genHtmlShim webapp port = renderHtml $(shamletFile $ hamletTemplate "htmlshim") where - url = "http://localhost:" ++ show port ++ "/?" ++ secretToken webapp + url = "http://localhost:" ++ show port ++ + "/?auth=" ++ unpack (secretToken webapp) diff --git a/Utility/WebApp.hs b/Utility/WebApp.hs index cded83229e..fb82c20507 100644 --- a/Utility/WebApp.hs +++ b/Utility/WebApp.hs @@ -1,30 +1,37 @@ -{- WAI webapp +{- Yesod webapp - - Copyright 2012 Joey Hess <joey@kitenet.net> - - Licensed under the GNU GPL version 3 or higher. -} -{-# LANGUAGE OverloadedStrings, CPP #-} +{-# LANGUAGE OverloadedStrings, CPP, RankNTypes #-} module Utility.WebApp where import Common -import Network.Wai +import Yesod +import qualified Network.Wai as Wai import Network.Wai.Handler.Warp import Network.Wai.Logger import Control.Monad.IO.Class import Network.HTTP.Types import System.Log.Logger import Data.ByteString.Lazy.UTF8 -import Data.ByteString.Lazy -import Data.CaseInsensitive as CI +import qualified Data.CaseInsensitive as CI import Network.Socket import Control.Exception import Crypto.Random import Data.Digest.Pure.SHA -import Data.ByteString.Lazy as L +import qualified Data.ByteString.Lazy as L +import Data.AssocList +import qualified Data.Text as T +import qualified Data.Text.Encoding as TE +import Blaze.ByteString.Builder.Char.Utf8 (fromText) +import Blaze.ByteString.Builder (Builder) +import Data.Monoid +import Control.Arrow ((***)) localhost :: String localhost = "localhost" @@ -85,26 +92,26 @@ debugEnabled = do - Recommend only inserting this middleware when debugging is actually - enabled, as it's not optimised at all. -} -httpDebugLogger :: Middleware +httpDebugLogger :: Wai.Middleware httpDebugLogger waiApp req = do logRequest req waiApp req -logRequest :: MonadIO m => Request -> m () +logRequest :: MonadIO m => Wai.Request -> m () logRequest req = do liftIO $ debugM "WebApp" $ unwords - [ showSockAddr $ remoteHost req - , frombs $ requestMethod req - , frombs $ rawPathInfo req - --, show $ httpVersion req + [ showSockAddr $ Wai.remoteHost req + , frombs $ Wai.requestMethod req + , frombs $ Wai.rawPathInfo req + --, show $ Wai.httpVersion req --, frombs $ lookupRequestField "referer" req , frombs $ lookupRequestField "user-agent" req ] where - frombs v = toString $ fromChunks [v] + frombs v = toString $ L.fromChunks [v] -lookupRequestField :: CI Ascii -> Request -> Ascii -lookupRequestField k req = fromMaybe "" . lookup k $ requestHeaders req +lookupRequestField :: CI.CI Ascii -> Wai.Request -> Ascii +lookupRequestField k req = fromMaybe "" . lookup k $ Wai.requestHeaders req {- Generates a 512 byte random token, suitable to be used for an - authentication secret. -} @@ -115,3 +122,39 @@ genRandomToken = do case genBytes 512 g of Left e -> error $ "failed to generate secret token: " ++ show e Right (s, _) -> showDigest $ sha512 $ L.fromChunks [s] + +{- A Yesod isAuthorized method, which checks the auth cgi parameter + - against a token extracted from the Yesod application. -} +checkAuthToken :: forall t sub. (t -> T.Text) -> GHandler sub t AuthResult +checkAuthToken extractToken = do + webapp <- getYesod + req <- getRequest + let params = reqGetParams req + if lookupDef "" "auth" params == extractToken webapp + then return Authorized + else return AuthenticationRequired + +{- A Yesod joinPath method, which adds an auth cgi parameter to every + - url matching a predicate, containing a token extracted from the + - Yesod application. + - + - A typical predicate would exclude files under /static. + -} +insertAuthToken :: forall y. (y -> T.Text) + -> ([T.Text] -> Bool) + -> y + -> T.Text + -> [T.Text] + -> [(T.Text, T.Text)] + -> Builder +insertAuthToken extractToken predicate webapp root pathbits params = + fromText root `mappend` encodePath pathbits' encodedparams + where + pathbits' = if null pathbits then [T.empty] else pathbits + encodedparams = map (TE.encodeUtf8 *** go) params' + go "" = Nothing + go x = Just $ TE.encodeUtf8 x + authparam = (T.pack "auth", extractToken webapp) + params' + | predicate pathbits = authparam:params + | otherwise = params diff --git a/templates/htmlshim.hamlet b/templates/htmlshim.hamlet index c10042c999..073b69c1bd 100644 --- a/templates/htmlshim.hamlet +++ b/templates/htmlshim.hamlet @@ -4,4 +4,4 @@ $doctype 5 <meta http-equiv="refresh" content="0; URL=#{url}"> <body> <p> - <a href=#{url}">Starting webapp... + <a href="#{url}">Starting webapp... From 6cecc26206c4a539999b04664136c6f785211a41 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 05:13:27 -0400 Subject: [PATCH 108/331] update build deps --- Utility/WebApp.hs | 4 ++-- debian/control | 5 +++++ doc/install.mdwn | 8 +++++++- git-annex.cabal | 7 ++++--- 4 files changed, 18 insertions(+), 6 deletions(-) diff --git a/Utility/WebApp.hs b/Utility/WebApp.hs index fb82c20507..6936c6699e 100644 --- a/Utility/WebApp.hs +++ b/Utility/WebApp.hs @@ -25,7 +25,7 @@ import Control.Exception import Crypto.Random import Data.Digest.Pure.SHA import qualified Data.ByteString.Lazy as L -import Data.AssocList +import Data.List import qualified Data.Text as T import qualified Data.Text.Encoding as TE import Blaze.ByteString.Builder.Char.Utf8 (fromText) @@ -130,7 +130,7 @@ checkAuthToken extractToken = do webapp <- getYesod req <- getRequest let params = reqGetParams req - if lookupDef "" "auth" params == extractToken webapp + if lookup "auth" params == Just (extractToken webapp) then return Authorized else return AuthenticationRequired diff --git a/debian/control b/debian/control index 65c666cde4..58645259ef 100644 --- a/debian/control +++ b/debian/control @@ -24,12 +24,17 @@ Build-Depends: libghc-stm-dev (>= 2.3), libghc-dbus-dev, libghc-yesod-dev, + libghc-yesod-static-dev, libghc-case-insensitive-dev, libghc-http-types-dev, libghc-transformers-dev, libghc-wai-dev, libghc-wai-logger-dev, libghc-warp-dev, + libghc-blaze-builder-dev, + libghc-blaze-html-dev, + libghc-crypto-api-dev, + libghc-hamlet-dev, ikiwiki, perlmagick, git, diff --git a/doc/install.mdwn b/doc/install.mdwn index 619d5fa11d..38039fbb91 100644 --- a/doc/install.mdwn +++ b/doc/install.mdwn @@ -23,7 +23,8 @@ it yourself and [[manually_build_with_cabal|install/cabal]]. ## Installation by hand -To build and use git-annex, you will need: +This is not recommended, it's easier to let cabal pull in the many haskell +libraries. To build and use git-annex by hand, you will need: * Haskell stuff * [The Haskell Platform](http://haskell.org/platform/) (GHC 7.4 or newer) @@ -49,12 +50,17 @@ To build and use git-annex, you will need: (Linux only) * [dbus](http://hackage.haskell.org/package/dbus) * [yesod](http://hackage.haskell.org/package/yesod) + * [yesod-static](http://hackage.haskell.org/package/yesod-static) * [case-insensitive](http://hackage.haskell.org/package/case-insensitive) * [http-types](http://hackage.haskell.org/package/http-types) * [transformers](http://hackage.haskell.org/package/transformers) * [wai](http://hackage.haskell.org/package/wai) * [wai-logger](http://hackage.haskell.org/package/wai-logger) * [warp](http://hackage.haskell.org/package/warp) + * [blaze-builder](http://hackage.haskell.org/package/blaze-builder) + * [blaze-html](http://hackage.haskell.org/package/blaze-html) + * [crypto-api](http://hackage.haskell.org/package/crypto-api) + * [hamlet](http://hackage.haskell.org/package/hamlet) * Shell commands * [git](http://git-scm.com/) * [uuid](http://www.ossp.org/pkg/lib/uuid/) diff --git a/git-annex.cabal b/git-annex.cabal index 086df31d29..c7d9bf5707 100644 --- a/git-annex.cabal +++ b/git-annex.cabal @@ -46,8 +46,7 @@ Executable git-annex unix, containers, utf8-string, network, mtl, bytestring, old-locale, time, pcre-light, extensible-exceptions, dataenc, SHA, process, json, HTTP, base == 4.5.*, monad-control, transformers-base, lifted-base, - IfElse, text, QuickCheck >= 2.1, bloomfilter, edit-distance, process, - case-insensitive, http-types, transformers, wai, wai-logger, warp + IfElse, text, QuickCheck >= 2.1, bloomfilter, edit-distance, process -- Need to list these because they're generated from .hsc files. Other-Modules: Utility.Touch Utility.Mounts Include-Dirs: Utility @@ -75,7 +74,9 @@ Executable git-annex CPP-Options: -DWITH_DBUS if flag(Webapp) - Build-Depends: yesod + Build-Depends: yesod, yesod-static, case-insensitive, http-types, + transformers, wai, wai-logger, warp, blaze-builder, blaze-html, + crypto-api, hamlet CPP-Options: -DWITH_WEBAPP if (os(darwin)) From b89b8015677febfb905bf1fd50546dc981d83ded Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 05:20:52 -0400 Subject: [PATCH 109/331] update --- Assistant/Threads/WebApp.hs | 6 +++--- doc/design/assistant/webapp.mdwn | 2 +- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 50add37354..3e53828af8 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -38,9 +38,9 @@ data WebApp = WebApp staticFiles "static" mkYesod "WebApp" [parseRoutes| -/static StaticR Static getStatic / HomeR GET /config ConfigR GET +/static StaticR Static getStatic |] instance Yesod WebApp where @@ -62,12 +62,12 @@ instance Yesod WebApp where getHomeR :: Handler RepHtml getHomeR = defaultLayout $ do - [whamlet|Hello, World<p><a href=@{ConfigR}>config|] + [whamlet|Hello, World<p><a href="@{ConfigR}">config|] getConfigR :: Handler RepHtml getConfigR = defaultLayout $ do setTitle "configuration" - [whamlet|<a href=@{HomeR}>main|] + [whamlet|<a href="@{HomeR}">main|] webAppThread :: ThreadState -> DaemonStatusHandle -> IO () webAppThread st dstatus = do diff --git a/doc/design/assistant/webapp.mdwn b/doc/design/assistant/webapp.mdwn index cec766c579..0f6051d6d6 100644 --- a/doc/design/assistant/webapp.mdwn +++ b/doc/design/assistant/webapp.mdwn @@ -4,7 +4,7 @@ The webapp is a web server that displays a shiny interface. * Listen only to localhost. **done** * Instruct the user's web browser to open an url that contains a secret - token. This guards against other users on the same system. + token. This guards against other users on the same system. **done** * I would like to avoid passwords or other authentication methods, it's your local system. * Alternative for Linux at least would be to write a small program using From cccdb448749de70d1769ecef79605e4f389f9c5d Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 11:52:49 -0400 Subject: [PATCH 110/331] git annex webapp --force forces a restart of the daemon Useful for testing.. --- Command/WebApp.hs | 16 ++++++++++++---- Utility/Daemon.hs | 2 +- Utility/WebApp.hs | 1 - 3 files changed, 13 insertions(+), 6 deletions(-) diff --git a/Command/WebApp.hs b/Command/WebApp.hs index 0e01a07cd3..e94338a2fd 100644 --- a/Command/WebApp.hs +++ b/Command/WebApp.hs @@ -11,7 +11,7 @@ import Common.Annex import Command import Assistant import Utility.WebApp -import Utility.Daemon +import Utility.Daemon (checkDaemon) import qualified Annex import Control.Concurrent @@ -25,9 +25,17 @@ seek = [withNothing start] start :: CommandStart start = notBareRepo $ do - r <- checkpid - when (r == Nothing) $ - startassistant + ifM (Annex.getState Annex.force) + ( do + stopDaemon + liftIO . catchMaybeIO . removeFile + =<< fromRepo gitAnnexPidFile + startassistant + , do + r <- checkpid + when (r == Nothing) $ + startassistant + ) f <- liftIO . absPath =<< fromRepo gitAnnexHtmlShim let url = "file://" ++ f ifM (liftIO $ runBrowser url) diff --git a/Utility/Daemon.hs b/Utility/Daemon.hs index 8aa70d155c..3386ea4434 100644 --- a/Utility/Daemon.hs +++ b/Utility/Daemon.hs @@ -84,7 +84,7 @@ checkDaemon pidfile = do | otherwise = error $ "stale pid in " ++ pidfile ++ " (got " ++ show pid' ++ - "; expected" ++ show pid ++ " )" + "; expected " ++ show pid ++ " )" {- Stops the daemon, safely. -} stopDaemon :: FilePath -> IO () diff --git a/Utility/WebApp.hs b/Utility/WebApp.hs index 6936c6699e..8a1887678a 100644 --- a/Utility/WebApp.hs +++ b/Utility/WebApp.hs @@ -25,7 +25,6 @@ import Control.Exception import Crypto.Random import Data.Digest.Pure.SHA import qualified Data.ByteString.Lazy as L -import Data.List import qualified Data.Text as T import qualified Data.Text.Encoding as TE import Blaze.ByteString.Builder.Char.Utf8 (fromText) From a453be4195c36d8214ab44eafbb403ed55bc1d87 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 12:10:53 -0400 Subject: [PATCH 111/331] disable client session cookie --- Assistant/Threads/WebApp.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 3e53828af8..6e2296d5c1 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -60,6 +60,9 @@ instance Yesod WebApp where excludeStatic [] = True excludeStatic (p:_) = p /= "static" + {- Sessions are overkill for a local webapp with 1 user. -} + makeSessionBackend _ = return Nothing + getHomeR :: Handler RepHtml getHomeR = defaultLayout $ do [whamlet|Hello, World<p><a href="@{ConfigR}">config|] From 3c117685ebaceb1b33ba2058255ef55518a0f850 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 12:17:28 -0400 Subject: [PATCH 112/331] on second thought, let's use --restart rather than --force --force could enable other, unwanted behavior --- Command/WebApp.hs | 22 +++++++++++++--------- 1 file changed, 13 insertions(+), 9 deletions(-) diff --git a/Command/WebApp.hs b/Command/WebApp.hs index e94338a2fd..3730e14198 100644 --- a/Command/WebApp.hs +++ b/Command/WebApp.hs @@ -13,29 +13,33 @@ import Assistant import Utility.WebApp import Utility.Daemon (checkDaemon) import qualified Annex +import Option import Control.Concurrent import System.Posix.Process def :: [Command] -def = [command "webapp" paramNothing seek "launch webapp"] +def = [withOptions [restartOption] $ + command "webapp" paramNothing seek "launch webapp"] + +restartOption :: Option +restartOption = Option.flag [] "restart" "restart the assistant daemon" seek :: [CommandSeek] -seek = [withNothing start] +seek = [withFlag restartOption $ \restart -> withNothing $ start restart] -start :: CommandStart -start = notBareRepo $ do - ifM (Annex.getState Annex.force) - ( do +start :: Bool -> CommandStart +start restart = notBareRepo $ do + if restart + then do stopDaemon - liftIO . catchMaybeIO . removeFile + void $ liftIO . catchMaybeIO . removeFile =<< fromRepo gitAnnexPidFile startassistant - , do + else do r <- checkpid when (r == Nothing) $ startassistant - ) f <- liftIO . absPath =<< fromRepo gitAnnexHtmlShim let url = "file://" ++ f ifM (liftIO $ runBrowser url) From 95f4b192f0accbdaaa4e5c985b4e1c1a17b8aec7 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 12:41:20 -0400 Subject: [PATCH 113/331] on second thought, the session cookie is still useful to support setMessage --- Assistant/Threads/WebApp.hs | 3 +-- Utility/WebApp.hs | 15 ++++++++++++++- 2 files changed, 15 insertions(+), 3 deletions(-) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 6e2296d5c1..d663b0cd52 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -60,8 +60,7 @@ instance Yesod WebApp where excludeStatic [] = True excludeStatic (p:_) = p /= "static" - {- Sessions are overkill for a local webapp with 1 user. -} - makeSessionBackend _ = return Nothing + makeSessionBackend = webAppSessionBackend getHomeR :: Handler RepHtml getHomeR = defaultLayout $ do diff --git a/Utility/WebApp.hs b/Utility/WebApp.hs index 8a1887678a..23e00ba62a 100644 --- a/Utility/WebApp.hs +++ b/Utility/WebApp.hs @@ -24,6 +24,7 @@ import Network.Socket import Control.Exception import Crypto.Random import Data.Digest.Pure.SHA +import qualified Web.ClientSession as CS import qualified Data.ByteString.Lazy as L import qualified Data.Text as T import qualified Data.Text.Encoding as TE @@ -112,7 +113,19 @@ logRequest req = do lookupRequestField :: CI.CI Ascii -> Wai.Request -> Ascii lookupRequestField k req = fromMaybe "" . lookup k $ Wai.requestHeaders req -{- Generates a 512 byte random token, suitable to be used for an +{- Rather than storing a session key on disk, use a random key + - that will only be valid for this run of the webapp. -} +webAppSessionBackend :: Yesod y => y -> IO (Maybe (SessionBackend y)) +webAppSessionBackend _ = do + g <- newGenIO :: IO SystemRandom + case genBytes 96 g of + Left e -> error $ "failed to generate random key: " ++ show e + Right (s, _) -> case CS.initKey s of + Left e -> error $ "failed to initialize key: " ++ show e + Right key -> return $ Just $ + clientSessionBackend key 120 + +{- Generates a random sha512 string, suitable to be used for an - authentication secret. -} genRandomToken :: IO String genRandomToken = do From 2f775ef3e3aaea9ab15f99db3a48390a903919ae Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 12:59:40 -0400 Subject: [PATCH 114/331] fix OSX open call --- Utility/WebApp.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Utility/WebApp.hs b/Utility/WebApp.hs index 23e00ba62a..517251a7a9 100644 --- a/Utility/WebApp.hs +++ b/Utility/WebApp.hs @@ -42,7 +42,7 @@ localhost = "localhost" runBrowser :: String -> IO Bool runBrowser url = boolSystem cmd [Param url] where -#if MAC +#if OSX cmd = "open" #else cmd = "xdg-open" From 8e49206af5bed49999c0b2d55b17cd32b1ef666e Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 13:02:00 -0400 Subject: [PATCH 115/331] fix normal build to include OPTFLAGS --- Makefile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Makefile b/Makefile index 9f312dc49c..4a74e712f1 100644 --- a/Makefile +++ b/Makefile @@ -27,7 +27,7 @@ endif endif PREFIX=/usr -GHCFLAGS=-O2 $(BASEFLAGS) $(FEATURES) +GHCFLAGS=-O2 $(BASEFLAGS) $(FEATURES) $(OPTFLAGS) ifdef PROFILE GHCFLAGS=-prof -auto-all -rtsopts -caf-all -fforce-recomp $(BASEFLAGS) $(FEATURES) $(OPTFLAGS) From 78002d4976ded84cd2b0edbd78f9bb27371befe7 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 13:05:52 -0400 Subject: [PATCH 116/331] only enable dbus on linux for now --- git-annex.cabal | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/git-annex.cabal b/git-annex.cabal index c7d9bf5707..3aa32ba5a0 100644 --- a/git-annex.cabal +++ b/git-annex.cabal @@ -69,7 +69,7 @@ Executable git-annex if (! os(windows)) CPP-Options: -DWITH_KQUEUE - if flag(Dbus) + if os(linux) && flag(Dbus) Build-Depends: dbus CPP-Options: -DWITH_DBUS @@ -79,7 +79,7 @@ Executable git-annex crypto-api, hamlet CPP-Options: -DWITH_WEBAPP - if (os(darwin)) + if os(darwin) CPP-Options: -DOSX Test-Suite test From df00c6166c55e7287914706fed9323ed3bf3ac1a Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 13:13:23 -0400 Subject: [PATCH 117/331] update deps Note that here I don't need blaze-markup for cabal to succeed, but Jimmy reports he does. Seems like Text.Blaze.Renderer.String moved from blaze to blaze-markup in some version. --- debian/control | 2 ++ doc/install.mdwn | 2 ++ git-annex.cabal | 2 +- 3 files changed, 5 insertions(+), 1 deletion(-) diff --git a/debian/control b/debian/control index 58645259ef..1e7cb19e2c 100644 --- a/debian/control +++ b/debian/control @@ -33,8 +33,10 @@ Build-Depends: libghc-warp-dev, libghc-blaze-builder-dev, libghc-blaze-html-dev, + libghc-blaze-markup-dev, libghc-crypto-api-dev, libghc-hamlet-dev, + libghc-clientsession-dev, ikiwiki, perlmagick, git, diff --git a/doc/install.mdwn b/doc/install.mdwn index 38039fbb91..e529952611 100644 --- a/doc/install.mdwn +++ b/doc/install.mdwn @@ -59,8 +59,10 @@ libraries. To build and use git-annex by hand, you will need: * [warp](http://hackage.haskell.org/package/warp) * [blaze-builder](http://hackage.haskell.org/package/blaze-builder) * [blaze-html](http://hackage.haskell.org/package/blaze-html) + * [blaze-markup](http://hackage.haskell.org/package/blaze-markup) * [crypto-api](http://hackage.haskell.org/package/crypto-api) * [hamlet](http://hackage.haskell.org/package/hamlet) + * [clientsession](http://hackage.haskell.org/package/clientsession) * Shell commands * [git](http://git-scm.com/) * [uuid](http://www.ossp.org/pkg/lib/uuid/) diff --git a/git-annex.cabal b/git-annex.cabal index 3aa32ba5a0..aa71dacb6f 100644 --- a/git-annex.cabal +++ b/git-annex.cabal @@ -76,7 +76,7 @@ Executable git-annex if flag(Webapp) Build-Depends: yesod, yesod-static, case-insensitive, http-types, transformers, wai, wai-logger, warp, blaze-builder, blaze-html, - crypto-api, hamlet + blaze-markup, crypto-api, hamlet, clientsession CPP-Options: -DWITH_WEBAPP if os(darwin) From 860415aa5b1d1c367a8a4810ef29e4a9417b0989 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 14:26:35 -0400 Subject: [PATCH 118/331] webapp: check that the shim exists, and restart the assistant if not --- Command/WebApp.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/Command/WebApp.hs b/Command/WebApp.hs index 3730e14198..6533634400 100644 --- a/Command/WebApp.hs +++ b/Command/WebApp.hs @@ -30,7 +30,9 @@ seek = [withFlag restartOption $ \restart -> withNothing $ start restart] start :: Bool -> CommandStart start restart = notBareRepo $ do - if restart + f <- liftIO . absPath =<< fromRepo gitAnnexHtmlShim + ok <- liftIO $ doesFileExist f + if restart || not ok then do stopDaemon void $ liftIO . catchMaybeIO . removeFile @@ -40,7 +42,6 @@ start restart = notBareRepo $ do r <- checkpid when (r == Nothing) $ startassistant - f <- liftIO . absPath =<< fromRepo gitAnnexHtmlShim let url = "file://" ++ f ifM (liftIO $ runBrowser url) ( stop From e79198aacbb7891b0b7a4d156160a1524038e18c Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 15:28:08 -0400 Subject: [PATCH 119/331] when starting the assistant, wait for it to create the shim file, as well as the pid file fixes a possible race --- Command/WebApp.hs | 39 +++++++++++++++++---------------------- 1 file changed, 17 insertions(+), 22 deletions(-) diff --git a/Command/WebApp.hs b/Command/WebApp.hs index 6533634400..5fcaad6fda 100644 --- a/Command/WebApp.hs +++ b/Command/WebApp.hs @@ -31,39 +31,34 @@ seek = [withFlag restartOption $ \restart -> withNothing $ start restart] start :: Bool -> CommandStart start restart = notBareRepo $ do f <- liftIO . absPath =<< fromRepo gitAnnexHtmlShim - ok <- liftIO $ doesFileExist f - if restart || not ok + if restart then do stopDaemon - void $ liftIO . catchMaybeIO . removeFile - =<< fromRepo gitAnnexPidFile - startassistant - else do - r <- checkpid - when (r == Nothing) $ - startassistant + nuke =<< fromRepo gitAnnexPidFile + startassistant f + else unlessM (checkpid f) $ + startassistant f let url = "file://" ++ f ifM (liftIO $ runBrowser url) ( stop , error $ "failed to start web browser on url " ++ url ) where - checkpid = do + nuke f = void $ liftIO $ catchMaybeIO $ removeFile f + checkpid f = do pidfile <- fromRepo gitAnnexPidFile - liftIO $ checkDaemon pidfile - startassistant = do + liftIO $ + doesFileExist f <&&> (isJust <$> checkDaemon pidfile) + startassistant f = do + nuke f {- Fork a separate process to run the assistant, - with a copy of the Annex state. -} state <- Annex.getState id liftIO $ void $ forkProcess $ Annex.eval state $ startDaemon True False - waitdaemon (100 :: Int) - waitdaemon 0 = error "failed to start git-annex assistant" - waitdaemon n = do - r <- checkpid - case r of - Just _ -> return () - Nothing -> do - -- wait 0.1 seconds before retry - liftIO $ threadDelay 100000 - waitdaemon (n - 1) + waitdaemon f (100 :: Int) + waitdaemon _ 0 = error "failed to start git-annex assistant" + waitdaemon f n = unlessM (checkpid f) $ do + -- wait 0.1 seconds before retry + liftIO $ threadDelay 100000 + waitdaemon f (n - 1) From 9fd03c65f9ebee437317a21e27afb600d9815209 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 17:56:24 -0400 Subject: [PATCH 120/331] webapp now does long polling The webapp is now a constantly updating clock! I accomplished this amazing feat using "long polling", with some jquery and a little custom java script. There are more modern techniques, but this one works everywhere. --- Assistant/Threads/WebApp.hs | 20 +++++++++++++++++++- Utility/Yesod.hs | 4 ++++ templates/default-layout.hamlet | 1 - templates/longpolling.julius | 25 +++++++++++++++++++++++++ templates/poll.hamlet | 2 ++ 5 files changed, 50 insertions(+), 2 deletions(-) create mode 100644 templates/longpolling.julius create mode 100644 templates/poll.hamlet diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index d663b0cd52..2d78609e85 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -21,9 +21,11 @@ import Git import Yesod import Yesod.Static import Text.Hamlet +import Text.Julius import Network.Socket (PortNumber) import Text.Blaze.Renderer.String import Data.Text +import Data.Time.Clock thisThread :: String thisThread = "WebApp" @@ -39,6 +41,7 @@ staticFiles "static" mkYesod "WebApp" [parseRoutes| / HomeR GET +/poll PollR GET /config ConfigR GET /static StaticR Static getStatic |] @@ -61,10 +64,25 @@ instance Yesod WebApp where excludeStatic (p:_) = p /= "static" makeSessionBackend = webAppSessionBackend + jsLoader _ = BottomOfHeadBlocking getHomeR :: Handler RepHtml getHomeR = defaultLayout $ do - [whamlet|Hello, World<p><a href="@{ConfigR}">config|] + [whamlet|<div id="poll">Starting ...|] + addScriptRemote "http://ajax.googleapis.com/ajax/libs/jquery/1.6.2/jquery.min.js" + toWidgetBody $(juliusFile $ juliusTemplate "longpolling") + [whamlet|<p><a href="@{ConfigR}">config|] + +{- Called by client to poll for a new webapp status display. + - + - Should block until the status has changed, and then return a div + - containing the new status, which will be inserted into the calling page. + -} +getPollR :: Handler RepHtml +getPollR = do + webapp <- getYesod + time <- show <$> liftIO getCurrentTime + hamletToRepHtml $(hamletFile $ hamletTemplate "poll") getConfigR :: Handler RepHtml getConfigR = defaultLayout $ do diff --git a/Utility/Yesod.hs b/Utility/Yesod.hs index 05f684490a..a0dd3bdd2f 100644 --- a/Utility/Yesod.hs +++ b/Utility/Yesod.hs @@ -16,3 +16,7 @@ template f = "templates" </> f {- A hamlet template file. -} hamletTemplate :: FilePath -> FilePath hamletTemplate f = template f ++ ".hamlet" + +{- A julius template file. -} +juliusTemplate :: FilePath -> FilePath +juliusTemplate f = template f ++ ".julius" diff --git a/templates/default-layout.hamlet b/templates/default-layout.hamlet index e07addc8e0..bd16969f93 100644 --- a/templates/default-layout.hamlet +++ b/templates/default-layout.hamlet @@ -3,7 +3,6 @@ $doctype 5 <head> <title>#{baseTitle webapp} #{pageTitle page} <link rel="icon" href=@{StaticR favicon_ico} type="image/x-icon"> - ^{pageHead page} <body> $maybe msg <- mmsg diff --git a/templates/longpolling.julius b/templates/longpolling.julius new file mode 100644 index 0000000000..38ecbc77d2 --- /dev/null +++ b/templates/longpolling.julius @@ -0,0 +1,25 @@ +// Uses long-polling to update a div with id=poll. +// The PollR route should return a new div, also with id=poll. + +(function( $ ) { + +$.LongPoll = (function() { + return { + send : function() { + $.ajax({ + 'url': '@{PollR}', + 'dataType': 'html', + 'success': function(data, status, jqxhr) { + $('#poll').replaceWith(data); + setTimeout($.LongPoll.send, 3000); + }, + }); + } + } +}()); + +$(document).bind('ready.app', function() { + setTimeout($.LongPoll.send, 40); +}); + +})( jQuery ); diff --git a/templates/poll.hamlet b/templates/poll.hamlet new file mode 100644 index 0000000000..fcdd705b65 --- /dev/null +++ b/templates/poll.hamlet @@ -0,0 +1,2 @@ +<div id="poll"> + polled at #{time} From 9b2eec2e7af34e107bcb438a501286996fe0eb41 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 18:04:09 -0400 Subject: [PATCH 121/331] increase timeout from 10 to 100 seconds I've seen 10 be too short under load. --- Command/WebApp.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Command/WebApp.hs b/Command/WebApp.hs index 5fcaad6fda..7d0a310d40 100644 --- a/Command/WebApp.hs +++ b/Command/WebApp.hs @@ -56,7 +56,7 @@ start restart = notBareRepo $ do state <- Annex.getState id liftIO $ void $ forkProcess $ Annex.eval state $ startDaemon True False - waitdaemon f (100 :: Int) + waitdaemon f (1000 :: Int) waitdaemon _ 0 = error "failed to start git-annex assistant" waitdaemon f n = unlessM (checkpid f) $ do -- wait 0.1 seconds before retry From f5ef46d01eb7bbaac45eec162267bcbf2500d511 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 21:03:46 -0400 Subject: [PATCH 122/331] cleaned up refreshing code into a widget Very happy to have a reusable autoUpdate widget that can make any Yesod widget automatically refresh! Also added support for non-javascript browsers, falling back to meta refresh. Also, the home page is now rendered with the webapp status on it, before any refreshing is done. --- Assistant/Threads/WebApp.hs | 58 ++++++++++++++++++++---- templates/longpolling.julius | 16 ++++--- templates/metarefresh.hamlet | 2 + templates/{poll.hamlet => status.hamlet} | 2 +- 4 files changed, 62 insertions(+), 16 deletions(-) create mode 100644 templates/metarefresh.hamlet rename templates/{poll.hamlet => status.hamlet} (51%) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 2d78609e85..0e1f9ba95f 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -41,7 +41,7 @@ staticFiles "static" mkYesod "WebApp" [parseRoutes| / HomeR GET -/poll PollR GET +/status StatusR GET /config ConfigR GET /static StaticR Static getStatic |] @@ -66,23 +66,63 @@ instance Yesod WebApp where makeSessionBackend = webAppSessionBackend jsLoader _ = BottomOfHeadBlocking +{- Add to any widget to make it auto-update. + - + - The widget should have a html element with id=poll, which will be + - replaced when it's updated. + - + - Updating is done by getting html from the gethtml route. + - Or, the home route is used if the whole page has to be refreshed to + - update. + - + - ms_delay is how long to delay between updates. + - ms_startdelay is how long to delay before updating the widget at the + - state. + -} +autoUpdate :: Text -> Route WebApp -> Route WebApp -> Int -> Int -> Widget +autoUpdate poll gethtml home ms_delay ms_startdelay = do + {- Fallback refreshing is provided for non-javascript browsers. -} + let delayseconds = show $ ms_to_seconds ms_delay + toWidgetHead $(hamletFile $ hamletTemplate "metarefresh") + + {- Use long polling to update the status display. -} + let delay = show ms_delay + let startdelay = show ms_startdelay + addScriptRemote "http://ajax.googleapis.com/ajax/libs/jquery/1.6.2/jquery.min.js" + toWidgetHead $(juliusFile $ juliusTemplate "longpolling") + where + ms_to_seconds :: Int -> Int + ms_to_seconds ms = ceiling ((fromIntegral ms :: Double) / 1000) + +{- Continually updating status display. -} +statusDisplay :: Widget +statusDisplay = do + webapp <- lift getYesod + time <- show <$> liftIO getCurrentTime + + poll <- lift newIdent + $(whamletFile $ hamletTemplate "status") + + autoUpdate poll StatusR HomeR (3000 :: Int) (40 :: Int) + getHomeR :: Handler RepHtml getHomeR = defaultLayout $ do - [whamlet|<div id="poll">Starting ...|] - addScriptRemote "http://ajax.googleapis.com/ajax/libs/jquery/1.6.2/jquery.min.js" - toWidgetBody $(juliusFile $ juliusTemplate "longpolling") + statusDisplay [whamlet|<p><a href="@{ConfigR}">config|] {- Called by client to poll for a new webapp status display. - - Should block until the status has changed, and then return a div - containing the new status, which will be inserted into the calling page. + - + - Note that the head of the widget is not included, only its + - body is. To get the widget head content, the widget is also + - inserted onto the getHomeR page. -} -getPollR :: Handler RepHtml -getPollR = do - webapp <- getYesod - time <- show <$> liftIO getCurrentTime - hamletToRepHtml $(hamletFile $ hamletTemplate "poll") +getStatusR :: Handler RepHtml +getStatusR = do + page <- widgetToPageContent statusDisplay + hamletToRepHtml $ [hamlet|^{pageBody page}|] getConfigR :: Handler RepHtml getConfigR = defaultLayout $ do diff --git a/templates/longpolling.julius b/templates/longpolling.julius index 38ecbc77d2..26356f5e93 100644 --- a/templates/longpolling.julius +++ b/templates/longpolling.julius @@ -1,5 +1,9 @@ -// Uses long-polling to update a div with id=poll. -// The PollR route should return a new div, also with id=poll. + +// Uses long-polling to update a div with id=#{poll} +// The gethtml route should return a new div, with the same id. +// +// Maximum update frequency is controlled by #{startdelay} +// and #{delay}, both in milliseconds. (function( $ ) { @@ -7,11 +11,11 @@ $.LongPoll = (function() { return { send : function() { $.ajax({ - 'url': '@{PollR}', + 'url': '@{gethtml}', 'dataType': 'html', 'success': function(data, status, jqxhr) { - $('#poll').replaceWith(data); - setTimeout($.LongPoll.send, 3000); + $('##{poll}').replaceWith(data); + setTimeout($.LongPoll.send, #{delay}); }, }); } @@ -19,7 +23,7 @@ $.LongPoll = (function() { }()); $(document).bind('ready.app', function() { - setTimeout($.LongPoll.send, 40); + setTimeout($.LongPoll.send, #{startdelay}); }); })( jQuery ); diff --git a/templates/metarefresh.hamlet b/templates/metarefresh.hamlet new file mode 100644 index 0000000000..be22aa8992 --- /dev/null +++ b/templates/metarefresh.hamlet @@ -0,0 +1,2 @@ +<noscript> + <meta http-equiv="refresh" content="#{delayseconds}; URL=@{home}"> diff --git a/templates/poll.hamlet b/templates/status.hamlet similarity index 51% rename from templates/poll.hamlet rename to templates/status.hamlet index fcdd705b65..1f975b35f4 100644 --- a/templates/poll.hamlet +++ b/templates/status.hamlet @@ -1,2 +1,2 @@ -<div id="poll"> +<div id="#{poll}"> polled at #{time} From 77c3bf7f887933cf953d5983b849796ea075bfca Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 21:51:47 -0400 Subject: [PATCH 123/331] update thread list --- Assistant.hs | 25 ++++++++++++++----------- 1 file changed, 14 insertions(+), 11 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index c867529fdf..b539b27bc4 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -10,7 +10,7 @@ - The initial thread run, double forks to background, starts other - threads, and then stops, waiting for them to terminate, - or for a ctrl-c. - - Thread 2: watcher + - Thread 2: Watcher - Notices new files, and calls handlers for events, queuing changes. - Thread 3: inotify internal - Used by haskell inotify library to ensure inotify event buffer is @@ -19,43 +19,46 @@ - Scans the tree and registers inotify watches for each directory. - A MVar lock is used to prevent other inotify handlers from running - until this is complete. - - Thread 5: committer + - Thread 5: Committer - Waits for changes to occur, and runs the git queue to update its - index, then commits. Also queues Transfer events to send added - files to other remotes. - - Thread 6: pusher + - Thread 6: Pusher - Waits for commits to be made, and pushes updated branches to remotes, - in parallel. (Forks a process for each git push.) - - Thread 7: push retryer + - Thread 7: PushRetryer - Runs every 30 minutes when there are failed pushes, and retries - them. - - Thread 8: merger + - Thread 8: Merger - Waits for pushes to be received from remotes, and merges the - updated branches into the current branch. - (This uses inotify on .git/refs/heads, so there are additional - inotify threads associated with it, too.) - - Thread 9: transfer watcher + - Thread 9: TransferWatcher - Watches for transfer information files being created and removed, - and maintains the DaemonStatus currentTransfers map. - (This uses inotify on .git/annex/transfer/, so there are - additional inotify threads associated with it, too.) - - Thread 10: transferrer + - Thread 10: Transferrer - Waits for Transfers to be queued and does them. - - Thread 11: status logger + - Thread 11: StatusLogger - Wakes up periodically and records the daemon's status to disk. - - Thread 12: sanity checker + - Thread 12: SanityChecker - Wakes up periodically (rarely) and does sanity checks. - - Thread 13: mount watcher + - Thread 13: MountWatcher - Either uses dbus to watch for drive mount events, or, when - there's no dbus, polls to find newly mounted filesystems. - Once a filesystem that contains a remote is mounted, updates - state about that remote, pulls from it, and queues a push to it, - as well as an update, and queues it onto the - ConnectedRemoteChan - - Thread 14: transfer scanner + - Thread 14: TransferScanner - Does potentially expensive checks to find data that needs to be - transferred from or to remotes, and queues Transfers. - Uses the ScanRemotes map. + - Thread 15: WebApp + - Spawns more threads as necessary to handle clients. + - Displays the DaemonStatus. - - ThreadState: (MVar) - The Annex state is stored here, which allows resuscitating the From e40f94cbcdcacebb8215ee16b5c575ca865ad810 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 21:51:56 -0400 Subject: [PATCH 124/331] add threadState member, will need this later to access the daemonStatus --- Assistant/Threads/WebApp.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 0e1f9ba95f..593c43eae3 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -31,7 +31,8 @@ thisThread :: String thisThread = "WebApp" data WebApp = WebApp - { daemonStatus :: DaemonStatusHandle + { threadState :: ThreadState + , daemonStatus :: DaemonStatusHandle , secretToken :: Text , baseTitle :: String , getStatic :: Static @@ -148,7 +149,8 @@ mkWebApp st dstatus = do else dir token <- genRandomToken return $ WebApp - { daemonStatus = dstatus + { threadState = st + , daemonStatus = dstatus , secretToken = pack token , baseTitle = reldir , getStatic = $(embed "static") From 615dc09ffc321ce04d3014b3a9f07e7f04b69c80 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 22:54:31 -0400 Subject: [PATCH 125/331] use widgetFile --- Assistant/Threads/WebApp.hs | 5 ++--- Utility/Yesod.hs | 17 ++++++----------- 2 files changed, 8 insertions(+), 14 deletions(-) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 593c43eae3..addb49f79d 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -21,7 +21,6 @@ import Git import Yesod import Yesod.Static import Text.Hamlet -import Text.Julius import Network.Socket (PortNumber) import Text.Blaze.Renderer.String import Data.Text @@ -90,7 +89,7 @@ autoUpdate poll gethtml home ms_delay ms_startdelay = do let delay = show ms_delay let startdelay = show ms_startdelay addScriptRemote "http://ajax.googleapis.com/ajax/libs/jquery/1.6.2/jquery.min.js" - toWidgetHead $(juliusFile $ juliusTemplate "longpolling") + $(widgetFile "longpolling") where ms_to_seconds :: Int -> Int ms_to_seconds ms = ceiling ((fromIntegral ms :: Double) / 1000) @@ -102,7 +101,7 @@ statusDisplay = do time <- show <$> liftIO getCurrentTime poll <- lift newIdent - $(whamletFile $ hamletTemplate "status") + $(widgetFile "status") autoUpdate poll StatusR HomeR (3000 :: Int) (40 :: Int) diff --git a/Utility/Yesod.hs b/Utility/Yesod.hs index a0dd3bdd2f..2d2c6c3436 100644 --- a/Utility/Yesod.hs +++ b/Utility/Yesod.hs @@ -1,4 +1,4 @@ -{- Yesod stuff +{- Yesod stuff, that's typically found in the scaffolded site. - - Copyright 2012 Joey Hess <joey@kitenet.net> - @@ -7,16 +7,11 @@ module Utility.Yesod where -import System.FilePath +import Yesod.Default.Util +import Language.Haskell.TH.Syntax -{- Filename of a template, in the templates/ directory. -} -template :: FilePath -> FilePath -template f = "templates" </> f +widgetFile :: String -> Q Exp +widgetFile = widgetFileNoReload -{- A hamlet template file. -} hamletTemplate :: FilePath -> FilePath -hamletTemplate f = template f ++ ".hamlet" - -{- A julius template file. -} -juliusTemplate :: FilePath -> FilePath -juliusTemplate f = template f ++ ".julius" +hamletTemplate f = globFile "hamlet" f From ff4ab6d6da60ecf9081f743fc13b5785ebe79d12 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 22:59:14 -0400 Subject: [PATCH 126/331] work around GHC not knowing to rebuild files using template haskell when things they include change --- Makefile | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/Makefile b/Makefile index 4a74e712f1..a6fdab7ca7 100644 --- a/Makefile +++ b/Makefile @@ -6,6 +6,7 @@ FEATURES=-DWITH_ASSISTANT -DWITH_S3 -DWITH_WEBAPP bins=git-annex mans=git-annex.1 git-annex-shell.1 sources=Build/SysConfig.hs Utility/Touch.hs Utility/Mounts.hs +thfiles=Assistant/Threads/WebApp.hs all=$(bins) $(mans) docs OS:=$(shell uname | sed 's/[-_].*//') @@ -55,8 +56,13 @@ Build/SysConfig.hs: configure.hs Build/TestConfig.hs Build/Configure.hs %.hs: %.hsc hsc2hs $< +# Force GHC to rebuild template haskell files whenever includes +# change +$(thfiles): $(shell echo templates/* static/*) +$(thfiles): + touch $(thfiles) -git-annex: $(sources) $(clibs) +git-annex: $(sources) $(clibs) $(thfiles) $(GHCMAKE) $@ $(clibs) git-annex.1: doc/git-annex.mdwn From 1983ca2852461ca2082504dd22de07638030665b Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Thu, 26 Jul 2012 23:55:51 -0400 Subject: [PATCH 127/331] added jquery to static site Had to switch to toWaiAppPlain to avoid a seeming bug in toWaiApp; chromium only received a partial copy of jquery. Always the same length each time, which makes me think it's a bug in the compression, although a bug in the autohead middleware is also a possibility. Anyway, there's little need for compression for a local webapp. Not wasting time compressing things is probably a net gain. Similarly, I've not worried about minifying this yet. Although that would avoid bloating the git-annex binary quite so much. --- Assistant/Threads/WebApp.hs | 4 +- debian/copyright | 28 +- static/jquery.full.js | 8981 +++++++++++++++++++++++++++++++++++ 3 files changed, 9010 insertions(+), 3 deletions(-) create mode 100644 static/jquery.full.js diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index addb49f79d..f82a1fb6b9 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -88,7 +88,7 @@ autoUpdate poll gethtml home ms_delay ms_startdelay = do {- Use long polling to update the status display. -} let delay = show ms_delay let startdelay = show ms_startdelay - addScriptRemote "http://ajax.googleapis.com/ajax/libs/jquery/1.6.2/jquery.min.js" + addScript $ StaticR jquery_full_js $(widgetFile "longpolling") where ms_to_seconds :: Int -> Int @@ -132,7 +132,7 @@ getConfigR = defaultLayout $ do webAppThread :: ThreadState -> DaemonStatusHandle -> IO () webAppThread st dstatus = do webapp <- mkWebApp st dstatus - app <- toWaiApp webapp + app <- toWaiAppPlain webapp app' <- ifM debugEnabled ( return $ httpDebugLogger app , return app diff --git a/debian/copyright b/debian/copyright index 26a559cc51..72b6333671 100644 --- a/debian/copyright +++ b/debian/copyright @@ -24,8 +24,34 @@ License: BSD-3-clause Utility/libmounts.c in this package's source, or in /usr/share/common-licenses/BSD on Debian systems. -Files: doc/logo.png doc/logo_small.png doc/favicon.png +Files: doc/logo.png doc/logo_small.png */favicon.ico Copyright: 2007 Henrik Nyh <http://henrik.nyh.se/> 2010 Joey Hess <joey@kitenet.net> License: other Free to modify and redistribute with due credit, and obviously free to use. + +Files: static/jquery* +Copyright: © 2005-2011 by John Resig, Branden Aaron & Jörn Zaefferer + © 2011 The Dojo Foundation +License: MIT or GPL-2 + The full text of version 2 of the GPL is distributed in + /usr/share/common-licenses/GPL-2 on Debian systems. + . + Permission is hereby granted, free of charge, to any person obtaining + a copy of this software and associated documentation files (the + "Software"), to deal in the Software without restriction, including + without limitation the rights to use, copy, modify, merge, publish, + distribute, sublicense, and/or sell copies of the Software, and to + permit persons to whom the Software is furnished to do so, subject to + the following conditions: + . + The above copyright notice and this permission notice shall be + included in all copies or substantial portions of the Software. + . + THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, + EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF + MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND + NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE + LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION + OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION + WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. diff --git a/static/jquery.full.js b/static/jquery.full.js new file mode 100644 index 0000000000..f3201aacb6 --- /dev/null +++ b/static/jquery.full.js @@ -0,0 +1,8981 @@ +/*! + * jQuery JavaScript Library v1.6.2 + * http://jquery.com/ + * + * Copyright 2011, John Resig + * Dual licensed under the MIT or GPL Version 2 licenses. + * http://jquery.org/license + * + * Includes Sizzle.js + * http://sizzlejs.com/ + * Copyright 2011, The Dojo Foundation + * Released under the MIT, BSD, and GPL Licenses. + * + * Date: Thu Jun 30 14:16:56 2011 -0400 + */ +(function( window, undefined ) { + +// Use the correct document accordingly with window argument (sandbox) +var document = window.document, + navigator = window.navigator, + location = window.location; +var jQuery = (function() { + +// Define a local copy of jQuery +var jQuery = function( selector, context ) { + // The jQuery object is actually just the init constructor 'enhanced' + return new jQuery.fn.init( selector, context, rootjQuery ); + }, + + // Map over jQuery in case of overwrite + _jQuery = window.jQuery, + + // Map over the $ in case of overwrite + _$ = window.$, + + // A central reference to the root jQuery(document) + rootjQuery, + + // A simple way to check for HTML strings or ID strings + // (both of which we optimize for) + quickExpr = /^(?:[^<]*(<[\w\W]+>)[^>]*$|#([\w\-]*)$)/, + + // Check if a string has a non-whitespace character in it + rnotwhite = /\S/, + + // Used for trimming whitespace + trimLeft = /^\s+/, + trimRight = /\s+$/, + + // Check for digits + rdigit = /\d/, + + // Match a standalone tag + rsingleTag = /^<(\w+)\s*\/?>(?:<\/\1>)?$/, + + // JSON RegExp + rvalidchars = /^[\],:{}\s]*$/, + rvalidescape = /\\(?:["\\\/bfnrt]|u[0-9a-fA-F]{4})/g, + rvalidtokens = /"[^"\\\n\r]*"|true|false|null|-?\d+(?:\.\d*)?(?:[eE][+\-]?\d+)?/g, + rvalidbraces = /(?:^|:|,)(?:\s*\[)+/g, + + // Useragent RegExp + rwebkit = /(webkit)[ \/]([\w.]+)/, + ropera = /(opera)(?:.*version)?[ \/]([\w.]+)/, + rmsie = /(msie) ([\w.]+)/, + rmozilla = /(mozilla)(?:.*? rv:([\w.]+))?/, + + // Matches dashed string for camelizing + rdashAlpha = /-([a-z])/ig, + + // Used by jQuery.camelCase as callback to replace() + fcamelCase = function( all, letter ) { + return letter.toUpperCase(); + }, + + // Keep a UserAgent string for use with jQuery.browser + userAgent = navigator.userAgent, + + // For matching the engine and version of the browser + browserMatch, + + // The deferred used on DOM ready + readyList, + + // The ready event handler + DOMContentLoaded, + + // Save a reference to some core methods + toString = Object.prototype.toString, + hasOwn = Object.prototype.hasOwnProperty, + push = Array.prototype.push, + slice = Array.prototype.slice, + trim = String.prototype.trim, + indexOf = Array.prototype.indexOf, + + // [[Class]] -> type pairs + class2type = {}; + +jQuery.fn = jQuery.prototype = { + constructor: jQuery, + init: function( selector, context, rootjQuery ) { + var match, elem, ret, doc; + + // Handle $(""), $(null), or $(undefined) + if ( !selector ) { + return this; + } + + // Handle $(DOMElement) + if ( selector.nodeType ) { + this.context = this[0] = selector; + this.length = 1; + return this; + } + + // The body element only exists once, optimize finding it + if ( selector === "body" && !context && document.body ) { + this.context = document; + this[0] = document.body; + this.selector = selector; + this.length = 1; + return this; + } + + // Handle HTML strings + if ( typeof selector === "string" ) { + // Are we dealing with HTML string or an ID? + if ( selector.charAt(0) === "<" && selector.charAt( selector.length - 1 ) === ">" && selector.length >= 3 ) { + // Assume that strings that start and end with <> are HTML and skip the regex check + match = [ null, selector, null ]; + + } else { + match = quickExpr.exec( selector ); + } + + // Verify a match, and that no context was specified for #id + if ( match && (match[1] || !context) ) { + + // HANDLE: $(html) -> $(array) + if ( match[1] ) { + context = context instanceof jQuery ? context[0] : context; + doc = (context ? context.ownerDocument || context : document); + + // If a single string is passed in and it's a single tag + // just do a createElement and skip the rest + ret = rsingleTag.exec( selector ); + + if ( ret ) { + if ( jQuery.isPlainObject( context ) ) { + selector = [ document.createElement( ret[1] ) ]; + jQuery.fn.attr.call( selector, context, true ); + + } else { + selector = [ doc.createElement( ret[1] ) ]; + } + + } else { + ret = jQuery.buildFragment( [ match[1] ], [ doc ] ); + selector = (ret.cacheable ? jQuery.clone(ret.fragment) : ret.fragment).childNodes; + } + + return jQuery.merge( this, selector ); + + // HANDLE: $("#id") + } else { + elem = document.getElementById( match[2] ); + + // Check parentNode to catch when Blackberry 4.6 returns + // nodes that are no longer in the document #6963 + if ( elem && elem.parentNode ) { + // Handle the case where IE and Opera return items + // by name instead of ID + if ( elem.id !== match[2] ) { + return rootjQuery.find( selector ); + } + + // Otherwise, we inject the element directly into the jQuery object + this.length = 1; + this[0] = elem; + } + + this.context = document; + this.selector = selector; + return this; + } + + // HANDLE: $(expr, $(...)) + } else if ( !context || context.jquery ) { + return (context || rootjQuery).find( selector ); + + // HANDLE: $(expr, context) + // (which is just equivalent to: $(context).find(expr) + } else { + return this.constructor( context ).find( selector ); + } + + // HANDLE: $(function) + // Shortcut for document ready + } else if ( jQuery.isFunction( selector ) ) { + return rootjQuery.ready( selector ); + } + + if (selector.selector !== undefined) { + this.selector = selector.selector; + this.context = selector.context; + } + + return jQuery.makeArray( selector, this ); + }, + + // Start with an empty selector + selector: "", + + // The current version of jQuery being used + jquery: "1.6.2", + + // The default length of a jQuery object is 0 + length: 0, + + // The number of elements contained in the matched element set + size: function() { + return this.length; + }, + + toArray: function() { + return slice.call( this, 0 ); + }, + + // Get the Nth element in the matched element set OR + // Get the whole matched element set as a clean array + get: function( num ) { + return num == null ? + + // Return a 'clean' array + this.toArray() : + + // Return just the object + ( num < 0 ? this[ this.length + num ] : this[ num ] ); + }, + + // Take an array of elements and push it onto the stack + // (returning the new matched element set) + pushStack: function( elems, name, selector ) { + // Build a new jQuery matched element set + var ret = this.constructor(); + + if ( jQuery.isArray( elems ) ) { + push.apply( ret, elems ); + + } else { + jQuery.merge( ret, elems ); + } + + // Add the old object onto the stack (as a reference) + ret.prevObject = this; + + ret.context = this.context; + + if ( name === "find" ) { + ret.selector = this.selector + (this.selector ? " " : "") + selector; + } else if ( name ) { + ret.selector = this.selector + "." + name + "(" + selector + ")"; + } + + // Return the newly-formed element set + return ret; + }, + + // Execute a callback for every element in the matched set. + // (You can seed the arguments with an array of args, but this is + // only used internally.) + each: function( callback, args ) { + return jQuery.each( this, callback, args ); + }, + + ready: function( fn ) { + // Attach the listeners + jQuery.bindReady(); + + // Add the callback + readyList.done( fn ); + + return this; + }, + + eq: function( i ) { + return i === -1 ? + this.slice( i ) : + this.slice( i, +i + 1 ); + }, + + first: function() { + return this.eq( 0 ); + }, + + last: function() { + return this.eq( -1 ); + }, + + slice: function() { + return this.pushStack( slice.apply( this, arguments ), + "slice", slice.call(arguments).join(",") ); + }, + + map: function( callback ) { + return this.pushStack( jQuery.map(this, function( elem, i ) { + return callback.call( elem, i, elem ); + })); + }, + + end: function() { + return this.prevObject || this.constructor(null); + }, + + // For internal use only. + // Behaves like an Array's method, not like a jQuery method. + push: push, + sort: [].sort, + splice: [].splice +}; + +// Give the init function the jQuery prototype for later instantiation +jQuery.fn.init.prototype = jQuery.fn; + +jQuery.extend = jQuery.fn.extend = function() { + var options, name, src, copy, copyIsArray, clone, + target = arguments[0] || {}, + i = 1, + length = arguments.length, + deep = false; + + // Handle a deep copy situation + if ( typeof target === "boolean" ) { + deep = target; + target = arguments[1] || {}; + // skip the boolean and the target + i = 2; + } + + // Handle case when target is a string or something (possible in deep copy) + if ( typeof target !== "object" && !jQuery.isFunction(target) ) { + target = {}; + } + + // extend jQuery itself if only one argument is passed + if ( length === i ) { + target = this; + --i; + } + + for ( ; i < length; i++ ) { + // Only deal with non-null/undefined values + if ( (options = arguments[ i ]) != null ) { + // Extend the base object + for ( name in options ) { + src = target[ name ]; + copy = options[ name ]; + + // Prevent never-ending loop + if ( target === copy ) { + continue; + } + + // Recurse if we're merging plain objects or arrays + if ( deep && copy && ( jQuery.isPlainObject(copy) || (copyIsArray = jQuery.isArray(copy)) ) ) { + if ( copyIsArray ) { + copyIsArray = false; + clone = src && jQuery.isArray(src) ? src : []; + + } else { + clone = src && jQuery.isPlainObject(src) ? src : {}; + } + + // Never move original objects, clone them + target[ name ] = jQuery.extend( deep, clone, copy ); + + // Don't bring in undefined values + } else if ( copy !== undefined ) { + target[ name ] = copy; + } + } + } + } + + // Return the modified object + return target; +}; + +jQuery.extend({ + noConflict: function( deep ) { + if ( window.$ === jQuery ) { + window.$ = _$; + } + + if ( deep && window.jQuery === jQuery ) { + window.jQuery = _jQuery; + } + + return jQuery; + }, + + // Is the DOM ready to be used? Set to true once it occurs. + isReady: false, + + // A counter to track how many items to wait for before + // the ready event fires. See #6781 + readyWait: 1, + + // Hold (or release) the ready event + holdReady: function( hold ) { + if ( hold ) { + jQuery.readyWait++; + } else { + jQuery.ready( true ); + } + }, + + // Handle when the DOM is ready + ready: function( wait ) { + // Either a released hold or an DOMready/load event and not yet ready + if ( (wait === true && !--jQuery.readyWait) || (wait !== true && !jQuery.isReady) ) { + // Make sure body exists, at least, in case IE gets a little overzealous (ticket #5443). + if ( !document.body ) { + return setTimeout( jQuery.ready, 1 ); + } + + // Remember that the DOM is ready + jQuery.isReady = true; + + // If a normal DOM Ready event fired, decrement, and wait if need be + if ( wait !== true && --jQuery.readyWait > 0 ) { + return; + } + + // If there are functions bound, to execute + readyList.resolveWith( document, [ jQuery ] ); + + // Trigger any bound ready events + if ( jQuery.fn.trigger ) { + jQuery( document ).trigger( "ready" ).unbind( "ready" ); + } + } + }, + + bindReady: function() { + if ( readyList ) { + return; + } + + readyList = jQuery._Deferred(); + + // Catch cases where $(document).ready() is called after the + // browser event has already occurred. + if ( document.readyState === "complete" ) { + // Handle it asynchronously to allow scripts the opportunity to delay ready + return setTimeout( jQuery.ready, 1 ); + } + + // Mozilla, Opera and webkit nightlies currently support this event + if ( document.addEventListener ) { + // Use the handy event callback + document.addEventListener( "DOMContentLoaded", DOMContentLoaded, false ); + + // A fallback to window.onload, that will always work + window.addEventListener( "load", jQuery.ready, false ); + + // If IE event model is used + } else if ( document.attachEvent ) { + // ensure firing before onload, + // maybe late but safe also for iframes + document.attachEvent( "onreadystatechange", DOMContentLoaded ); + + // A fallback to window.onload, that will always work + window.attachEvent( "onload", jQuery.ready ); + + // If IE and not a frame + // continually check to see if the document is ready + var toplevel = false; + + try { + toplevel = window.frameElement == null; + } catch(e) {} + + if ( document.documentElement.doScroll && toplevel ) { + doScrollCheck(); + } + } + }, + + // See test/unit/core.js for details concerning isFunction. + // Since version 1.3, DOM methods and functions like alert + // aren't supported. They return false on IE (#2968). + isFunction: function( obj ) { + return jQuery.type(obj) === "function"; + }, + + isArray: Array.isArray || function( obj ) { + return jQuery.type(obj) === "array"; + }, + + // A crude way of determining if an object is a window + isWindow: function( obj ) { + return obj && typeof obj === "object" && "setInterval" in obj; + }, + + isNaN: function( obj ) { + return obj == null || !rdigit.test( obj ) || isNaN( obj ); + }, + + type: function( obj ) { + return obj == null ? + String( obj ) : + class2type[ toString.call(obj) ] || "object"; + }, + + isPlainObject: function( obj ) { + // Must be an Object. + // Because of IE, we also have to check the presence of the constructor property. + // Make sure that DOM nodes and window objects don't pass through, as well + if ( !obj || jQuery.type(obj) !== "object" || obj.nodeType || jQuery.isWindow( obj ) ) { + return false; + } + + // Not own constructor property must be Object + if ( obj.constructor && + !hasOwn.call(obj, "constructor") && + !hasOwn.call(obj.constructor.prototype, "isPrototypeOf") ) { + return false; + } + + // Own properties are enumerated firstly, so to speed up, + // if last one is own, then all properties are own. + + var key; + for ( key in obj ) {} + + return key === undefined || hasOwn.call( obj, key ); + }, + + isEmptyObject: function( obj ) { + for ( var name in obj ) { + return false; + } + return true; + }, + + error: function( msg ) { + throw msg; + }, + + parseJSON: function( data ) { + if ( typeof data !== "string" || !data ) { + return null; + } + + // Make sure leading/trailing whitespace is removed (IE can't handle it) + data = jQuery.trim( data ); + + // Attempt to parse using the native JSON parser first + if ( window.JSON && window.JSON.parse ) { + return window.JSON.parse( data ); + } + + // Make sure the incoming data is actual JSON + // Logic borrowed from http://json.org/json2.js + if ( rvalidchars.test( data.replace( rvalidescape, "@" ) + .replace( rvalidtokens, "]" ) + .replace( rvalidbraces, "")) ) { + + return (new Function( "return " + data ))(); + + } + jQuery.error( "Invalid JSON: " + data ); + }, + + // Cross-browser xml parsing + // (xml & tmp used internally) + parseXML: function( data , xml , tmp ) { + + if ( window.DOMParser ) { // Standard + tmp = new DOMParser(); + xml = tmp.parseFromString( data , "text/xml" ); + } else { // IE + xml = new ActiveXObject( "Microsoft.XMLDOM" ); + xml.async = "false"; + xml.loadXML( data ); + } + + tmp = xml.documentElement; + + if ( ! tmp || ! tmp.nodeName || tmp.nodeName === "parsererror" ) { + jQuery.error( "Invalid XML: " + data ); + } + + return xml; + }, + + noop: function() {}, + + // Evaluates a script in a global context + // Workarounds based on findings by Jim Driscoll + // http://weblogs.java.net/blog/driscoll/archive/2009/09/08/eval-javascript-global-context + globalEval: function( data ) { + if ( data && rnotwhite.test( data ) ) { + // We use execScript on Internet Explorer + // We use an anonymous function so that context is window + // rather than jQuery in Firefox + ( window.execScript || function( data ) { + window[ "eval" ].call( window, data ); + } )( data ); + } + }, + + // Converts a dashed string to camelCased string; + // Used by both the css and data modules + camelCase: function( string ) { + return string.replace( rdashAlpha, fcamelCase ); + }, + + nodeName: function( elem, name ) { + return elem.nodeName && elem.nodeName.toUpperCase() === name.toUpperCase(); + }, + + // args is for internal usage only + each: function( object, callback, args ) { + var name, i = 0, + length = object.length, + isObj = length === undefined || jQuery.isFunction( object ); + + if ( args ) { + if ( isObj ) { + for ( name in object ) { + if ( callback.apply( object[ name ], args ) === false ) { + break; + } + } + } else { + for ( ; i < length; ) { + if ( callback.apply( object[ i++ ], args ) === false ) { + break; + } + } + } + + // A special, fast, case for the most common use of each + } else { + if ( isObj ) { + for ( name in object ) { + if ( callback.call( object[ name ], name, object[ name ] ) === false ) { + break; + } + } + } else { + for ( ; i < length; ) { + if ( callback.call( object[ i ], i, object[ i++ ] ) === false ) { + break; + } + } + } + } + + return object; + }, + + // Use native String.trim function wherever possible + trim: trim ? + function( text ) { + return text == null ? + "" : + trim.call( text ); + } : + + // Otherwise use our own trimming functionality + function( text ) { + return text == null ? + "" : + text.toString().replace( trimLeft, "" ).replace( trimRight, "" ); + }, + + // results is for internal usage only + makeArray: function( array, results ) { + var ret = results || []; + + if ( array != null ) { + // The window, strings (and functions) also have 'length' + // The extra typeof function check is to prevent crashes + // in Safari 2 (See: #3039) + // Tweaked logic slightly to handle Blackberry 4.7 RegExp issues #6930 + var type = jQuery.type( array ); + + if ( array.length == null || type === "string" || type === "function" || type === "regexp" || jQuery.isWindow( array ) ) { + push.call( ret, array ); + } else { + jQuery.merge( ret, array ); + } + } + + return ret; + }, + + inArray: function( elem, array ) { + + if ( indexOf ) { + return indexOf.call( array, elem ); + } + + for ( var i = 0, length = array.length; i < length; i++ ) { + if ( array[ i ] === elem ) { + return i; + } + } + + return -1; + }, + + merge: function( first, second ) { + var i = first.length, + j = 0; + + if ( typeof second.length === "number" ) { + for ( var l = second.length; j < l; j++ ) { + first[ i++ ] = second[ j ]; + } + + } else { + while ( second[j] !== undefined ) { + first[ i++ ] = second[ j++ ]; + } + } + + first.length = i; + + return first; + }, + + grep: function( elems, callback, inv ) { + var ret = [], retVal; + inv = !!inv; + + // Go through the array, only saving the items + // that pass the validator function + for ( var i = 0, length = elems.length; i < length; i++ ) { + retVal = !!callback( elems[ i ], i ); + if ( inv !== retVal ) { + ret.push( elems[ i ] ); + } + } + + return ret; + }, + + // arg is for internal usage only + map: function( elems, callback, arg ) { + var value, key, ret = [], + i = 0, + length = elems.length, + // jquery objects are treated as arrays + isArray = elems instanceof jQuery || length !== undefined && typeof length === "number" && ( ( length > 0 && elems[ 0 ] && elems[ length -1 ] ) || length === 0 || jQuery.isArray( elems ) ) ; + + // Go through the array, translating each of the items to their + if ( isArray ) { + for ( ; i < length; i++ ) { + value = callback( elems[ i ], i, arg ); + + if ( value != null ) { + ret[ ret.length ] = value; + } + } + + // Go through every key on the object, + } else { + for ( key in elems ) { + value = callback( elems[ key ], key, arg ); + + if ( value != null ) { + ret[ ret.length ] = value; + } + } + } + + // Flatten any nested arrays + return ret.concat.apply( [], ret ); + }, + + // A global GUID counter for objects + guid: 1, + + // Bind a function to a context, optionally partially applying any + // arguments. + proxy: function( fn, context ) { + if ( typeof context === "string" ) { + var tmp = fn[ context ]; + context = fn; + fn = tmp; + } + + // Quick check to determine if target is callable, in the spec + // this throws a TypeError, but we will just return undefined. + if ( !jQuery.isFunction( fn ) ) { + return undefined; + } + + // Simulated bind + var args = slice.call( arguments, 2 ), + proxy = function() { + return fn.apply( context, args.concat( slice.call( arguments ) ) ); + }; + + // Set the guid of unique handler to the same of original handler, so it can be removed + proxy.guid = fn.guid = fn.guid || proxy.guid || jQuery.guid++; + + return proxy; + }, + + // Mutifunctional method to get and set values to a collection + // The value/s can optionally be executed if it's a function + access: function( elems, key, value, exec, fn, pass ) { + var length = elems.length; + + // Setting many attributes + if ( typeof key === "object" ) { + for ( var k in key ) { + jQuery.access( elems, k, key[k], exec, fn, value ); + } + return elems; + } + + // Setting one attribute + if ( value !== undefined ) { + // Optionally, function values get executed if exec is true + exec = !pass && exec && jQuery.isFunction(value); + + for ( var i = 0; i < length; i++ ) { + fn( elems[i], key, exec ? value.call( elems[i], i, fn( elems[i], key ) ) : value, pass ); + } + + return elems; + } + + // Getting an attribute + return length ? fn( elems[0], key ) : undefined; + }, + + now: function() { + return (new Date()).getTime(); + }, + + // Use of jQuery.browser is frowned upon. + // More details: http://docs.jquery.com/Utilities/jQuery.browser + uaMatch: function( ua ) { + ua = ua.toLowerCase(); + + var match = rwebkit.exec( ua ) || + ropera.exec( ua ) || + rmsie.exec( ua ) || + ua.indexOf("compatible") < 0 && rmozilla.exec( ua ) || + []; + + return { browser: match[1] || "", version: match[2] || "0" }; + }, + + sub: function() { + function jQuerySub( selector, context ) { + return new jQuerySub.fn.init( selector, context ); + } + jQuery.extend( true, jQuerySub, this ); + jQuerySub.superclass = this; + jQuerySub.fn = jQuerySub.prototype = this(); + jQuerySub.fn.constructor = jQuerySub; + jQuerySub.sub = this.sub; + jQuerySub.fn.init = function init( selector, context ) { + if ( context && context instanceof jQuery && !(context instanceof jQuerySub) ) { + context = jQuerySub( context ); + } + + return jQuery.fn.init.call( this, selector, context, rootjQuerySub ); + }; + jQuerySub.fn.init.prototype = jQuerySub.fn; + var rootjQuerySub = jQuerySub(document); + return jQuerySub; + }, + + browser: {} +}); + +// Populate the class2type map +jQuery.each("Boolean Number String Function Array Date RegExp Object".split(" "), function(i, name) { + class2type[ "[object " + name + "]" ] = name.toLowerCase(); +}); + +browserMatch = jQuery.uaMatch( userAgent ); +if ( browserMatch.browser ) { + jQuery.browser[ browserMatch.browser ] = true; + jQuery.browser.version = browserMatch.version; +} + +// Deprecated, use jQuery.browser.webkit instead +if ( jQuery.browser.webkit ) { + jQuery.browser.safari = true; +} + +// IE doesn't match non-breaking spaces with \s +if ( rnotwhite.test( "\xA0" ) ) { + trimLeft = /^[\s\xA0]+/; + trimRight = /[\s\xA0]+$/; +} + +// All jQuery objects should point back to these +rootjQuery = jQuery(document); + +// Cleanup functions for the document ready method +if ( document.addEventListener ) { + DOMContentLoaded = function() { + document.removeEventListener( "DOMContentLoaded", DOMContentLoaded, false ); + jQuery.ready(); + }; + +} else if ( document.attachEvent ) { + DOMContentLoaded = function() { + // Make sure body exists, at least, in case IE gets a little overzealous (ticket #5443). + if ( document.readyState === "complete" ) { + document.detachEvent( "onreadystatechange", DOMContentLoaded ); + jQuery.ready(); + } + }; +} + +// The DOM ready check for Internet Explorer +function doScrollCheck() { + if ( jQuery.isReady ) { + return; + } + + try { + // If IE is used, use the trick by Diego Perini + // http://javascript.nwbox.com/IEContentLoaded/ + document.documentElement.doScroll("left"); + } catch(e) { + setTimeout( doScrollCheck, 1 ); + return; + } + + // and execute any waiting functions + jQuery.ready(); +} + +return jQuery; + +})(); + + +var // Promise methods + promiseMethods = "done fail isResolved isRejected promise then always pipe".split( " " ), + // Static reference to slice + sliceDeferred = [].slice; + +jQuery.extend({ + // Create a simple deferred (one callbacks list) + _Deferred: function() { + var // callbacks list + callbacks = [], + // stored [ context , args ] + fired, + // to avoid firing when already doing so + firing, + // flag to know if the deferred has been cancelled + cancelled, + // the deferred itself + deferred = { + + // done( f1, f2, ...) + done: function() { + if ( !cancelled ) { + var args = arguments, + i, + length, + elem, + type, + _fired; + if ( fired ) { + _fired = fired; + fired = 0; + } + for ( i = 0, length = args.length; i < length; i++ ) { + elem = args[ i ]; + type = jQuery.type( elem ); + if ( type === "array" ) { + deferred.done.apply( deferred, elem ); + } else if ( type === "function" ) { + callbacks.push( elem ); + } + } + if ( _fired ) { + deferred.resolveWith( _fired[ 0 ], _fired[ 1 ] ); + } + } + return this; + }, + + // resolve with given context and args + resolveWith: function( context, args ) { + if ( !cancelled && !fired && !firing ) { + // make sure args are available (#8421) + args = args || []; + firing = 1; + try { + while( callbacks[ 0 ] ) { + callbacks.shift().apply( context, args ); + } + } + finally { + fired = [ context, args ]; + firing = 0; + } + } + return this; + }, + + // resolve with this as context and given arguments + resolve: function() { + deferred.resolveWith( this, arguments ); + return this; + }, + + // Has this deferred been resolved? + isResolved: function() { + return !!( firing || fired ); + }, + + // Cancel + cancel: function() { + cancelled = 1; + callbacks = []; + return this; + } + }; + + return deferred; + }, + + // Full fledged deferred (two callbacks list) + Deferred: function( func ) { + var deferred = jQuery._Deferred(), + failDeferred = jQuery._Deferred(), + promise; + // Add errorDeferred methods, then and promise + jQuery.extend( deferred, { + then: function( doneCallbacks, failCallbacks ) { + deferred.done( doneCallbacks ).fail( failCallbacks ); + return this; + }, + always: function() { + return deferred.done.apply( deferred, arguments ).fail.apply( this, arguments ); + }, + fail: failDeferred.done, + rejectWith: failDeferred.resolveWith, + reject: failDeferred.resolve, + isRejected: failDeferred.isResolved, + pipe: function( fnDone, fnFail ) { + return jQuery.Deferred(function( newDefer ) { + jQuery.each( { + done: [ fnDone, "resolve" ], + fail: [ fnFail, "reject" ] + }, function( handler, data ) { + var fn = data[ 0 ], + action = data[ 1 ], + returned; + if ( jQuery.isFunction( fn ) ) { + deferred[ handler ](function() { + returned = fn.apply( this, arguments ); + if ( returned && jQuery.isFunction( returned.promise ) ) { + returned.promise().then( newDefer.resolve, newDefer.reject ); + } else { + newDefer[ action ]( returned ); + } + }); + } else { + deferred[ handler ]( newDefer[ action ] ); + } + }); + }).promise(); + }, + // Get a promise for this deferred + // If obj is provided, the promise aspect is added to the object + promise: function( obj ) { + if ( obj == null ) { + if ( promise ) { + return promise; + } + promise = obj = {}; + } + var i = promiseMethods.length; + while( i-- ) { + obj[ promiseMethods[i] ] = deferred[ promiseMethods[i] ]; + } + return obj; + } + }); + // Make sure only one callback list will be used + deferred.done( failDeferred.cancel ).fail( deferred.cancel ); + // Unexpose cancel + delete deferred.cancel; + // Call given func if any + if ( func ) { + func.call( deferred, deferred ); + } + return deferred; + }, + + // Deferred helper + when: function( firstParam ) { + var args = arguments, + i = 0, + length = args.length, + count = length, + deferred = length <= 1 && firstParam && jQuery.isFunction( firstParam.promise ) ? + firstParam : + jQuery.Deferred(); + function resolveFunc( i ) { + return function( value ) { + args[ i ] = arguments.length > 1 ? sliceDeferred.call( arguments, 0 ) : value; + if ( !( --count ) ) { + // Strange bug in FF4: + // Values changed onto the arguments object sometimes end up as undefined values + // outside the $.when method. Cloning the object into a fresh array solves the issue + deferred.resolveWith( deferred, sliceDeferred.call( args, 0 ) ); + } + }; + } + if ( length > 1 ) { + for( ; i < length; i++ ) { + if ( args[ i ] && jQuery.isFunction( args[ i ].promise ) ) { + args[ i ].promise().then( resolveFunc(i), deferred.reject ); + } else { + --count; + } + } + if ( !count ) { + deferred.resolveWith( deferred, args ); + } + } else if ( deferred !== firstParam ) { + deferred.resolveWith( deferred, length ? [ firstParam ] : [] ); + } + return deferred.promise(); + } +}); + + + +jQuery.support = (function() { + + var div = document.createElement( "div" ), + documentElement = document.documentElement, + all, + a, + select, + opt, + input, + marginDiv, + support, + fragment, + body, + testElementParent, + testElement, + testElementStyle, + tds, + events, + eventName, + i, + isSupported; + + // Preliminary tests + div.setAttribute("className", "t"); + div.innerHTML = " <link/><table></table><a href='/a' style='top:1px;float:left;opacity:.55;'>a</a><input type='checkbox'/>"; + + all = div.getElementsByTagName( "*" ); + a = div.getElementsByTagName( "a" )[ 0 ]; + + // Can't get basic test support + if ( !all || !all.length || !a ) { + return {}; + } + + // First batch of supports tests + select = document.createElement( "select" ); + opt = select.appendChild( document.createElement("option") ); + input = div.getElementsByTagName( "input" )[ 0 ]; + + support = { + // IE strips leading whitespace when .innerHTML is used + leadingWhitespace: ( div.firstChild.nodeType === 3 ), + + // Make sure that tbody elements aren't automatically inserted + // IE will insert them into empty tables + tbody: !div.getElementsByTagName( "tbody" ).length, + + // Make sure that link elements get serialized correctly by innerHTML + // This requires a wrapper element in IE + htmlSerialize: !!div.getElementsByTagName( "link" ).length, + + // Get the style information from getAttribute + // (IE uses .cssText instead) + style: /top/.test( a.getAttribute("style") ), + + // Make sure that URLs aren't manipulated + // (IE normalizes it by default) + hrefNormalized: ( a.getAttribute( "href" ) === "/a" ), + + // Make sure that element opacity exists + // (IE uses filter instead) + // Use a regex to work around a WebKit issue. See #5145 + opacity: /^0.55$/.test( a.style.opacity ), + + // Verify style float existence + // (IE uses styleFloat instead of cssFloat) + cssFloat: !!a.style.cssFloat, + + // Make sure that if no value is specified for a checkbox + // that it defaults to "on". + // (WebKit defaults to "" instead) + checkOn: ( input.value === "on" ), + + // Make sure that a selected-by-default option has a working selected property. + // (WebKit defaults to false instead of true, IE too, if it's in an optgroup) + optSelected: opt.selected, + + // Test setAttribute on camelCase class. If it works, we need attrFixes when doing get/setAttribute (ie6/7) + getSetAttribute: div.className !== "t", + + // Will be defined later + submitBubbles: true, + changeBubbles: true, + focusinBubbles: false, + deleteExpando: true, + noCloneEvent: true, + inlineBlockNeedsLayout: false, + shrinkWrapBlocks: false, + reliableMarginRight: true + }; + + // Make sure checked status is properly cloned + input.checked = true; + support.noCloneChecked = input.cloneNode( true ).checked; + + // Make sure that the options inside disabled selects aren't marked as disabled + // (WebKit marks them as disabled) + select.disabled = true; + support.optDisabled = !opt.disabled; + + // Test to see if it's possible to delete an expando from an element + // Fails in Internet Explorer + try { + delete div.test; + } catch( e ) { + support.deleteExpando = false; + } + + if ( !div.addEventListener && div.attachEvent && div.fireEvent ) { + div.attachEvent( "onclick", function() { + // Cloning a node shouldn't copy over any + // bound event handlers (IE does this) + support.noCloneEvent = false; + }); + div.cloneNode( true ).fireEvent( "onclick" ); + } + + // Check if a radio maintains it's value + // after being appended to the DOM + input = document.createElement("input"); + input.value = "t"; + input.setAttribute("type", "radio"); + support.radioValue = input.value === "t"; + + input.setAttribute("checked", "checked"); + div.appendChild( input ); + fragment = document.createDocumentFragment(); + fragment.appendChild( div.firstChild ); + + // WebKit doesn't clone checked state correctly in fragments + support.checkClone = fragment.cloneNode( true ).cloneNode( true ).lastChild.checked; + + div.innerHTML = ""; + + // Figure out if the W3C box model works as expected + div.style.width = div.style.paddingLeft = "1px"; + + body = document.getElementsByTagName( "body" )[ 0 ]; + // We use our own, invisible, body unless the body is already present + // in which case we use a div (#9239) + testElement = document.createElement( body ? "div" : "body" ); + testElementStyle = { + visibility: "hidden", + width: 0, + height: 0, + border: 0, + margin: 0 + }; + if ( body ) { + jQuery.extend( testElementStyle, { + position: "absolute", + left: -1000, + top: -1000 + }); + } + for ( i in testElementStyle ) { + testElement.style[ i ] = testElementStyle[ i ]; + } + testElement.appendChild( div ); + testElementParent = body || documentElement; + testElementParent.insertBefore( testElement, testElementParent.firstChild ); + + // Check if a disconnected checkbox will retain its checked + // value of true after appended to the DOM (IE6/7) + support.appendChecked = input.checked; + + support.boxModel = div.offsetWidth === 2; + + if ( "zoom" in div.style ) { + // Check if natively block-level elements act like inline-block + // elements when setting their display to 'inline' and giving + // them layout + // (IE < 8 does this) + div.style.display = "inline"; + div.style.zoom = 1; + support.inlineBlockNeedsLayout = ( div.offsetWidth === 2 ); + + // Check if elements with layout shrink-wrap their children + // (IE 6 does this) + div.style.display = ""; + div.innerHTML = "<div style='width:4px;'></div>"; + support.shrinkWrapBlocks = ( div.offsetWidth !== 2 ); + } + + div.innerHTML = "<table><tr><td style='padding:0;border:0;display:none'></td><td>t</td></tr></table>"; + tds = div.getElementsByTagName( "td" ); + + // Check if table cells still have offsetWidth/Height when they are set + // to display:none and there are still other visible table cells in a + // table row; if so, offsetWidth/Height are not reliable for use when + // determining if an element has been hidden directly using + // display:none (it is still safe to use offsets if a parent element is + // hidden; don safety goggles and see bug #4512 for more information). + // (only IE 8 fails this test) + isSupported = ( tds[ 0 ].offsetHeight === 0 ); + + tds[ 0 ].style.display = ""; + tds[ 1 ].style.display = "none"; + + // Check if empty table cells still have offsetWidth/Height + // (IE < 8 fail this test) + support.reliableHiddenOffsets = isSupported && ( tds[ 0 ].offsetHeight === 0 ); + div.innerHTML = ""; + + // Check if div with explicit width and no margin-right incorrectly + // gets computed margin-right based on width of container. For more + // info see bug #3333 + // Fails in WebKit before Feb 2011 nightlies + // WebKit Bug 13343 - getComputedStyle returns wrong value for margin-right + if ( document.defaultView && document.defaultView.getComputedStyle ) { + marginDiv = document.createElement( "div" ); + marginDiv.style.width = "0"; + marginDiv.style.marginRight = "0"; + div.appendChild( marginDiv ); + support.reliableMarginRight = + ( parseInt( ( document.defaultView.getComputedStyle( marginDiv, null ) || { marginRight: 0 } ).marginRight, 10 ) || 0 ) === 0; + } + + // Remove the body element we added + testElement.innerHTML = ""; + testElementParent.removeChild( testElement ); + + // Technique from Juriy Zaytsev + // http://thinkweb2.com/projects/prototype/detecting-event-support-without-browser-sniffing/ + // We only care about the case where non-standard event systems + // are used, namely in IE. Short-circuiting here helps us to + // avoid an eval call (in setAttribute) which can cause CSP + // to go haywire. See: https://developer.mozilla.org/en/Security/CSP + if ( div.attachEvent ) { + for( i in { + submit: 1, + change: 1, + focusin: 1 + } ) { + eventName = "on" + i; + isSupported = ( eventName in div ); + if ( !isSupported ) { + div.setAttribute( eventName, "return;" ); + isSupported = ( typeof div[ eventName ] === "function" ); + } + support[ i + "Bubbles" ] = isSupported; + } + } + + // Null connected elements to avoid leaks in IE + testElement = fragment = select = opt = body = marginDiv = div = input = null; + + return support; +})(); + +// Keep track of boxModel +jQuery.boxModel = jQuery.support.boxModel; + + + + +var rbrace = /^(?:\{.*\}|\[.*\])$/, + rmultiDash = /([a-z])([A-Z])/g; + +jQuery.extend({ + cache: {}, + + // Please use with caution + uuid: 0, + + // Unique for each copy of jQuery on the page + // Non-digits removed to match rinlinejQuery + expando: "jQuery" + ( jQuery.fn.jquery + Math.random() ).replace( /\D/g, "" ), + + // The following elements throw uncatchable exceptions if you + // attempt to add expando properties to them. + noData: { + "embed": true, + // Ban all objects except for Flash (which handle expandos) + "object": "clsid:D27CDB6E-AE6D-11cf-96B8-444553540000", + "applet": true + }, + + hasData: function( elem ) { + elem = elem.nodeType ? jQuery.cache[ elem[jQuery.expando] ] : elem[ jQuery.expando ]; + + return !!elem && !isEmptyDataObject( elem ); + }, + + data: function( elem, name, data, pvt /* Internal Use Only */ ) { + if ( !jQuery.acceptData( elem ) ) { + return; + } + + var internalKey = jQuery.expando, getByName = typeof name === "string", thisCache, + + // We have to handle DOM nodes and JS objects differently because IE6-7 + // can't GC object references properly across the DOM-JS boundary + isNode = elem.nodeType, + + // Only DOM nodes need the global jQuery cache; JS object data is + // attached directly to the object so GC can occur automatically + cache = isNode ? jQuery.cache : elem, + + // Only defining an ID for JS objects if its cache already exists allows + // the code to shortcut on the same path as a DOM node with no cache + id = isNode ? elem[ jQuery.expando ] : elem[ jQuery.expando ] && jQuery.expando; + + // Avoid doing any more work than we need to when trying to get data on an + // object that has no data at all + if ( (!id || (pvt && id && !cache[ id ][ internalKey ])) && getByName && data === undefined ) { + return; + } + + if ( !id ) { + // Only DOM nodes need a new unique ID for each element since their data + // ends up in the global cache + if ( isNode ) { + elem[ jQuery.expando ] = id = ++jQuery.uuid; + } else { + id = jQuery.expando; + } + } + + if ( !cache[ id ] ) { + cache[ id ] = {}; + + // TODO: This is a hack for 1.5 ONLY. Avoids exposing jQuery + // metadata on plain JS objects when the object is serialized using + // JSON.stringify + if ( !isNode ) { + cache[ id ].toJSON = jQuery.noop; + } + } + + // An object can be passed to jQuery.data instead of a key/value pair; this gets + // shallow copied over onto the existing cache + if ( typeof name === "object" || typeof name === "function" ) { + if ( pvt ) { + cache[ id ][ internalKey ] = jQuery.extend(cache[ id ][ internalKey ], name); + } else { + cache[ id ] = jQuery.extend(cache[ id ], name); + } + } + + thisCache = cache[ id ]; + + // Internal jQuery data is stored in a separate object inside the object's data + // cache in order to avoid key collisions between internal data and user-defined + // data + if ( pvt ) { + if ( !thisCache[ internalKey ] ) { + thisCache[ internalKey ] = {}; + } + + thisCache = thisCache[ internalKey ]; + } + + if ( data !== undefined ) { + thisCache[ jQuery.camelCase( name ) ] = data; + } + + // TODO: This is a hack for 1.5 ONLY. It will be removed in 1.6. Users should + // not attempt to inspect the internal events object using jQuery.data, as this + // internal data object is undocumented and subject to change. + if ( name === "events" && !thisCache[name] ) { + return thisCache[ internalKey ] && thisCache[ internalKey ].events; + } + + return getByName ? + // Check for both converted-to-camel and non-converted data property names + thisCache[ jQuery.camelCase( name ) ] || thisCache[ name ] : + thisCache; + }, + + removeData: function( elem, name, pvt /* Internal Use Only */ ) { + if ( !jQuery.acceptData( elem ) ) { + return; + } + + var internalKey = jQuery.expando, isNode = elem.nodeType, + + // See jQuery.data for more information + cache = isNode ? jQuery.cache : elem, + + // See jQuery.data for more information + id = isNode ? elem[ jQuery.expando ] : jQuery.expando; + + // If there is already no cache entry for this object, there is no + // purpose in continuing + if ( !cache[ id ] ) { + return; + } + + if ( name ) { + var thisCache = pvt ? cache[ id ][ internalKey ] : cache[ id ]; + + if ( thisCache ) { + delete thisCache[ name ]; + + // If there is no data left in the cache, we want to continue + // and let the cache object itself get destroyed + if ( !isEmptyDataObject(thisCache) ) { + return; + } + } + } + + // See jQuery.data for more information + if ( pvt ) { + delete cache[ id ][ internalKey ]; + + // Don't destroy the parent cache unless the internal data object + // had been the only thing left in it + if ( !isEmptyDataObject(cache[ id ]) ) { + return; + } + } + + var internalCache = cache[ id ][ internalKey ]; + + // Browsers that fail expando deletion also refuse to delete expandos on + // the window, but it will allow it on all other JS objects; other browsers + // don't care + if ( jQuery.support.deleteExpando || cache != window ) { + delete cache[ id ]; + } else { + cache[ id ] = null; + } + + // We destroyed the entire user cache at once because it's faster than + // iterating through each key, but we need to continue to persist internal + // data if it existed + if ( internalCache ) { + cache[ id ] = {}; + // TODO: This is a hack for 1.5 ONLY. Avoids exposing jQuery + // metadata on plain JS objects when the object is serialized using + // JSON.stringify + if ( !isNode ) { + cache[ id ].toJSON = jQuery.noop; + } + + cache[ id ][ internalKey ] = internalCache; + + // Otherwise, we need to eliminate the expando on the node to avoid + // false lookups in the cache for entries that no longer exist + } else if ( isNode ) { + // IE does not allow us to delete expando properties from nodes, + // nor does it have a removeAttribute function on Document nodes; + // we must handle all of these cases + if ( jQuery.support.deleteExpando ) { + delete elem[ jQuery.expando ]; + } else if ( elem.removeAttribute ) { + elem.removeAttribute( jQuery.expando ); + } else { + elem[ jQuery.expando ] = null; + } + } + }, + + // For internal use only. + _data: function( elem, name, data ) { + return jQuery.data( elem, name, data, true ); + }, + + // A method for determining if a DOM node can handle the data expando + acceptData: function( elem ) { + if ( elem.nodeName ) { + var match = jQuery.noData[ elem.nodeName.toLowerCase() ]; + + if ( match ) { + return !(match === true || elem.getAttribute("classid") !== match); + } + } + + return true; + } +}); + +jQuery.fn.extend({ + data: function( key, value ) { + var data = null; + + if ( typeof key === "undefined" ) { + if ( this.length ) { + data = jQuery.data( this[0] ); + + if ( this[0].nodeType === 1 ) { + var attr = this[0].attributes, name; + for ( var i = 0, l = attr.length; i < l; i++ ) { + name = attr[i].name; + + if ( name.indexOf( "data-" ) === 0 ) { + name = jQuery.camelCase( name.substring(5) ); + + dataAttr( this[0], name, data[ name ] ); + } + } + } + } + + return data; + + } else if ( typeof key === "object" ) { + return this.each(function() { + jQuery.data( this, key ); + }); + } + + var parts = key.split("."); + parts[1] = parts[1] ? "." + parts[1] : ""; + + if ( value === undefined ) { + data = this.triggerHandler("getData" + parts[1] + "!", [parts[0]]); + + // Try to fetch any internally stored data first + if ( data === undefined && this.length ) { + data = jQuery.data( this[0], key ); + data = dataAttr( this[0], key, data ); + } + + return data === undefined && parts[1] ? + this.data( parts[0] ) : + data; + + } else { + return this.each(function() { + var $this = jQuery( this ), + args = [ parts[0], value ]; + + $this.triggerHandler( "setData" + parts[1] + "!", args ); + jQuery.data( this, key, value ); + $this.triggerHandler( "changeData" + parts[1] + "!", args ); + }); + } + }, + + removeData: function( key ) { + return this.each(function() { + jQuery.removeData( this, key ); + }); + } +}); + +function dataAttr( elem, key, data ) { + // If nothing was found internally, try to fetch any + // data from the HTML5 data-* attribute + if ( data === undefined && elem.nodeType === 1 ) { + var name = "data-" + key.replace( rmultiDash, "$1-$2" ).toLowerCase(); + + data = elem.getAttribute( name ); + + if ( typeof data === "string" ) { + try { + data = data === "true" ? true : + data === "false" ? false : + data === "null" ? null : + !jQuery.isNaN( data ) ? parseFloat( data ) : + rbrace.test( data ) ? jQuery.parseJSON( data ) : + data; + } catch( e ) {} + + // Make sure we set the data so it isn't changed later + jQuery.data( elem, key, data ); + + } else { + data = undefined; + } + } + + return data; +} + +// TODO: This is a hack for 1.5 ONLY to allow objects with a single toJSON +// property to be considered empty objects; this property always exists in +// order to make sure JSON.stringify does not expose internal metadata +function isEmptyDataObject( obj ) { + for ( var name in obj ) { + if ( name !== "toJSON" ) { + return false; + } + } + + return true; +} + + + + +function handleQueueMarkDefer( elem, type, src ) { + var deferDataKey = type + "defer", + queueDataKey = type + "queue", + markDataKey = type + "mark", + defer = jQuery.data( elem, deferDataKey, undefined, true ); + if ( defer && + ( src === "queue" || !jQuery.data( elem, queueDataKey, undefined, true ) ) && + ( src === "mark" || !jQuery.data( elem, markDataKey, undefined, true ) ) ) { + // Give room for hard-coded callbacks to fire first + // and eventually mark/queue something else on the element + setTimeout( function() { + if ( !jQuery.data( elem, queueDataKey, undefined, true ) && + !jQuery.data( elem, markDataKey, undefined, true ) ) { + jQuery.removeData( elem, deferDataKey, true ); + defer.resolve(); + } + }, 0 ); + } +} + +jQuery.extend({ + + _mark: function( elem, type ) { + if ( elem ) { + type = (type || "fx") + "mark"; + jQuery.data( elem, type, (jQuery.data(elem,type,undefined,true) || 0) + 1, true ); + } + }, + + _unmark: function( force, elem, type ) { + if ( force !== true ) { + type = elem; + elem = force; + force = false; + } + if ( elem ) { + type = type || "fx"; + var key = type + "mark", + count = force ? 0 : ( (jQuery.data( elem, key, undefined, true) || 1 ) - 1 ); + if ( count ) { + jQuery.data( elem, key, count, true ); + } else { + jQuery.removeData( elem, key, true ); + handleQueueMarkDefer( elem, type, "mark" ); + } + } + }, + + queue: function( elem, type, data ) { + if ( elem ) { + type = (type || "fx") + "queue"; + var q = jQuery.data( elem, type, undefined, true ); + // Speed up dequeue by getting out quickly if this is just a lookup + if ( data ) { + if ( !q || jQuery.isArray(data) ) { + q = jQuery.data( elem, type, jQuery.makeArray(data), true ); + } else { + q.push( data ); + } + } + return q || []; + } + }, + + dequeue: function( elem, type ) { + type = type || "fx"; + + var queue = jQuery.queue( elem, type ), + fn = queue.shift(), + defer; + + // If the fx queue is dequeued, always remove the progress sentinel + if ( fn === "inprogress" ) { + fn = queue.shift(); + } + + if ( fn ) { + // Add a progress sentinel to prevent the fx queue from being + // automatically dequeued + if ( type === "fx" ) { + queue.unshift("inprogress"); + } + + fn.call(elem, function() { + jQuery.dequeue(elem, type); + }); + } + + if ( !queue.length ) { + jQuery.removeData( elem, type + "queue", true ); + handleQueueMarkDefer( elem, type, "queue" ); + } + } +}); + +jQuery.fn.extend({ + queue: function( type, data ) { + if ( typeof type !== "string" ) { + data = type; + type = "fx"; + } + + if ( data === undefined ) { + return jQuery.queue( this[0], type ); + } + return this.each(function() { + var queue = jQuery.queue( this, type, data ); + + if ( type === "fx" && queue[0] !== "inprogress" ) { + jQuery.dequeue( this, type ); + } + }); + }, + dequeue: function( type ) { + return this.each(function() { + jQuery.dequeue( this, type ); + }); + }, + // Based off of the plugin by Clint Helfers, with permission. + // http://blindsignals.com/index.php/2009/07/jquery-delay/ + delay: function( time, type ) { + time = jQuery.fx ? jQuery.fx.speeds[time] || time : time; + type = type || "fx"; + + return this.queue( type, function() { + var elem = this; + setTimeout(function() { + jQuery.dequeue( elem, type ); + }, time ); + }); + }, + clearQueue: function( type ) { + return this.queue( type || "fx", [] ); + }, + // Get a promise resolved when queues of a certain type + // are emptied (fx is the type by default) + promise: function( type, object ) { + if ( typeof type !== "string" ) { + object = type; + type = undefined; + } + type = type || "fx"; + var defer = jQuery.Deferred(), + elements = this, + i = elements.length, + count = 1, + deferDataKey = type + "defer", + queueDataKey = type + "queue", + markDataKey = type + "mark", + tmp; + function resolve() { + if ( !( --count ) ) { + defer.resolveWith( elements, [ elements ] ); + } + } + while( i-- ) { + if (( tmp = jQuery.data( elements[ i ], deferDataKey, undefined, true ) || + ( jQuery.data( elements[ i ], queueDataKey, undefined, true ) || + jQuery.data( elements[ i ], markDataKey, undefined, true ) ) && + jQuery.data( elements[ i ], deferDataKey, jQuery._Deferred(), true ) )) { + count++; + tmp.done( resolve ); + } + } + resolve(); + return defer.promise(); + } +}); + + + + +var rclass = /[\n\t\r]/g, + rspace = /\s+/, + rreturn = /\r/g, + rtype = /^(?:button|input)$/i, + rfocusable = /^(?:button|input|object|select|textarea)$/i, + rclickable = /^a(?:rea)?$/i, + rboolean = /^(?:autofocus|autoplay|async|checked|controls|defer|disabled|hidden|loop|multiple|open|readonly|required|scoped|selected)$/i, + rinvalidChar = /\:|^on/, + formHook, boolHook; + +jQuery.fn.extend({ + attr: function( name, value ) { + return jQuery.access( this, name, value, true, jQuery.attr ); + }, + + removeAttr: function( name ) { + return this.each(function() { + jQuery.removeAttr( this, name ); + }); + }, + + prop: function( name, value ) { + return jQuery.access( this, name, value, true, jQuery.prop ); + }, + + removeProp: function( name ) { + name = jQuery.propFix[ name ] || name; + return this.each(function() { + // try/catch handles cases where IE balks (such as removing a property on window) + try { + this[ name ] = undefined; + delete this[ name ]; + } catch( e ) {} + }); + }, + + addClass: function( value ) { + var classNames, i, l, elem, + setClass, c, cl; + + if ( jQuery.isFunction( value ) ) { + return this.each(function( j ) { + jQuery( this ).addClass( value.call(this, j, this.className) ); + }); + } + + if ( value && typeof value === "string" ) { + classNames = value.split( rspace ); + + for ( i = 0, l = this.length; i < l; i++ ) { + elem = this[ i ]; + + if ( elem.nodeType === 1 ) { + if ( !elem.className && classNames.length === 1 ) { + elem.className = value; + + } else { + setClass = " " + elem.className + " "; + + for ( c = 0, cl = classNames.length; c < cl; c++ ) { + if ( !~setClass.indexOf( " " + classNames[ c ] + " " ) ) { + setClass += classNames[ c ] + " "; + } + } + elem.className = jQuery.trim( setClass ); + } + } + } + } + + return this; + }, + + removeClass: function( value ) { + var classNames, i, l, elem, className, c, cl; + + if ( jQuery.isFunction( value ) ) { + return this.each(function( j ) { + jQuery( this ).removeClass( value.call(this, j, this.className) ); + }); + } + + if ( (value && typeof value === "string") || value === undefined ) { + classNames = (value || "").split( rspace ); + + for ( i = 0, l = this.length; i < l; i++ ) { + elem = this[ i ]; + + if ( elem.nodeType === 1 && elem.className ) { + if ( value ) { + className = (" " + elem.className + " ").replace( rclass, " " ); + for ( c = 0, cl = classNames.length; c < cl; c++ ) { + className = className.replace(" " + classNames[ c ] + " ", " "); + } + elem.className = jQuery.trim( className ); + + } else { + elem.className = ""; + } + } + } + } + + return this; + }, + + toggleClass: function( value, stateVal ) { + var type = typeof value, + isBool = typeof stateVal === "boolean"; + + if ( jQuery.isFunction( value ) ) { + return this.each(function( i ) { + jQuery( this ).toggleClass( value.call(this, i, this.className, stateVal), stateVal ); + }); + } + + return this.each(function() { + if ( type === "string" ) { + // toggle individual class names + var className, + i = 0, + self = jQuery( this ), + state = stateVal, + classNames = value.split( rspace ); + + while ( (className = classNames[ i++ ]) ) { + // check each className given, space seperated list + state = isBool ? state : !self.hasClass( className ); + self[ state ? "addClass" : "removeClass" ]( className ); + } + + } else if ( type === "undefined" || type === "boolean" ) { + if ( this.className ) { + // store className if set + jQuery._data( this, "__className__", this.className ); + } + + // toggle whole className + this.className = this.className || value === false ? "" : jQuery._data( this, "__className__" ) || ""; + } + }); + }, + + hasClass: function( selector ) { + var className = " " + selector + " "; + for ( var i = 0, l = this.length; i < l; i++ ) { + if ( (" " + this[i].className + " ").replace(rclass, " ").indexOf( className ) > -1 ) { + return true; + } + } + + return false; + }, + + val: function( value ) { + var hooks, ret, + elem = this[0]; + + if ( !arguments.length ) { + if ( elem ) { + hooks = jQuery.valHooks[ elem.nodeName.toLowerCase() ] || jQuery.valHooks[ elem.type ]; + + if ( hooks && "get" in hooks && (ret = hooks.get( elem, "value" )) !== undefined ) { + return ret; + } + + ret = elem.value; + + return typeof ret === "string" ? + // handle most common string cases + ret.replace(rreturn, "") : + // handle cases where value is null/undef or number + ret == null ? "" : ret; + } + + return undefined; + } + + var isFunction = jQuery.isFunction( value ); + + return this.each(function( i ) { + var self = jQuery(this), val; + + if ( this.nodeType !== 1 ) { + return; + } + + if ( isFunction ) { + val = value.call( this, i, self.val() ); + } else { + val = value; + } + + // Treat null/undefined as ""; convert numbers to string + if ( val == null ) { + val = ""; + } else if ( typeof val === "number" ) { + val += ""; + } else if ( jQuery.isArray( val ) ) { + val = jQuery.map(val, function ( value ) { + return value == null ? "" : value + ""; + }); + } + + hooks = jQuery.valHooks[ this.nodeName.toLowerCase() ] || jQuery.valHooks[ this.type ]; + + // If set returns undefined, fall back to normal setting + if ( !hooks || !("set" in hooks) || hooks.set( this, val, "value" ) === undefined ) { + this.value = val; + } + }); + } +}); + +jQuery.extend({ + valHooks: { + option: { + get: function( elem ) { + // attributes.value is undefined in Blackberry 4.7 but + // uses .value. See #6932 + var val = elem.attributes.value; + return !val || val.specified ? elem.value : elem.text; + } + }, + select: { + get: function( elem ) { + var value, + index = elem.selectedIndex, + values = [], + options = elem.options, + one = elem.type === "select-one"; + + // Nothing was selected + if ( index < 0 ) { + return null; + } + + // Loop through all the selected options + for ( var i = one ? index : 0, max = one ? index + 1 : options.length; i < max; i++ ) { + var option = options[ i ]; + + // Don't return options that are disabled or in a disabled optgroup + if ( option.selected && (jQuery.support.optDisabled ? !option.disabled : option.getAttribute("disabled") === null) && + (!option.parentNode.disabled || !jQuery.nodeName( option.parentNode, "optgroup" )) ) { + + // Get the specific value for the option + value = jQuery( option ).val(); + + // We don't need an array for one selects + if ( one ) { + return value; + } + + // Multi-Selects return an array + values.push( value ); + } + } + + // Fixes Bug #2551 -- select.val() broken in IE after form.reset() + if ( one && !values.length && options.length ) { + return jQuery( options[ index ] ).val(); + } + + return values; + }, + + set: function( elem, value ) { + var values = jQuery.makeArray( value ); + + jQuery(elem).find("option").each(function() { + this.selected = jQuery.inArray( jQuery(this).val(), values ) >= 0; + }); + + if ( !values.length ) { + elem.selectedIndex = -1; + } + return values; + } + } + }, + + attrFn: { + val: true, + css: true, + html: true, + text: true, + data: true, + width: true, + height: true, + offset: true + }, + + attrFix: { + // Always normalize to ensure hook usage + tabindex: "tabIndex" + }, + + attr: function( elem, name, value, pass ) { + var nType = elem.nodeType; + + // don't get/set attributes on text, comment and attribute nodes + if ( !elem || nType === 3 || nType === 8 || nType === 2 ) { + return undefined; + } + + if ( pass && name in jQuery.attrFn ) { + return jQuery( elem )[ name ]( value ); + } + + // Fallback to prop when attributes are not supported + if ( !("getAttribute" in elem) ) { + return jQuery.prop( elem, name, value ); + } + + var ret, hooks, + notxml = nType !== 1 || !jQuery.isXMLDoc( elem ); + + // Normalize the name if needed + if ( notxml ) { + name = jQuery.attrFix[ name ] || name; + + hooks = jQuery.attrHooks[ name ]; + + if ( !hooks ) { + // Use boolHook for boolean attributes + if ( rboolean.test( name ) ) { + + hooks = boolHook; + + // Use formHook for forms and if the name contains certain characters + } else if ( formHook && name !== "className" && + (jQuery.nodeName( elem, "form" ) || rinvalidChar.test( name )) ) { + + hooks = formHook; + } + } + } + + if ( value !== undefined ) { + + if ( value === null ) { + jQuery.removeAttr( elem, name ); + return undefined; + + } else if ( hooks && "set" in hooks && notxml && (ret = hooks.set( elem, value, name )) !== undefined ) { + return ret; + + } else { + elem.setAttribute( name, "" + value ); + return value; + } + + } else if ( hooks && "get" in hooks && notxml && (ret = hooks.get( elem, name )) !== null ) { + return ret; + + } else { + + ret = elem.getAttribute( name ); + + // Non-existent attributes return null, we normalize to undefined + return ret === null ? + undefined : + ret; + } + }, + + removeAttr: function( elem, name ) { + var propName; + if ( elem.nodeType === 1 ) { + name = jQuery.attrFix[ name ] || name; + + if ( jQuery.support.getSetAttribute ) { + // Use removeAttribute in browsers that support it + elem.removeAttribute( name ); + } else { + jQuery.attr( elem, name, "" ); + elem.removeAttributeNode( elem.getAttributeNode( name ) ); + } + + // Set corresponding property to false for boolean attributes + if ( rboolean.test( name ) && (propName = jQuery.propFix[ name ] || name) in elem ) { + elem[ propName ] = false; + } + } + }, + + attrHooks: { + type: { + set: function( elem, value ) { + // We can't allow the type property to be changed (since it causes problems in IE) + if ( rtype.test( elem.nodeName ) && elem.parentNode ) { + jQuery.error( "type property can't be changed" ); + } else if ( !jQuery.support.radioValue && value === "radio" && jQuery.nodeName(elem, "input") ) { + // Setting the type on a radio button after the value resets the value in IE6-9 + // Reset value to it's default in case type is set after value + // This is for element creation + var val = elem.value; + elem.setAttribute( "type", value ); + if ( val ) { + elem.value = val; + } + return value; + } + } + }, + tabIndex: { + get: function( elem ) { + // elem.tabIndex doesn't always return the correct value when it hasn't been explicitly set + // http://fluidproject.org/blog/2008/01/09/getting-setting-and-removing-tabindex-values-with-javascript/ + var attributeNode = elem.getAttributeNode("tabIndex"); + + return attributeNode && attributeNode.specified ? + parseInt( attributeNode.value, 10 ) : + rfocusable.test( elem.nodeName ) || rclickable.test( elem.nodeName ) && elem.href ? + 0 : + undefined; + } + }, + // Use the value property for back compat + // Use the formHook for button elements in IE6/7 (#1954) + value: { + get: function( elem, name ) { + if ( formHook && jQuery.nodeName( elem, "button" ) ) { + return formHook.get( elem, name ); + } + return name in elem ? + elem.value : + null; + }, + set: function( elem, value, name ) { + if ( formHook && jQuery.nodeName( elem, "button" ) ) { + return formHook.set( elem, value, name ); + } + // Does not return so that setAttribute is also used + elem.value = value; + } + } + }, + + propFix: { + tabindex: "tabIndex", + readonly: "readOnly", + "for": "htmlFor", + "class": "className", + maxlength: "maxLength", + cellspacing: "cellSpacing", + cellpadding: "cellPadding", + rowspan: "rowSpan", + colspan: "colSpan", + usemap: "useMap", + frameborder: "frameBorder", + contenteditable: "contentEditable" + }, + + prop: function( elem, name, value ) { + var nType = elem.nodeType; + + // don't get/set properties on text, comment and attribute nodes + if ( !elem || nType === 3 || nType === 8 || nType === 2 ) { + return undefined; + } + + var ret, hooks, + notxml = nType !== 1 || !jQuery.isXMLDoc( elem ); + + if ( notxml ) { + // Fix name and attach hooks + name = jQuery.propFix[ name ] || name; + hooks = jQuery.propHooks[ name ]; + } + + if ( value !== undefined ) { + if ( hooks && "set" in hooks && (ret = hooks.set( elem, value, name )) !== undefined ) { + return ret; + + } else { + return (elem[ name ] = value); + } + + } else { + if ( hooks && "get" in hooks && (ret = hooks.get( elem, name )) !== undefined ) { + return ret; + + } else { + return elem[ name ]; + } + } + }, + + propHooks: {} +}); + +// Hook for boolean attributes +boolHook = { + get: function( elem, name ) { + // Align boolean attributes with corresponding properties + return jQuery.prop( elem, name ) ? + name.toLowerCase() : + undefined; + }, + set: function( elem, value, name ) { + var propName; + if ( value === false ) { + // Remove boolean attributes when set to false + jQuery.removeAttr( elem, name ); + } else { + // value is true since we know at this point it's type boolean and not false + // Set boolean attributes to the same name and set the DOM property + propName = jQuery.propFix[ name ] || name; + if ( propName in elem ) { + // Only set the IDL specifically if it already exists on the element + elem[ propName ] = true; + } + + elem.setAttribute( name, name.toLowerCase() ); + } + return name; + } +}; + +// IE6/7 do not support getting/setting some attributes with get/setAttribute +if ( !jQuery.support.getSetAttribute ) { + + // propFix is more comprehensive and contains all fixes + jQuery.attrFix = jQuery.propFix; + + // Use this for any attribute on a form in IE6/7 + formHook = jQuery.attrHooks.name = jQuery.attrHooks.title = jQuery.valHooks.button = { + get: function( elem, name ) { + var ret; + ret = elem.getAttributeNode( name ); + // Return undefined if nodeValue is empty string + return ret && ret.nodeValue !== "" ? + ret.nodeValue : + undefined; + }, + set: function( elem, value, name ) { + // Check form objects in IE (multiple bugs related) + // Only use nodeValue if the attribute node exists on the form + var ret = elem.getAttributeNode( name ); + if ( ret ) { + ret.nodeValue = value; + return value; + } + } + }; + + // Set width and height to auto instead of 0 on empty string( Bug #8150 ) + // This is for removals + jQuery.each([ "width", "height" ], function( i, name ) { + jQuery.attrHooks[ name ] = jQuery.extend( jQuery.attrHooks[ name ], { + set: function( elem, value ) { + if ( value === "" ) { + elem.setAttribute( name, "auto" ); + return value; + } + } + }); + }); +} + + +// Some attributes require a special call on IE +if ( !jQuery.support.hrefNormalized ) { + jQuery.each([ "href", "src", "width", "height" ], function( i, name ) { + jQuery.attrHooks[ name ] = jQuery.extend( jQuery.attrHooks[ name ], { + get: function( elem ) { + var ret = elem.getAttribute( name, 2 ); + return ret === null ? undefined : ret; + } + }); + }); +} + +if ( !jQuery.support.style ) { + jQuery.attrHooks.style = { + get: function( elem ) { + // Return undefined in the case of empty string + // Normalize to lowercase since IE uppercases css property names + return elem.style.cssText.toLowerCase() || undefined; + }, + set: function( elem, value ) { + return (elem.style.cssText = "" + value); + } + }; +} + +// Safari mis-reports the default selected property of an option +// Accessing the parent's selectedIndex property fixes it +if ( !jQuery.support.optSelected ) { + jQuery.propHooks.selected = jQuery.extend( jQuery.propHooks.selected, { + get: function( elem ) { + var parent = elem.parentNode; + + if ( parent ) { + parent.selectedIndex; + + // Make sure that it also works with optgroups, see #5701 + if ( parent.parentNode ) { + parent.parentNode.selectedIndex; + } + } + } + }); +} + +// Radios and checkboxes getter/setter +if ( !jQuery.support.checkOn ) { + jQuery.each([ "radio", "checkbox" ], function() { + jQuery.valHooks[ this ] = { + get: function( elem ) { + // Handle the case where in Webkit "" is returned instead of "on" if a value isn't specified + return elem.getAttribute("value") === null ? "on" : elem.value; + } + }; + }); +} +jQuery.each([ "radio", "checkbox" ], function() { + jQuery.valHooks[ this ] = jQuery.extend( jQuery.valHooks[ this ], { + set: function( elem, value ) { + if ( jQuery.isArray( value ) ) { + return (elem.checked = jQuery.inArray( jQuery(elem).val(), value ) >= 0); + } + } + }); +}); + + + + +var rnamespaces = /\.(.*)$/, + rformElems = /^(?:textarea|input|select)$/i, + rperiod = /\./g, + rspaces = / /g, + rescape = /[^\w\s.|`]/g, + fcleanup = function( nm ) { + return nm.replace(rescape, "\\$&"); + }; + +/* + * A number of helper functions used for managing events. + * Many of the ideas behind this code originated from + * Dean Edwards' addEvent library. + */ +jQuery.event = { + + // Bind an event to an element + // Original by Dean Edwards + add: function( elem, types, handler, data ) { + if ( elem.nodeType === 3 || elem.nodeType === 8 ) { + return; + } + + if ( handler === false ) { + handler = returnFalse; + } else if ( !handler ) { + // Fixes bug #7229. Fix recommended by jdalton + return; + } + + var handleObjIn, handleObj; + + if ( handler.handler ) { + handleObjIn = handler; + handler = handleObjIn.handler; + } + + // Make sure that the function being executed has a unique ID + if ( !handler.guid ) { + handler.guid = jQuery.guid++; + } + + // Init the element's event structure + var elemData = jQuery._data( elem ); + + // If no elemData is found then we must be trying to bind to one of the + // banned noData elements + if ( !elemData ) { + return; + } + + var events = elemData.events, + eventHandle = elemData.handle; + + if ( !events ) { + elemData.events = events = {}; + } + + if ( !eventHandle ) { + elemData.handle = eventHandle = function( e ) { + // Discard the second event of a jQuery.event.trigger() and + // when an event is called after a page has unloaded + return typeof jQuery !== "undefined" && (!e || jQuery.event.triggered !== e.type) ? + jQuery.event.handle.apply( eventHandle.elem, arguments ) : + undefined; + }; + } + + // Add elem as a property of the handle function + // This is to prevent a memory leak with non-native events in IE. + eventHandle.elem = elem; + + // Handle multiple events separated by a space + // jQuery(...).bind("mouseover mouseout", fn); + types = types.split(" "); + + var type, i = 0, namespaces; + + while ( (type = types[ i++ ]) ) { + handleObj = handleObjIn ? + jQuery.extend({}, handleObjIn) : + { handler: handler, data: data }; + + // Namespaced event handlers + if ( type.indexOf(".") > -1 ) { + namespaces = type.split("."); + type = namespaces.shift(); + handleObj.namespace = namespaces.slice(0).sort().join("."); + + } else { + namespaces = []; + handleObj.namespace = ""; + } + + handleObj.type = type; + if ( !handleObj.guid ) { + handleObj.guid = handler.guid; + } + + // Get the current list of functions bound to this event + var handlers = events[ type ], + special = jQuery.event.special[ type ] || {}; + + // Init the event handler queue + if ( !handlers ) { + handlers = events[ type ] = []; + + // Check for a special event handler + // Only use addEventListener/attachEvent if the special + // events handler returns false + if ( !special.setup || special.setup.call( elem, data, namespaces, eventHandle ) === false ) { + // Bind the global event handler to the element + if ( elem.addEventListener ) { + elem.addEventListener( type, eventHandle, false ); + + } else if ( elem.attachEvent ) { + elem.attachEvent( "on" + type, eventHandle ); + } + } + } + + if ( special.add ) { + special.add.call( elem, handleObj ); + + if ( !handleObj.handler.guid ) { + handleObj.handler.guid = handler.guid; + } + } + + // Add the function to the element's handler list + handlers.push( handleObj ); + + // Keep track of which events have been used, for event optimization + jQuery.event.global[ type ] = true; + } + + // Nullify elem to prevent memory leaks in IE + elem = null; + }, + + global: {}, + + // Detach an event or set of events from an element + remove: function( elem, types, handler, pos ) { + // don't do events on text and comment nodes + if ( elem.nodeType === 3 || elem.nodeType === 8 ) { + return; + } + + if ( handler === false ) { + handler = returnFalse; + } + + var ret, type, fn, j, i = 0, all, namespaces, namespace, special, eventType, handleObj, origType, + elemData = jQuery.hasData( elem ) && jQuery._data( elem ), + events = elemData && elemData.events; + + if ( !elemData || !events ) { + return; + } + + // types is actually an event object here + if ( types && types.type ) { + handler = types.handler; + types = types.type; + } + + // Unbind all events for the element + if ( !types || typeof types === "string" && types.charAt(0) === "." ) { + types = types || ""; + + for ( type in events ) { + jQuery.event.remove( elem, type + types ); + } + + return; + } + + // Handle multiple events separated by a space + // jQuery(...).unbind("mouseover mouseout", fn); + types = types.split(" "); + + while ( (type = types[ i++ ]) ) { + origType = type; + handleObj = null; + all = type.indexOf(".") < 0; + namespaces = []; + + if ( !all ) { + // Namespaced event handlers + namespaces = type.split("."); + type = namespaces.shift(); + + namespace = new RegExp("(^|\\.)" + + jQuery.map( namespaces.slice(0).sort(), fcleanup ).join("\\.(?:.*\\.)?") + "(\\.|$)"); + } + + eventType = events[ type ]; + + if ( !eventType ) { + continue; + } + + if ( !handler ) { + for ( j = 0; j < eventType.length; j++ ) { + handleObj = eventType[ j ]; + + if ( all || namespace.test( handleObj.namespace ) ) { + jQuery.event.remove( elem, origType, handleObj.handler, j ); + eventType.splice( j--, 1 ); + } + } + + continue; + } + + special = jQuery.event.special[ type ] || {}; + + for ( j = pos || 0; j < eventType.length; j++ ) { + handleObj = eventType[ j ]; + + if ( handler.guid === handleObj.guid ) { + // remove the given handler for the given type + if ( all || namespace.test( handleObj.namespace ) ) { + if ( pos == null ) { + eventType.splice( j--, 1 ); + } + + if ( special.remove ) { + special.remove.call( elem, handleObj ); + } + } + + if ( pos != null ) { + break; + } + } + } + + // remove generic event handler if no more handlers exist + if ( eventType.length === 0 || pos != null && eventType.length === 1 ) { + if ( !special.teardown || special.teardown.call( elem, namespaces ) === false ) { + jQuery.removeEvent( elem, type, elemData.handle ); + } + + ret = null; + delete events[ type ]; + } + } + + // Remove the expando if it's no longer used + if ( jQuery.isEmptyObject( events ) ) { + var handle = elemData.handle; + if ( handle ) { + handle.elem = null; + } + + delete elemData.events; + delete elemData.handle; + + if ( jQuery.isEmptyObject( elemData ) ) { + jQuery.removeData( elem, undefined, true ); + } + } + }, + + // Events that are safe to short-circuit if no handlers are attached. + // Native DOM events should not be added, they may have inline handlers. + customEvent: { + "getData": true, + "setData": true, + "changeData": true + }, + + trigger: function( event, data, elem, onlyHandlers ) { + // Event object or event type + var type = event.type || event, + namespaces = [], + exclusive; + + if ( type.indexOf("!") >= 0 ) { + // Exclusive events trigger only for the exact event (no namespaces) + type = type.slice(0, -1); + exclusive = true; + } + + if ( type.indexOf(".") >= 0 ) { + // Namespaced trigger; create a regexp to match event type in handle() + namespaces = type.split("."); + type = namespaces.shift(); + namespaces.sort(); + } + + if ( (!elem || jQuery.event.customEvent[ type ]) && !jQuery.event.global[ type ] ) { + // No jQuery handlers for this event type, and it can't have inline handlers + return; + } + + // Caller can pass in an Event, Object, or just an event type string + event = typeof event === "object" ? + // jQuery.Event object + event[ jQuery.expando ] ? event : + // Object literal + new jQuery.Event( type, event ) : + // Just the event type (string) + new jQuery.Event( type ); + + event.type = type; + event.exclusive = exclusive; + event.namespace = namespaces.join("."); + event.namespace_re = new RegExp("(^|\\.)" + namespaces.join("\\.(?:.*\\.)?") + "(\\.|$)"); + + // triggerHandler() and global events don't bubble or run the default action + if ( onlyHandlers || !elem ) { + event.preventDefault(); + event.stopPropagation(); + } + + // Handle a global trigger + if ( !elem ) { + // TODO: Stop taunting the data cache; remove global events and always attach to document + jQuery.each( jQuery.cache, function() { + // internalKey variable is just used to make it easier to find + // and potentially change this stuff later; currently it just + // points to jQuery.expando + var internalKey = jQuery.expando, + internalCache = this[ internalKey ]; + if ( internalCache && internalCache.events && internalCache.events[ type ] ) { + jQuery.event.trigger( event, data, internalCache.handle.elem ); + } + }); + return; + } + + // Don't do events on text and comment nodes + if ( elem.nodeType === 3 || elem.nodeType === 8 ) { + return; + } + + // Clean up the event in case it is being reused + event.result = undefined; + event.target = elem; + + // Clone any incoming data and prepend the event, creating the handler arg list + data = data != null ? jQuery.makeArray( data ) : []; + data.unshift( event ); + + var cur = elem, + // IE doesn't like method names with a colon (#3533, #8272) + ontype = type.indexOf(":") < 0 ? "on" + type : ""; + + // Fire event on the current element, then bubble up the DOM tree + do { + var handle = jQuery._data( cur, "handle" ); + + event.currentTarget = cur; + if ( handle ) { + handle.apply( cur, data ); + } + + // Trigger an inline bound script + if ( ontype && jQuery.acceptData( cur ) && cur[ ontype ] && cur[ ontype ].apply( cur, data ) === false ) { + event.result = false; + event.preventDefault(); + } + + // Bubble up to document, then to window + cur = cur.parentNode || cur.ownerDocument || cur === event.target.ownerDocument && window; + } while ( cur && !event.isPropagationStopped() ); + + // If nobody prevented the default action, do it now + if ( !event.isDefaultPrevented() ) { + var old, + special = jQuery.event.special[ type ] || {}; + + if ( (!special._default || special._default.call( elem.ownerDocument, event ) === false) && + !(type === "click" && jQuery.nodeName( elem, "a" )) && jQuery.acceptData( elem ) ) { + + // Call a native DOM method on the target with the same name name as the event. + // Can't use an .isFunction)() check here because IE6/7 fails that test. + // IE<9 dies on focus to hidden element (#1486), may want to revisit a try/catch. + try { + if ( ontype && elem[ type ] ) { + // Don't re-trigger an onFOO event when we call its FOO() method + old = elem[ ontype ]; + + if ( old ) { + elem[ ontype ] = null; + } + + jQuery.event.triggered = type; + elem[ type ](); + } + } catch ( ieError ) {} + + if ( old ) { + elem[ ontype ] = old; + } + + jQuery.event.triggered = undefined; + } + } + + return event.result; + }, + + handle: function( event ) { + event = jQuery.event.fix( event || window.event ); + // Snapshot the handlers list since a called handler may add/remove events. + var handlers = ((jQuery._data( this, "events" ) || {})[ event.type ] || []).slice(0), + run_all = !event.exclusive && !event.namespace, + args = Array.prototype.slice.call( arguments, 0 ); + + // Use the fix-ed Event rather than the (read-only) native event + args[0] = event; + event.currentTarget = this; + + for ( var j = 0, l = handlers.length; j < l; j++ ) { + var handleObj = handlers[ j ]; + + // Triggered event must 1) be non-exclusive and have no namespace, or + // 2) have namespace(s) a subset or equal to those in the bound event. + if ( run_all || event.namespace_re.test( handleObj.namespace ) ) { + // Pass in a reference to the handler function itself + // So that we can later remove it + event.handler = handleObj.handler; + event.data = handleObj.data; + event.handleObj = handleObj; + + var ret = handleObj.handler.apply( this, args ); + + if ( ret !== undefined ) { + event.result = ret; + if ( ret === false ) { + event.preventDefault(); + event.stopPropagation(); + } + } + + if ( event.isImmediatePropagationStopped() ) { + break; + } + } + } + return event.result; + }, + + props: "altKey attrChange attrName bubbles button cancelable charCode clientX clientY ctrlKey currentTarget data detail eventPhase fromElement handler keyCode layerX layerY metaKey newValue offsetX offsetY pageX pageY prevValue relatedNode relatedTarget screenX screenY shiftKey srcElement target toElement view wheelDelta which".split(" "), + + fix: function( event ) { + if ( event[ jQuery.expando ] ) { + return event; + } + + // store a copy of the original event object + // and "clone" to set read-only properties + var originalEvent = event; + event = jQuery.Event( originalEvent ); + + for ( var i = this.props.length, prop; i; ) { + prop = this.props[ --i ]; + event[ prop ] = originalEvent[ prop ]; + } + + // Fix target property, if necessary + if ( !event.target ) { + // Fixes #1925 where srcElement might not be defined either + event.target = event.srcElement || document; + } + + // check if target is a textnode (safari) + if ( event.target.nodeType === 3 ) { + event.target = event.target.parentNode; + } + + // Add relatedTarget, if necessary + if ( !event.relatedTarget && event.fromElement ) { + event.relatedTarget = event.fromElement === event.target ? event.toElement : event.fromElement; + } + + // Calculate pageX/Y if missing and clientX/Y available + if ( event.pageX == null && event.clientX != null ) { + var eventDocument = event.target.ownerDocument || document, + doc = eventDocument.documentElement, + body = eventDocument.body; + + event.pageX = event.clientX + (doc && doc.scrollLeft || body && body.scrollLeft || 0) - (doc && doc.clientLeft || body && body.clientLeft || 0); + event.pageY = event.clientY + (doc && doc.scrollTop || body && body.scrollTop || 0) - (doc && doc.clientTop || body && body.clientTop || 0); + } + + // Add which for key events + if ( event.which == null && (event.charCode != null || event.keyCode != null) ) { + event.which = event.charCode != null ? event.charCode : event.keyCode; + } + + // Add metaKey to non-Mac browsers (use ctrl for PC's and Meta for Macs) + if ( !event.metaKey && event.ctrlKey ) { + event.metaKey = event.ctrlKey; + } + + // Add which for click: 1 === left; 2 === middle; 3 === right + // Note: button is not normalized, so don't use it + if ( !event.which && event.button !== undefined ) { + event.which = (event.button & 1 ? 1 : ( event.button & 2 ? 3 : ( event.button & 4 ? 2 : 0 ) )); + } + + return event; + }, + + // Deprecated, use jQuery.guid instead + guid: 1E8, + + // Deprecated, use jQuery.proxy instead + proxy: jQuery.proxy, + + special: { + ready: { + // Make sure the ready event is setup + setup: jQuery.bindReady, + teardown: jQuery.noop + }, + + live: { + add: function( handleObj ) { + jQuery.event.add( this, + liveConvert( handleObj.origType, handleObj.selector ), + jQuery.extend({}, handleObj, {handler: liveHandler, guid: handleObj.handler.guid}) ); + }, + + remove: function( handleObj ) { + jQuery.event.remove( this, liveConvert( handleObj.origType, handleObj.selector ), handleObj ); + } + }, + + beforeunload: { + setup: function( data, namespaces, eventHandle ) { + // We only want to do this special case on windows + if ( jQuery.isWindow( this ) ) { + this.onbeforeunload = eventHandle; + } + }, + + teardown: function( namespaces, eventHandle ) { + if ( this.onbeforeunload === eventHandle ) { + this.onbeforeunload = null; + } + } + } + } +}; + +jQuery.removeEvent = document.removeEventListener ? + function( elem, type, handle ) { + if ( elem.removeEventListener ) { + elem.removeEventListener( type, handle, false ); + } + } : + function( elem, type, handle ) { + if ( elem.detachEvent ) { + elem.detachEvent( "on" + type, handle ); + } + }; + +jQuery.Event = function( src, props ) { + // Allow instantiation without the 'new' keyword + if ( !this.preventDefault ) { + return new jQuery.Event( src, props ); + } + + // Event object + if ( src && src.type ) { + this.originalEvent = src; + this.type = src.type; + + // Events bubbling up the document may have been marked as prevented + // by a handler lower down the tree; reflect the correct value. + this.isDefaultPrevented = (src.defaultPrevented || src.returnValue === false || + src.getPreventDefault && src.getPreventDefault()) ? returnTrue : returnFalse; + + // Event type + } else { + this.type = src; + } + + // Put explicitly provided properties onto the event object + if ( props ) { + jQuery.extend( this, props ); + } + + // timeStamp is buggy for some events on Firefox(#3843) + // So we won't rely on the native value + this.timeStamp = jQuery.now(); + + // Mark it as fixed + this[ jQuery.expando ] = true; +}; + +function returnFalse() { + return false; +} +function returnTrue() { + return true; +} + +// jQuery.Event is based on DOM3 Events as specified by the ECMAScript Language Binding +// http://www.w3.org/TR/2003/WD-DOM-Level-3-Events-20030331/ecma-script-binding.html +jQuery.Event.prototype = { + preventDefault: function() { + this.isDefaultPrevented = returnTrue; + + var e = this.originalEvent; + if ( !e ) { + return; + } + + // if preventDefault exists run it on the original event + if ( e.preventDefault ) { + e.preventDefault(); + + // otherwise set the returnValue property of the original event to false (IE) + } else { + e.returnValue = false; + } + }, + stopPropagation: function() { + this.isPropagationStopped = returnTrue; + + var e = this.originalEvent; + if ( !e ) { + return; + } + // if stopPropagation exists run it on the original event + if ( e.stopPropagation ) { + e.stopPropagation(); + } + // otherwise set the cancelBubble property of the original event to true (IE) + e.cancelBubble = true; + }, + stopImmediatePropagation: function() { + this.isImmediatePropagationStopped = returnTrue; + this.stopPropagation(); + }, + isDefaultPrevented: returnFalse, + isPropagationStopped: returnFalse, + isImmediatePropagationStopped: returnFalse +}; + +// Checks if an event happened on an element within another element +// Used in jQuery.event.special.mouseenter and mouseleave handlers +var withinElement = function( event ) { + + // Check if mouse(over|out) are still within the same parent element + var related = event.relatedTarget, + inside = false, + eventType = event.type; + + event.type = event.data; + + if ( related !== this ) { + + if ( related ) { + inside = jQuery.contains( this, related ); + } + + if ( !inside ) { + + jQuery.event.handle.apply( this, arguments ); + + event.type = eventType; + } + } +}, + +// In case of event delegation, we only need to rename the event.type, +// liveHandler will take care of the rest. +delegate = function( event ) { + event.type = event.data; + jQuery.event.handle.apply( this, arguments ); +}; + +// Create mouseenter and mouseleave events +jQuery.each({ + mouseenter: "mouseover", + mouseleave: "mouseout" +}, function( orig, fix ) { + jQuery.event.special[ orig ] = { + setup: function( data ) { + jQuery.event.add( this, fix, data && data.selector ? delegate : withinElement, orig ); + }, + teardown: function( data ) { + jQuery.event.remove( this, fix, data && data.selector ? delegate : withinElement ); + } + }; +}); + +// submit delegation +if ( !jQuery.support.submitBubbles ) { + + jQuery.event.special.submit = { + setup: function( data, namespaces ) { + if ( !jQuery.nodeName( this, "form" ) ) { + jQuery.event.add(this, "click.specialSubmit", function( e ) { + var elem = e.target, + type = elem.type; + + if ( (type === "submit" || type === "image") && jQuery( elem ).closest("form").length ) { + trigger( "submit", this, arguments ); + } + }); + + jQuery.event.add(this, "keypress.specialSubmit", function( e ) { + var elem = e.target, + type = elem.type; + + if ( (type === "text" || type === "password") && jQuery( elem ).closest("form").length && e.keyCode === 13 ) { + trigger( "submit", this, arguments ); + } + }); + + } else { + return false; + } + }, + + teardown: function( namespaces ) { + jQuery.event.remove( this, ".specialSubmit" ); + } + }; + +} + +// change delegation, happens here so we have bind. +if ( !jQuery.support.changeBubbles ) { + + var changeFilters, + + getVal = function( elem ) { + var type = elem.type, val = elem.value; + + if ( type === "radio" || type === "checkbox" ) { + val = elem.checked; + + } else if ( type === "select-multiple" ) { + val = elem.selectedIndex > -1 ? + jQuery.map( elem.options, function( elem ) { + return elem.selected; + }).join("-") : + ""; + + } else if ( jQuery.nodeName( elem, "select" ) ) { + val = elem.selectedIndex; + } + + return val; + }, + + testChange = function testChange( e ) { + var elem = e.target, data, val; + + if ( !rformElems.test( elem.nodeName ) || elem.readOnly ) { + return; + } + + data = jQuery._data( elem, "_change_data" ); + val = getVal(elem); + + // the current data will be also retrieved by beforeactivate + if ( e.type !== "focusout" || elem.type !== "radio" ) { + jQuery._data( elem, "_change_data", val ); + } + + if ( data === undefined || val === data ) { + return; + } + + if ( data != null || val ) { + e.type = "change"; + e.liveFired = undefined; + jQuery.event.trigger( e, arguments[1], elem ); + } + }; + + jQuery.event.special.change = { + filters: { + focusout: testChange, + + beforedeactivate: testChange, + + click: function( e ) { + var elem = e.target, type = jQuery.nodeName( elem, "input" ) ? elem.type : ""; + + if ( type === "radio" || type === "checkbox" || jQuery.nodeName( elem, "select" ) ) { + testChange.call( this, e ); + } + }, + + // Change has to be called before submit + // Keydown will be called before keypress, which is used in submit-event delegation + keydown: function( e ) { + var elem = e.target, type = jQuery.nodeName( elem, "input" ) ? elem.type : ""; + + if ( (e.keyCode === 13 && !jQuery.nodeName( elem, "textarea" ) ) || + (e.keyCode === 32 && (type === "checkbox" || type === "radio")) || + type === "select-multiple" ) { + testChange.call( this, e ); + } + }, + + // Beforeactivate happens also before the previous element is blurred + // with this event you can't trigger a change event, but you can store + // information + beforeactivate: function( e ) { + var elem = e.target; + jQuery._data( elem, "_change_data", getVal(elem) ); + } + }, + + setup: function( data, namespaces ) { + if ( this.type === "file" ) { + return false; + } + + for ( var type in changeFilters ) { + jQuery.event.add( this, type + ".specialChange", changeFilters[type] ); + } + + return rformElems.test( this.nodeName ); + }, + + teardown: function( namespaces ) { + jQuery.event.remove( this, ".specialChange" ); + + return rformElems.test( this.nodeName ); + } + }; + + changeFilters = jQuery.event.special.change.filters; + + // Handle when the input is .focus()'d + changeFilters.focus = changeFilters.beforeactivate; +} + +function trigger( type, elem, args ) { + // Piggyback on a donor event to simulate a different one. + // Fake originalEvent to avoid donor's stopPropagation, but if the + // simulated event prevents default then we do the same on the donor. + // Don't pass args or remember liveFired; they apply to the donor event. + var event = jQuery.extend( {}, args[ 0 ] ); + event.type = type; + event.originalEvent = {}; + event.liveFired = undefined; + jQuery.event.handle.call( elem, event ); + if ( event.isDefaultPrevented() ) { + args[ 0 ].preventDefault(); + } +} + +// Create "bubbling" focus and blur events +if ( !jQuery.support.focusinBubbles ) { + jQuery.each({ focus: "focusin", blur: "focusout" }, function( orig, fix ) { + + // Attach a single capturing handler while someone wants focusin/focusout + var attaches = 0; + + jQuery.event.special[ fix ] = { + setup: function() { + if ( attaches++ === 0 ) { + document.addEventListener( orig, handler, true ); + } + }, + teardown: function() { + if ( --attaches === 0 ) { + document.removeEventListener( orig, handler, true ); + } + } + }; + + function handler( donor ) { + // Donor event is always a native one; fix it and switch its type. + // Let focusin/out handler cancel the donor focus/blur event. + var e = jQuery.event.fix( donor ); + e.type = fix; + e.originalEvent = {}; + jQuery.event.trigger( e, null, e.target ); + if ( e.isDefaultPrevented() ) { + donor.preventDefault(); + } + } + }); +} + +jQuery.each(["bind", "one"], function( i, name ) { + jQuery.fn[ name ] = function( type, data, fn ) { + var handler; + + // Handle object literals + if ( typeof type === "object" ) { + for ( var key in type ) { + this[ name ](key, data, type[key], fn); + } + return this; + } + + if ( arguments.length === 2 || data === false ) { + fn = data; + data = undefined; + } + + if ( name === "one" ) { + handler = function( event ) { + jQuery( this ).unbind( event, handler ); + return fn.apply( this, arguments ); + }; + handler.guid = fn.guid || jQuery.guid++; + } else { + handler = fn; + } + + if ( type === "unload" && name !== "one" ) { + this.one( type, data, fn ); + + } else { + for ( var i = 0, l = this.length; i < l; i++ ) { + jQuery.event.add( this[i], type, handler, data ); + } + } + + return this; + }; +}); + +jQuery.fn.extend({ + unbind: function( type, fn ) { + // Handle object literals + if ( typeof type === "object" && !type.preventDefault ) { + for ( var key in type ) { + this.unbind(key, type[key]); + } + + } else { + for ( var i = 0, l = this.length; i < l; i++ ) { + jQuery.event.remove( this[i], type, fn ); + } + } + + return this; + }, + + delegate: function( selector, types, data, fn ) { + return this.live( types, data, fn, selector ); + }, + + undelegate: function( selector, types, fn ) { + if ( arguments.length === 0 ) { + return this.unbind( "live" ); + + } else { + return this.die( types, null, fn, selector ); + } + }, + + trigger: function( type, data ) { + return this.each(function() { + jQuery.event.trigger( type, data, this ); + }); + }, + + triggerHandler: function( type, data ) { + if ( this[0] ) { + return jQuery.event.trigger( type, data, this[0], true ); + } + }, + + toggle: function( fn ) { + // Save reference to arguments for access in closure + var args = arguments, + guid = fn.guid || jQuery.guid++, + i = 0, + toggler = function( event ) { + // Figure out which function to execute + var lastToggle = ( jQuery.data( this, "lastToggle" + fn.guid ) || 0 ) % i; + jQuery.data( this, "lastToggle" + fn.guid, lastToggle + 1 ); + + // Make sure that clicks stop + event.preventDefault(); + + // and execute the function + return args[ lastToggle ].apply( this, arguments ) || false; + }; + + // link all the functions, so any of them can unbind this click handler + toggler.guid = guid; + while ( i < args.length ) { + args[ i++ ].guid = guid; + } + + return this.click( toggler ); + }, + + hover: function( fnOver, fnOut ) { + return this.mouseenter( fnOver ).mouseleave( fnOut || fnOver ); + } +}); + +var liveMap = { + focus: "focusin", + blur: "focusout", + mouseenter: "mouseover", + mouseleave: "mouseout" +}; + +jQuery.each(["live", "die"], function( i, name ) { + jQuery.fn[ name ] = function( types, data, fn, origSelector /* Internal Use Only */ ) { + var type, i = 0, match, namespaces, preType, + selector = origSelector || this.selector, + context = origSelector ? this : jQuery( this.context ); + + if ( typeof types === "object" && !types.preventDefault ) { + for ( var key in types ) { + context[ name ]( key, data, types[key], selector ); + } + + return this; + } + + if ( name === "die" && !types && + origSelector && origSelector.charAt(0) === "." ) { + + context.unbind( origSelector ); + + return this; + } + + if ( data === false || jQuery.isFunction( data ) ) { + fn = data || returnFalse; + data = undefined; + } + + types = (types || "").split(" "); + + while ( (type = types[ i++ ]) != null ) { + match = rnamespaces.exec( type ); + namespaces = ""; + + if ( match ) { + namespaces = match[0]; + type = type.replace( rnamespaces, "" ); + } + + if ( type === "hover" ) { + types.push( "mouseenter" + namespaces, "mouseleave" + namespaces ); + continue; + } + + preType = type; + + if ( liveMap[ type ] ) { + types.push( liveMap[ type ] + namespaces ); + type = type + namespaces; + + } else { + type = (liveMap[ type ] || type) + namespaces; + } + + if ( name === "live" ) { + // bind live handler + for ( var j = 0, l = context.length; j < l; j++ ) { + jQuery.event.add( context[j], "live." + liveConvert( type, selector ), + { data: data, selector: selector, handler: fn, origType: type, origHandler: fn, preType: preType } ); + } + + } else { + // unbind live handler + context.unbind( "live." + liveConvert( type, selector ), fn ); + } + } + + return this; + }; +}); + +function liveHandler( event ) { + var stop, maxLevel, related, match, handleObj, elem, j, i, l, data, close, namespace, ret, + elems = [], + selectors = [], + events = jQuery._data( this, "events" ); + + // Make sure we avoid non-left-click bubbling in Firefox (#3861) and disabled elements in IE (#6911) + if ( event.liveFired === this || !events || !events.live || event.target.disabled || event.button && event.type === "click" ) { + return; + } + + if ( event.namespace ) { + namespace = new RegExp("(^|\\.)" + event.namespace.split(".").join("\\.(?:.*\\.)?") + "(\\.|$)"); + } + + event.liveFired = this; + + var live = events.live.slice(0); + + for ( j = 0; j < live.length; j++ ) { + handleObj = live[j]; + + if ( handleObj.origType.replace( rnamespaces, "" ) === event.type ) { + selectors.push( handleObj.selector ); + + } else { + live.splice( j--, 1 ); + } + } + + match = jQuery( event.target ).closest( selectors, event.currentTarget ); + + for ( i = 0, l = match.length; i < l; i++ ) { + close = match[i]; + + for ( j = 0; j < live.length; j++ ) { + handleObj = live[j]; + + if ( close.selector === handleObj.selector && (!namespace || namespace.test( handleObj.namespace )) && !close.elem.disabled ) { + elem = close.elem; + related = null; + + // Those two events require additional checking + if ( handleObj.preType === "mouseenter" || handleObj.preType === "mouseleave" ) { + event.type = handleObj.preType; + related = jQuery( event.relatedTarget ).closest( handleObj.selector )[0]; + + // Make sure not to accidentally match a child element with the same selector + if ( related && jQuery.contains( elem, related ) ) { + related = elem; + } + } + + if ( !related || related !== elem ) { + elems.push({ elem: elem, handleObj: handleObj, level: close.level }); + } + } + } + } + + for ( i = 0, l = elems.length; i < l; i++ ) { + match = elems[i]; + + if ( maxLevel && match.level > maxLevel ) { + break; + } + + event.currentTarget = match.elem; + event.data = match.handleObj.data; + event.handleObj = match.handleObj; + + ret = match.handleObj.origHandler.apply( match.elem, arguments ); + + if ( ret === false || event.isPropagationStopped() ) { + maxLevel = match.level; + + if ( ret === false ) { + stop = false; + } + if ( event.isImmediatePropagationStopped() ) { + break; + } + } + } + + return stop; +} + +function liveConvert( type, selector ) { + return (type && type !== "*" ? type + "." : "") + selector.replace(rperiod, "`").replace(rspaces, "&"); +} + +jQuery.each( ("blur focus focusin focusout load resize scroll unload click dblclick " + + "mousedown mouseup mousemove mouseover mouseout mouseenter mouseleave " + + "change select submit keydown keypress keyup error").split(" "), function( i, name ) { + + // Handle event binding + jQuery.fn[ name ] = function( data, fn ) { + if ( fn == null ) { + fn = data; + data = null; + } + + return arguments.length > 0 ? + this.bind( name, data, fn ) : + this.trigger( name ); + }; + + if ( jQuery.attrFn ) { + jQuery.attrFn[ name ] = true; + } +}); + + + +/*! + * Sizzle CSS Selector Engine + * Copyright 2011, The Dojo Foundation + * Released under the MIT, BSD, and GPL Licenses. + * More information: http://sizzlejs.com/ + */ +(function(){ + +var chunker = /((?:\((?:\([^()]+\)|[^()]+)+\)|\[(?:\[[^\[\]]*\]|['"][^'"]*['"]|[^\[\]'"]+)+\]|\\.|[^ >+~,(\[\\]+)+|[>+~])(\s*,\s*)?((?:.|\r|\n)*)/g, + done = 0, + toString = Object.prototype.toString, + hasDuplicate = false, + baseHasDuplicate = true, + rBackslash = /\\/g, + rNonWord = /\W/; + +// Here we check if the JavaScript engine is using some sort of +// optimization where it does not always call our comparision +// function. If that is the case, discard the hasDuplicate value. +// Thus far that includes Google Chrome. +[0, 0].sort(function() { + baseHasDuplicate = false; + return 0; +}); + +var Sizzle = function( selector, context, results, seed ) { + results = results || []; + context = context || document; + + var origContext = context; + + if ( context.nodeType !== 1 && context.nodeType !== 9 ) { + return []; + } + + if ( !selector || typeof selector !== "string" ) { + return results; + } + + var m, set, checkSet, extra, ret, cur, pop, i, + prune = true, + contextXML = Sizzle.isXML( context ), + parts = [], + soFar = selector; + + // Reset the position of the chunker regexp (start from head) + do { + chunker.exec( "" ); + m = chunker.exec( soFar ); + + if ( m ) { + soFar = m[3]; + + parts.push( m[1] ); + + if ( m[2] ) { + extra = m[3]; + break; + } + } + } while ( m ); + + if ( parts.length > 1 && origPOS.exec( selector ) ) { + + if ( parts.length === 2 && Expr.relative[ parts[0] ] ) { + set = posProcess( parts[0] + parts[1], context ); + + } else { + set = Expr.relative[ parts[0] ] ? + [ context ] : + Sizzle( parts.shift(), context ); + + while ( parts.length ) { + selector = parts.shift(); + + if ( Expr.relative[ selector ] ) { + selector += parts.shift(); + } + + set = posProcess( selector, set ); + } + } + + } else { + // Take a shortcut and set the context if the root selector is an ID + // (but not if it'll be faster if the inner selector is an ID) + if ( !seed && parts.length > 1 && context.nodeType === 9 && !contextXML && + Expr.match.ID.test(parts[0]) && !Expr.match.ID.test(parts[parts.length - 1]) ) { + + ret = Sizzle.find( parts.shift(), context, contextXML ); + context = ret.expr ? + Sizzle.filter( ret.expr, ret.set )[0] : + ret.set[0]; + } + + if ( context ) { + ret = seed ? + { expr: parts.pop(), set: makeArray(seed) } : + Sizzle.find( parts.pop(), parts.length === 1 && (parts[0] === "~" || parts[0] === "+") && context.parentNode ? context.parentNode : context, contextXML ); + + set = ret.expr ? + Sizzle.filter( ret.expr, ret.set ) : + ret.set; + + if ( parts.length > 0 ) { + checkSet = makeArray( set ); + + } else { + prune = false; + } + + while ( parts.length ) { + cur = parts.pop(); + pop = cur; + + if ( !Expr.relative[ cur ] ) { + cur = ""; + } else { + pop = parts.pop(); + } + + if ( pop == null ) { + pop = context; + } + + Expr.relative[ cur ]( checkSet, pop, contextXML ); + } + + } else { + checkSet = parts = []; + } + } + + if ( !checkSet ) { + checkSet = set; + } + + if ( !checkSet ) { + Sizzle.error( cur || selector ); + } + + if ( toString.call(checkSet) === "[object Array]" ) { + if ( !prune ) { + results.push.apply( results, checkSet ); + + } else if ( context && context.nodeType === 1 ) { + for ( i = 0; checkSet[i] != null; i++ ) { + if ( checkSet[i] && (checkSet[i] === true || checkSet[i].nodeType === 1 && Sizzle.contains(context, checkSet[i])) ) { + results.push( set[i] ); + } + } + + } else { + for ( i = 0; checkSet[i] != null; i++ ) { + if ( checkSet[i] && checkSet[i].nodeType === 1 ) { + results.push( set[i] ); + } + } + } + + } else { + makeArray( checkSet, results ); + } + + if ( extra ) { + Sizzle( extra, origContext, results, seed ); + Sizzle.uniqueSort( results ); + } + + return results; +}; + +Sizzle.uniqueSort = function( results ) { + if ( sortOrder ) { + hasDuplicate = baseHasDuplicate; + results.sort( sortOrder ); + + if ( hasDuplicate ) { + for ( var i = 1; i < results.length; i++ ) { + if ( results[i] === results[ i - 1 ] ) { + results.splice( i--, 1 ); + } + } + } + } + + return results; +}; + +Sizzle.matches = function( expr, set ) { + return Sizzle( expr, null, null, set ); +}; + +Sizzle.matchesSelector = function( node, expr ) { + return Sizzle( expr, null, null, [node] ).length > 0; +}; + +Sizzle.find = function( expr, context, isXML ) { + var set; + + if ( !expr ) { + return []; + } + + for ( var i = 0, l = Expr.order.length; i < l; i++ ) { + var match, + type = Expr.order[i]; + + if ( (match = Expr.leftMatch[ type ].exec( expr )) ) { + var left = match[1]; + match.splice( 1, 1 ); + + if ( left.substr( left.length - 1 ) !== "\\" ) { + match[1] = (match[1] || "").replace( rBackslash, "" ); + set = Expr.find[ type ]( match, context, isXML ); + + if ( set != null ) { + expr = expr.replace( Expr.match[ type ], "" ); + break; + } + } + } + } + + if ( !set ) { + set = typeof context.getElementsByTagName !== "undefined" ? + context.getElementsByTagName( "*" ) : + []; + } + + return { set: set, expr: expr }; +}; + +Sizzle.filter = function( expr, set, inplace, not ) { + var match, anyFound, + old = expr, + result = [], + curLoop = set, + isXMLFilter = set && set[0] && Sizzle.isXML( set[0] ); + + while ( expr && set.length ) { + for ( var type in Expr.filter ) { + if ( (match = Expr.leftMatch[ type ].exec( expr )) != null && match[2] ) { + var found, item, + filter = Expr.filter[ type ], + left = match[1]; + + anyFound = false; + + match.splice(1,1); + + if ( left.substr( left.length - 1 ) === "\\" ) { + continue; + } + + if ( curLoop === result ) { + result = []; + } + + if ( Expr.preFilter[ type ] ) { + match = Expr.preFilter[ type ]( match, curLoop, inplace, result, not, isXMLFilter ); + + if ( !match ) { + anyFound = found = true; + + } else if ( match === true ) { + continue; + } + } + + if ( match ) { + for ( var i = 0; (item = curLoop[i]) != null; i++ ) { + if ( item ) { + found = filter( item, match, i, curLoop ); + var pass = not ^ !!found; + + if ( inplace && found != null ) { + if ( pass ) { + anyFound = true; + + } else { + curLoop[i] = false; + } + + } else if ( pass ) { + result.push( item ); + anyFound = true; + } + } + } + } + + if ( found !== undefined ) { + if ( !inplace ) { + curLoop = result; + } + + expr = expr.replace( Expr.match[ type ], "" ); + + if ( !anyFound ) { + return []; + } + + break; + } + } + } + + // Improper expression + if ( expr === old ) { + if ( anyFound == null ) { + Sizzle.error( expr ); + + } else { + break; + } + } + + old = expr; + } + + return curLoop; +}; + +Sizzle.error = function( msg ) { + throw "Syntax error, unrecognized expression: " + msg; +}; + +var Expr = Sizzle.selectors = { + order: [ "ID", "NAME", "TAG" ], + + match: { + ID: /#((?:[\w\u00c0-\uFFFF\-]|\\.)+)/, + CLASS: /\.((?:[\w\u00c0-\uFFFF\-]|\\.)+)/, + NAME: /\[name=['"]*((?:[\w\u00c0-\uFFFF\-]|\\.)+)['"]*\]/, + ATTR: /\[\s*((?:[\w\u00c0-\uFFFF\-]|\\.)+)\s*(?:(\S?=)\s*(?:(['"])(.*?)\3|(#?(?:[\w\u00c0-\uFFFF\-]|\\.)*)|)|)\s*\]/, + TAG: /^((?:[\w\u00c0-\uFFFF\*\-]|\\.)+)/, + CHILD: /:(only|nth|last|first)-child(?:\(\s*(even|odd|(?:[+\-]?\d+|(?:[+\-]?\d*)?n\s*(?:[+\-]\s*\d+)?))\s*\))?/, + POS: /:(nth|eq|gt|lt|first|last|even|odd)(?:\((\d*)\))?(?=[^\-]|$)/, + PSEUDO: /:((?:[\w\u00c0-\uFFFF\-]|\\.)+)(?:\((['"]?)((?:\([^\)]+\)|[^\(\)]*)+)\2\))?/ + }, + + leftMatch: {}, + + attrMap: { + "class": "className", + "for": "htmlFor" + }, + + attrHandle: { + href: function( elem ) { + return elem.getAttribute( "href" ); + }, + type: function( elem ) { + return elem.getAttribute( "type" ); + } + }, + + relative: { + "+": function(checkSet, part){ + var isPartStr = typeof part === "string", + isTag = isPartStr && !rNonWord.test( part ), + isPartStrNotTag = isPartStr && !isTag; + + if ( isTag ) { + part = part.toLowerCase(); + } + + for ( var i = 0, l = checkSet.length, elem; i < l; i++ ) { + if ( (elem = checkSet[i]) ) { + while ( (elem = elem.previousSibling) && elem.nodeType !== 1 ) {} + + checkSet[i] = isPartStrNotTag || elem && elem.nodeName.toLowerCase() === part ? + elem || false : + elem === part; + } + } + + if ( isPartStrNotTag ) { + Sizzle.filter( part, checkSet, true ); + } + }, + + ">": function( checkSet, part ) { + var elem, + isPartStr = typeof part === "string", + i = 0, + l = checkSet.length; + + if ( isPartStr && !rNonWord.test( part ) ) { + part = part.toLowerCase(); + + for ( ; i < l; i++ ) { + elem = checkSet[i]; + + if ( elem ) { + var parent = elem.parentNode; + checkSet[i] = parent.nodeName.toLowerCase() === part ? parent : false; + } + } + + } else { + for ( ; i < l; i++ ) { + elem = checkSet[i]; + + if ( elem ) { + checkSet[i] = isPartStr ? + elem.parentNode : + elem.parentNode === part; + } + } + + if ( isPartStr ) { + Sizzle.filter( part, checkSet, true ); + } + } + }, + + "": function(checkSet, part, isXML){ + var nodeCheck, + doneName = done++, + checkFn = dirCheck; + + if ( typeof part === "string" && !rNonWord.test( part ) ) { + part = part.toLowerCase(); + nodeCheck = part; + checkFn = dirNodeCheck; + } + + checkFn( "parentNode", part, doneName, checkSet, nodeCheck, isXML ); + }, + + "~": function( checkSet, part, isXML ) { + var nodeCheck, + doneName = done++, + checkFn = dirCheck; + + if ( typeof part === "string" && !rNonWord.test( part ) ) { + part = part.toLowerCase(); + nodeCheck = part; + checkFn = dirNodeCheck; + } + + checkFn( "previousSibling", part, doneName, checkSet, nodeCheck, isXML ); + } + }, + + find: { + ID: function( match, context, isXML ) { + if ( typeof context.getElementById !== "undefined" && !isXML ) { + var m = context.getElementById(match[1]); + // Check parentNode to catch when Blackberry 4.6 returns + // nodes that are no longer in the document #6963 + return m && m.parentNode ? [m] : []; + } + }, + + NAME: function( match, context ) { + if ( typeof context.getElementsByName !== "undefined" ) { + var ret = [], + results = context.getElementsByName( match[1] ); + + for ( var i = 0, l = results.length; i < l; i++ ) { + if ( results[i].getAttribute("name") === match[1] ) { + ret.push( results[i] ); + } + } + + return ret.length === 0 ? null : ret; + } + }, + + TAG: function( match, context ) { + if ( typeof context.getElementsByTagName !== "undefined" ) { + return context.getElementsByTagName( match[1] ); + } + } + }, + preFilter: { + CLASS: function( match, curLoop, inplace, result, not, isXML ) { + match = " " + match[1].replace( rBackslash, "" ) + " "; + + if ( isXML ) { + return match; + } + + for ( var i = 0, elem; (elem = curLoop[i]) != null; i++ ) { + if ( elem ) { + if ( not ^ (elem.className && (" " + elem.className + " ").replace(/[\t\n\r]/g, " ").indexOf(match) >= 0) ) { + if ( !inplace ) { + result.push( elem ); + } + + } else if ( inplace ) { + curLoop[i] = false; + } + } + } + + return false; + }, + + ID: function( match ) { + return match[1].replace( rBackslash, "" ); + }, + + TAG: function( match, curLoop ) { + return match[1].replace( rBackslash, "" ).toLowerCase(); + }, + + CHILD: function( match ) { + if ( match[1] === "nth" ) { + if ( !match[2] ) { + Sizzle.error( match[0] ); + } + + match[2] = match[2].replace(/^\+|\s*/g, ''); + + // parse equations like 'even', 'odd', '5', '2n', '3n+2', '4n-1', '-n+6' + var test = /(-?)(\d*)(?:n([+\-]?\d*))?/.exec( + match[2] === "even" && "2n" || match[2] === "odd" && "2n+1" || + !/\D/.test( match[2] ) && "0n+" + match[2] || match[2]); + + // calculate the numbers (first)n+(last) including if they are negative + match[2] = (test[1] + (test[2] || 1)) - 0; + match[3] = test[3] - 0; + } + else if ( match[2] ) { + Sizzle.error( match[0] ); + } + + // TODO: Move to normal caching system + match[0] = done++; + + return match; + }, + + ATTR: function( match, curLoop, inplace, result, not, isXML ) { + var name = match[1] = match[1].replace( rBackslash, "" ); + + if ( !isXML && Expr.attrMap[name] ) { + match[1] = Expr.attrMap[name]; + } + + // Handle if an un-quoted value was used + match[4] = ( match[4] || match[5] || "" ).replace( rBackslash, "" ); + + if ( match[2] === "~=" ) { + match[4] = " " + match[4] + " "; + } + + return match; + }, + + PSEUDO: function( match, curLoop, inplace, result, not ) { + if ( match[1] === "not" ) { + // If we're dealing with a complex expression, or a simple one + if ( ( chunker.exec(match[3]) || "" ).length > 1 || /^\w/.test(match[3]) ) { + match[3] = Sizzle(match[3], null, null, curLoop); + + } else { + var ret = Sizzle.filter(match[3], curLoop, inplace, true ^ not); + + if ( !inplace ) { + result.push.apply( result, ret ); + } + + return false; + } + + } else if ( Expr.match.POS.test( match[0] ) || Expr.match.CHILD.test( match[0] ) ) { + return true; + } + + return match; + }, + + POS: function( match ) { + match.unshift( true ); + + return match; + } + }, + + filters: { + enabled: function( elem ) { + return elem.disabled === false && elem.type !== "hidden"; + }, + + disabled: function( elem ) { + return elem.disabled === true; + }, + + checked: function( elem ) { + return elem.checked === true; + }, + + selected: function( elem ) { + // Accessing this property makes selected-by-default + // options in Safari work properly + if ( elem.parentNode ) { + elem.parentNode.selectedIndex; + } + + return elem.selected === true; + }, + + parent: function( elem ) { + return !!elem.firstChild; + }, + + empty: function( elem ) { + return !elem.firstChild; + }, + + has: function( elem, i, match ) { + return !!Sizzle( match[3], elem ).length; + }, + + header: function( elem ) { + return (/h\d/i).test( elem.nodeName ); + }, + + text: function( elem ) { + var attr = elem.getAttribute( "type" ), type = elem.type; + // IE6 and 7 will map elem.type to 'text' for new HTML5 types (search, etc) + // use getAttribute instead to test this case + return elem.nodeName.toLowerCase() === "input" && "text" === type && ( attr === type || attr === null ); + }, + + radio: function( elem ) { + return elem.nodeName.toLowerCase() === "input" && "radio" === elem.type; + }, + + checkbox: function( elem ) { + return elem.nodeName.toLowerCase() === "input" && "checkbox" === elem.type; + }, + + file: function( elem ) { + return elem.nodeName.toLowerCase() === "input" && "file" === elem.type; + }, + + password: function( elem ) { + return elem.nodeName.toLowerCase() === "input" && "password" === elem.type; + }, + + submit: function( elem ) { + var name = elem.nodeName.toLowerCase(); + return (name === "input" || name === "button") && "submit" === elem.type; + }, + + image: function( elem ) { + return elem.nodeName.toLowerCase() === "input" && "image" === elem.type; + }, + + reset: function( elem ) { + var name = elem.nodeName.toLowerCase(); + return (name === "input" || name === "button") && "reset" === elem.type; + }, + + button: function( elem ) { + var name = elem.nodeName.toLowerCase(); + return name === "input" && "button" === elem.type || name === "button"; + }, + + input: function( elem ) { + return (/input|select|textarea|button/i).test( elem.nodeName ); + }, + + focus: function( elem ) { + return elem === elem.ownerDocument.activeElement; + } + }, + setFilters: { + first: function( elem, i ) { + return i === 0; + }, + + last: function( elem, i, match, array ) { + return i === array.length - 1; + }, + + even: function( elem, i ) { + return i % 2 === 0; + }, + + odd: function( elem, i ) { + return i % 2 === 1; + }, + + lt: function( elem, i, match ) { + return i < match[3] - 0; + }, + + gt: function( elem, i, match ) { + return i > match[3] - 0; + }, + + nth: function( elem, i, match ) { + return match[3] - 0 === i; + }, + + eq: function( elem, i, match ) { + return match[3] - 0 === i; + } + }, + filter: { + PSEUDO: function( elem, match, i, array ) { + var name = match[1], + filter = Expr.filters[ name ]; + + if ( filter ) { + return filter( elem, i, match, array ); + + } else if ( name === "contains" ) { + return (elem.textContent || elem.innerText || Sizzle.getText([ elem ]) || "").indexOf(match[3]) >= 0; + + } else if ( name === "not" ) { + var not = match[3]; + + for ( var j = 0, l = not.length; j < l; j++ ) { + if ( not[j] === elem ) { + return false; + } + } + + return true; + + } else { + Sizzle.error( name ); + } + }, + + CHILD: function( elem, match ) { + var type = match[1], + node = elem; + + switch ( type ) { + case "only": + case "first": + while ( (node = node.previousSibling) ) { + if ( node.nodeType === 1 ) { + return false; + } + } + + if ( type === "first" ) { + return true; + } + + node = elem; + + case "last": + while ( (node = node.nextSibling) ) { + if ( node.nodeType === 1 ) { + return false; + } + } + + return true; + + case "nth": + var first = match[2], + last = match[3]; + + if ( first === 1 && last === 0 ) { + return true; + } + + var doneName = match[0], + parent = elem.parentNode; + + if ( parent && (parent.sizcache !== doneName || !elem.nodeIndex) ) { + var count = 0; + + for ( node = parent.firstChild; node; node = node.nextSibling ) { + if ( node.nodeType === 1 ) { + node.nodeIndex = ++count; + } + } + + parent.sizcache = doneName; + } + + var diff = elem.nodeIndex - last; + + if ( first === 0 ) { + return diff === 0; + + } else { + return ( diff % first === 0 && diff / first >= 0 ); + } + } + }, + + ID: function( elem, match ) { + return elem.nodeType === 1 && elem.getAttribute("id") === match; + }, + + TAG: function( elem, match ) { + return (match === "*" && elem.nodeType === 1) || elem.nodeName.toLowerCase() === match; + }, + + CLASS: function( elem, match ) { + return (" " + (elem.className || elem.getAttribute("class")) + " ") + .indexOf( match ) > -1; + }, + + ATTR: function( elem, match ) { + var name = match[1], + result = Expr.attrHandle[ name ] ? + Expr.attrHandle[ name ]( elem ) : + elem[ name ] != null ? + elem[ name ] : + elem.getAttribute( name ), + value = result + "", + type = match[2], + check = match[4]; + + return result == null ? + type === "!=" : + type === "=" ? + value === check : + type === "*=" ? + value.indexOf(check) >= 0 : + type === "~=" ? + (" " + value + " ").indexOf(check) >= 0 : + !check ? + value && result !== false : + type === "!=" ? + value !== check : + type === "^=" ? + value.indexOf(check) === 0 : + type === "$=" ? + value.substr(value.length - check.length) === check : + type === "|=" ? + value === check || value.substr(0, check.length + 1) === check + "-" : + false; + }, + + POS: function( elem, match, i, array ) { + var name = match[2], + filter = Expr.setFilters[ name ]; + + if ( filter ) { + return filter( elem, i, match, array ); + } + } + } +}; + +var origPOS = Expr.match.POS, + fescape = function(all, num){ + return "\\" + (num - 0 + 1); + }; + +for ( var type in Expr.match ) { + Expr.match[ type ] = new RegExp( Expr.match[ type ].source + (/(?![^\[]*\])(?![^\(]*\))/.source) ); + Expr.leftMatch[ type ] = new RegExp( /(^(?:.|\r|\n)*?)/.source + Expr.match[ type ].source.replace(/\\(\d+)/g, fescape) ); +} + +var makeArray = function( array, results ) { + array = Array.prototype.slice.call( array, 0 ); + + if ( results ) { + results.push.apply( results, array ); + return results; + } + + return array; +}; + +// Perform a simple check to determine if the browser is capable of +// converting a NodeList to an array using builtin methods. +// Also verifies that the returned array holds DOM nodes +// (which is not the case in the Blackberry browser) +try { + Array.prototype.slice.call( document.documentElement.childNodes, 0 )[0].nodeType; + +// Provide a fallback method if it does not work +} catch( e ) { + makeArray = function( array, results ) { + var i = 0, + ret = results || []; + + if ( toString.call(array) === "[object Array]" ) { + Array.prototype.push.apply( ret, array ); + + } else { + if ( typeof array.length === "number" ) { + for ( var l = array.length; i < l; i++ ) { + ret.push( array[i] ); + } + + } else { + for ( ; array[i]; i++ ) { + ret.push( array[i] ); + } + } + } + + return ret; + }; +} + +var sortOrder, siblingCheck; + +if ( document.documentElement.compareDocumentPosition ) { + sortOrder = function( a, b ) { + if ( a === b ) { + hasDuplicate = true; + return 0; + } + + if ( !a.compareDocumentPosition || !b.compareDocumentPosition ) { + return a.compareDocumentPosition ? -1 : 1; + } + + return a.compareDocumentPosition(b) & 4 ? -1 : 1; + }; + +} else { + sortOrder = function( a, b ) { + // The nodes are identical, we can exit early + if ( a === b ) { + hasDuplicate = true; + return 0; + + // Fallback to using sourceIndex (in IE) if it's available on both nodes + } else if ( a.sourceIndex && b.sourceIndex ) { + return a.sourceIndex - b.sourceIndex; + } + + var al, bl, + ap = [], + bp = [], + aup = a.parentNode, + bup = b.parentNode, + cur = aup; + + // If the nodes are siblings (or identical) we can do a quick check + if ( aup === bup ) { + return siblingCheck( a, b ); + + // If no parents were found then the nodes are disconnected + } else if ( !aup ) { + return -1; + + } else if ( !bup ) { + return 1; + } + + // Otherwise they're somewhere else in the tree so we need + // to build up a full list of the parentNodes for comparison + while ( cur ) { + ap.unshift( cur ); + cur = cur.parentNode; + } + + cur = bup; + + while ( cur ) { + bp.unshift( cur ); + cur = cur.parentNode; + } + + al = ap.length; + bl = bp.length; + + // Start walking down the tree looking for a discrepancy + for ( var i = 0; i < al && i < bl; i++ ) { + if ( ap[i] !== bp[i] ) { + return siblingCheck( ap[i], bp[i] ); + } + } + + // We ended someplace up the tree so do a sibling check + return i === al ? + siblingCheck( a, bp[i], -1 ) : + siblingCheck( ap[i], b, 1 ); + }; + + siblingCheck = function( a, b, ret ) { + if ( a === b ) { + return ret; + } + + var cur = a.nextSibling; + + while ( cur ) { + if ( cur === b ) { + return -1; + } + + cur = cur.nextSibling; + } + + return 1; + }; +} + +// Utility function for retreiving the text value of an array of DOM nodes +Sizzle.getText = function( elems ) { + var ret = "", elem; + + for ( var i = 0; elems[i]; i++ ) { + elem = elems[i]; + + // Get the text from text nodes and CDATA nodes + if ( elem.nodeType === 3 || elem.nodeType === 4 ) { + ret += elem.nodeValue; + + // Traverse everything else, except comment nodes + } else if ( elem.nodeType !== 8 ) { + ret += Sizzle.getText( elem.childNodes ); + } + } + + return ret; +}; + +// Check to see if the browser returns elements by name when +// querying by getElementById (and provide a workaround) +(function(){ + // We're going to inject a fake input element with a specified name + var form = document.createElement("div"), + id = "script" + (new Date()).getTime(), + root = document.documentElement; + + form.innerHTML = "<a name='" + id + "'/>"; + + // Inject it into the root element, check its status, and remove it quickly + root.insertBefore( form, root.firstChild ); + + // The workaround has to do additional checks after a getElementById + // Which slows things down for other browsers (hence the branching) + if ( document.getElementById( id ) ) { + Expr.find.ID = function( match, context, isXML ) { + if ( typeof context.getElementById !== "undefined" && !isXML ) { + var m = context.getElementById(match[1]); + + return m ? + m.id === match[1] || typeof m.getAttributeNode !== "undefined" && m.getAttributeNode("id").nodeValue === match[1] ? + [m] : + undefined : + []; + } + }; + + Expr.filter.ID = function( elem, match ) { + var node = typeof elem.getAttributeNode !== "undefined" && elem.getAttributeNode("id"); + + return elem.nodeType === 1 && node && node.nodeValue === match; + }; + } + + root.removeChild( form ); + + // release memory in IE + root = form = null; +})(); + +(function(){ + // Check to see if the browser returns only elements + // when doing getElementsByTagName("*") + + // Create a fake element + var div = document.createElement("div"); + div.appendChild( document.createComment("") ); + + // Make sure no comments are found + if ( div.getElementsByTagName("*").length > 0 ) { + Expr.find.TAG = function( match, context ) { + var results = context.getElementsByTagName( match[1] ); + + // Filter out possible comments + if ( match[1] === "*" ) { + var tmp = []; + + for ( var i = 0; results[i]; i++ ) { + if ( results[i].nodeType === 1 ) { + tmp.push( results[i] ); + } + } + + results = tmp; + } + + return results; + }; + } + + // Check to see if an attribute returns normalized href attributes + div.innerHTML = "<a href='#'></a>"; + + if ( div.firstChild && typeof div.firstChild.getAttribute !== "undefined" && + div.firstChild.getAttribute("href") !== "#" ) { + + Expr.attrHandle.href = function( elem ) { + return elem.getAttribute( "href", 2 ); + }; + } + + // release memory in IE + div = null; +})(); + +if ( document.querySelectorAll ) { + (function(){ + var oldSizzle = Sizzle, + div = document.createElement("div"), + id = "__sizzle__"; + + div.innerHTML = "<p class='TEST'></p>"; + + // Safari can't handle uppercase or unicode characters when + // in quirks mode. + if ( div.querySelectorAll && div.querySelectorAll(".TEST").length === 0 ) { + return; + } + + Sizzle = function( query, context, extra, seed ) { + context = context || document; + + // Only use querySelectorAll on non-XML documents + // (ID selectors don't work in non-HTML documents) + if ( !seed && !Sizzle.isXML(context) ) { + // See if we find a selector to speed up + var match = /^(\w+$)|^\.([\w\-]+$)|^#([\w\-]+$)/.exec( query ); + + if ( match && (context.nodeType === 1 || context.nodeType === 9) ) { + // Speed-up: Sizzle("TAG") + if ( match[1] ) { + return makeArray( context.getElementsByTagName( query ), extra ); + + // Speed-up: Sizzle(".CLASS") + } else if ( match[2] && Expr.find.CLASS && context.getElementsByClassName ) { + return makeArray( context.getElementsByClassName( match[2] ), extra ); + } + } + + if ( context.nodeType === 9 ) { + // Speed-up: Sizzle("body") + // The body element only exists once, optimize finding it + if ( query === "body" && context.body ) { + return makeArray( [ context.body ], extra ); + + // Speed-up: Sizzle("#ID") + } else if ( match && match[3] ) { + var elem = context.getElementById( match[3] ); + + // Check parentNode to catch when Blackberry 4.6 returns + // nodes that are no longer in the document #6963 + if ( elem && elem.parentNode ) { + // Handle the case where IE and Opera return items + // by name instead of ID + if ( elem.id === match[3] ) { + return makeArray( [ elem ], extra ); + } + + } else { + return makeArray( [], extra ); + } + } + + try { + return makeArray( context.querySelectorAll(query), extra ); + } catch(qsaError) {} + + // qSA works strangely on Element-rooted queries + // We can work around this by specifying an extra ID on the root + // and working up from there (Thanks to Andrew Dupont for the technique) + // IE 8 doesn't work on object elements + } else if ( context.nodeType === 1 && context.nodeName.toLowerCase() !== "object" ) { + var oldContext = context, + old = context.getAttribute( "id" ), + nid = old || id, + hasParent = context.parentNode, + relativeHierarchySelector = /^\s*[+~]/.test( query ); + + if ( !old ) { + context.setAttribute( "id", nid ); + } else { + nid = nid.replace( /'/g, "\\$&" ); + } + if ( relativeHierarchySelector && hasParent ) { + context = context.parentNode; + } + + try { + if ( !relativeHierarchySelector || hasParent ) { + return makeArray( context.querySelectorAll( "[id='" + nid + "'] " + query ), extra ); + } + + } catch(pseudoError) { + } finally { + if ( !old ) { + oldContext.removeAttribute( "id" ); + } + } + } + } + + return oldSizzle(query, context, extra, seed); + }; + + for ( var prop in oldSizzle ) { + Sizzle[ prop ] = oldSizzle[ prop ]; + } + + // release memory in IE + div = null; + })(); +} + +(function(){ + var html = document.documentElement, + matches = html.matchesSelector || html.mozMatchesSelector || html.webkitMatchesSelector || html.msMatchesSelector; + + if ( matches ) { + // Check to see if it's possible to do matchesSelector + // on a disconnected node (IE 9 fails this) + var disconnectedMatch = !matches.call( document.createElement( "div" ), "div" ), + pseudoWorks = false; + + try { + // This should fail with an exception + // Gecko does not error, returns false instead + matches.call( document.documentElement, "[test!='']:sizzle" ); + + } catch( pseudoError ) { + pseudoWorks = true; + } + + Sizzle.matchesSelector = function( node, expr ) { + // Make sure that attribute selectors are quoted + expr = expr.replace(/\=\s*([^'"\]]*)\s*\]/g, "='$1']"); + + if ( !Sizzle.isXML( node ) ) { + try { + if ( pseudoWorks || !Expr.match.PSEUDO.test( expr ) && !/!=/.test( expr ) ) { + var ret = matches.call( node, expr ); + + // IE 9's matchesSelector returns false on disconnected nodes + if ( ret || !disconnectedMatch || + // As well, disconnected nodes are said to be in a document + // fragment in IE 9, so check for that + node.document && node.document.nodeType !== 11 ) { + return ret; + } + } + } catch(e) {} + } + + return Sizzle(expr, null, null, [node]).length > 0; + }; + } +})(); + +(function(){ + var div = document.createElement("div"); + + div.innerHTML = "<div class='test e'></div><div class='test'></div>"; + + // Opera can't find a second classname (in 9.6) + // Also, make sure that getElementsByClassName actually exists + if ( !div.getElementsByClassName || div.getElementsByClassName("e").length === 0 ) { + return; + } + + // Safari caches class attributes, doesn't catch changes (in 3.2) + div.lastChild.className = "e"; + + if ( div.getElementsByClassName("e").length === 1 ) { + return; + } + + Expr.order.splice(1, 0, "CLASS"); + Expr.find.CLASS = function( match, context, isXML ) { + if ( typeof context.getElementsByClassName !== "undefined" && !isXML ) { + return context.getElementsByClassName(match[1]); + } + }; + + // release memory in IE + div = null; +})(); + +function dirNodeCheck( dir, cur, doneName, checkSet, nodeCheck, isXML ) { + for ( var i = 0, l = checkSet.length; i < l; i++ ) { + var elem = checkSet[i]; + + if ( elem ) { + var match = false; + + elem = elem[dir]; + + while ( elem ) { + if ( elem.sizcache === doneName ) { + match = checkSet[elem.sizset]; + break; + } + + if ( elem.nodeType === 1 && !isXML ){ + elem.sizcache = doneName; + elem.sizset = i; + } + + if ( elem.nodeName.toLowerCase() === cur ) { + match = elem; + break; + } + + elem = elem[dir]; + } + + checkSet[i] = match; + } + } +} + +function dirCheck( dir, cur, doneName, checkSet, nodeCheck, isXML ) { + for ( var i = 0, l = checkSet.length; i < l; i++ ) { + var elem = checkSet[i]; + + if ( elem ) { + var match = false; + + elem = elem[dir]; + + while ( elem ) { + if ( elem.sizcache === doneName ) { + match = checkSet[elem.sizset]; + break; + } + + if ( elem.nodeType === 1 ) { + if ( !isXML ) { + elem.sizcache = doneName; + elem.sizset = i; + } + + if ( typeof cur !== "string" ) { + if ( elem === cur ) { + match = true; + break; + } + + } else if ( Sizzle.filter( cur, [elem] ).length > 0 ) { + match = elem; + break; + } + } + + elem = elem[dir]; + } + + checkSet[i] = match; + } + } +} + +if ( document.documentElement.contains ) { + Sizzle.contains = function( a, b ) { + return a !== b && (a.contains ? a.contains(b) : true); + }; + +} else if ( document.documentElement.compareDocumentPosition ) { + Sizzle.contains = function( a, b ) { + return !!(a.compareDocumentPosition(b) & 16); + }; + +} else { + Sizzle.contains = function() { + return false; + }; +} + +Sizzle.isXML = function( elem ) { + // documentElement is verified for cases where it doesn't yet exist + // (such as loading iframes in IE - #4833) + var documentElement = (elem ? elem.ownerDocument || elem : 0).documentElement; + + return documentElement ? documentElement.nodeName !== "HTML" : false; +}; + +var posProcess = function( selector, context ) { + var match, + tmpSet = [], + later = "", + root = context.nodeType ? [context] : context; + + // Position selectors must be done after the filter + // And so must :not(positional) so we move all PSEUDOs to the end + while ( (match = Expr.match.PSEUDO.exec( selector )) ) { + later += match[0]; + selector = selector.replace( Expr.match.PSEUDO, "" ); + } + + selector = Expr.relative[selector] ? selector + "*" : selector; + + for ( var i = 0, l = root.length; i < l; i++ ) { + Sizzle( selector, root[i], tmpSet ); + } + + return Sizzle.filter( later, tmpSet ); +}; + +// EXPOSE +jQuery.find = Sizzle; +jQuery.expr = Sizzle.selectors; +jQuery.expr[":"] = jQuery.expr.filters; +jQuery.unique = Sizzle.uniqueSort; +jQuery.text = Sizzle.getText; +jQuery.isXMLDoc = Sizzle.isXML; +jQuery.contains = Sizzle.contains; + + +})(); + + +var runtil = /Until$/, + rparentsprev = /^(?:parents|prevUntil|prevAll)/, + // Note: This RegExp should be improved, or likely pulled from Sizzle + rmultiselector = /,/, + isSimple = /^.[^:#\[\.,]*$/, + slice = Array.prototype.slice, + POS = jQuery.expr.match.POS, + // methods guaranteed to produce a unique set when starting from a unique set + guaranteedUnique = { + children: true, + contents: true, + next: true, + prev: true + }; + +jQuery.fn.extend({ + find: function( selector ) { + var self = this, + i, l; + + if ( typeof selector !== "string" ) { + return jQuery( selector ).filter(function() { + for ( i = 0, l = self.length; i < l; i++ ) { + if ( jQuery.contains( self[ i ], this ) ) { + return true; + } + } + }); + } + + var ret = this.pushStack( "", "find", selector ), + length, n, r; + + for ( i = 0, l = this.length; i < l; i++ ) { + length = ret.length; + jQuery.find( selector, this[i], ret ); + + if ( i > 0 ) { + // Make sure that the results are unique + for ( n = length; n < ret.length; n++ ) { + for ( r = 0; r < length; r++ ) { + if ( ret[r] === ret[n] ) { + ret.splice(n--, 1); + break; + } + } + } + } + } + + return ret; + }, + + has: function( target ) { + var targets = jQuery( target ); + return this.filter(function() { + for ( var i = 0, l = targets.length; i < l; i++ ) { + if ( jQuery.contains( this, targets[i] ) ) { + return true; + } + } + }); + }, + + not: function( selector ) { + return this.pushStack( winnow(this, selector, false), "not", selector); + }, + + filter: function( selector ) { + return this.pushStack( winnow(this, selector, true), "filter", selector ); + }, + + is: function( selector ) { + return !!selector && ( typeof selector === "string" ? + jQuery.filter( selector, this ).length > 0 : + this.filter( selector ).length > 0 ); + }, + + closest: function( selectors, context ) { + var ret = [], i, l, cur = this[0]; + + // Array + if ( jQuery.isArray( selectors ) ) { + var match, selector, + matches = {}, + level = 1; + + if ( cur && selectors.length ) { + for ( i = 0, l = selectors.length; i < l; i++ ) { + selector = selectors[i]; + + if ( !matches[ selector ] ) { + matches[ selector ] = POS.test( selector ) ? + jQuery( selector, context || this.context ) : + selector; + } + } + + while ( cur && cur.ownerDocument && cur !== context ) { + for ( selector in matches ) { + match = matches[ selector ]; + + if ( match.jquery ? match.index( cur ) > -1 : jQuery( cur ).is( match ) ) { + ret.push({ selector: selector, elem: cur, level: level }); + } + } + + cur = cur.parentNode; + level++; + } + } + + return ret; + } + + // String + var pos = POS.test( selectors ) || typeof selectors !== "string" ? + jQuery( selectors, context || this.context ) : + 0; + + for ( i = 0, l = this.length; i < l; i++ ) { + cur = this[i]; + + while ( cur ) { + if ( pos ? pos.index(cur) > -1 : jQuery.find.matchesSelector(cur, selectors) ) { + ret.push( cur ); + break; + + } else { + cur = cur.parentNode; + if ( !cur || !cur.ownerDocument || cur === context || cur.nodeType === 11 ) { + break; + } + } + } + } + + ret = ret.length > 1 ? jQuery.unique( ret ) : ret; + + return this.pushStack( ret, "closest", selectors ); + }, + + // Determine the position of an element within + // the matched set of elements + index: function( elem ) { + if ( !elem || typeof elem === "string" ) { + return jQuery.inArray( this[0], + // If it receives a string, the selector is used + // If it receives nothing, the siblings are used + elem ? jQuery( elem ) : this.parent().children() ); + } + // Locate the position of the desired element + return jQuery.inArray( + // If it receives a jQuery object, the first element is used + elem.jquery ? elem[0] : elem, this ); + }, + + add: function( selector, context ) { + var set = typeof selector === "string" ? + jQuery( selector, context ) : + jQuery.makeArray( selector && selector.nodeType ? [ selector ] : selector ), + all = jQuery.merge( this.get(), set ); + + return this.pushStack( isDisconnected( set[0] ) || isDisconnected( all[0] ) ? + all : + jQuery.unique( all ) ); + }, + + andSelf: function() { + return this.add( this.prevObject ); + } +}); + +// A painfully simple check to see if an element is disconnected +// from a document (should be improved, where feasible). +function isDisconnected( node ) { + return !node || !node.parentNode || node.parentNode.nodeType === 11; +} + +jQuery.each({ + parent: function( elem ) { + var parent = elem.parentNode; + return parent && parent.nodeType !== 11 ? parent : null; + }, + parents: function( elem ) { + return jQuery.dir( elem, "parentNode" ); + }, + parentsUntil: function( elem, i, until ) { + return jQuery.dir( elem, "parentNode", until ); + }, + next: function( elem ) { + return jQuery.nth( elem, 2, "nextSibling" ); + }, + prev: function( elem ) { + return jQuery.nth( elem, 2, "previousSibling" ); + }, + nextAll: function( elem ) { + return jQuery.dir( elem, "nextSibling" ); + }, + prevAll: function( elem ) { + return jQuery.dir( elem, "previousSibling" ); + }, + nextUntil: function( elem, i, until ) { + return jQuery.dir( elem, "nextSibling", until ); + }, + prevUntil: function( elem, i, until ) { + return jQuery.dir( elem, "previousSibling", until ); + }, + siblings: function( elem ) { + return jQuery.sibling( elem.parentNode.firstChild, elem ); + }, + children: function( elem ) { + return jQuery.sibling( elem.firstChild ); + }, + contents: function( elem ) { + return jQuery.nodeName( elem, "iframe" ) ? + elem.contentDocument || elem.contentWindow.document : + jQuery.makeArray( elem.childNodes ); + } +}, function( name, fn ) { + jQuery.fn[ name ] = function( until, selector ) { + var ret = jQuery.map( this, fn, until ), + // The variable 'args' was introduced in + // https://github.com/jquery/jquery/commit/52a0238 + // to work around a bug in Chrome 10 (Dev) and should be removed when the bug is fixed. + // http://code.google.com/p/v8/issues/detail?id=1050 + args = slice.call(arguments); + + if ( !runtil.test( name ) ) { + selector = until; + } + + if ( selector && typeof selector === "string" ) { + ret = jQuery.filter( selector, ret ); + } + + ret = this.length > 1 && !guaranteedUnique[ name ] ? jQuery.unique( ret ) : ret; + + if ( (this.length > 1 || rmultiselector.test( selector )) && rparentsprev.test( name ) ) { + ret = ret.reverse(); + } + + return this.pushStack( ret, name, args.join(",") ); + }; +}); + +jQuery.extend({ + filter: function( expr, elems, not ) { + if ( not ) { + expr = ":not(" + expr + ")"; + } + + return elems.length === 1 ? + jQuery.find.matchesSelector(elems[0], expr) ? [ elems[0] ] : [] : + jQuery.find.matches(expr, elems); + }, + + dir: function( elem, dir, until ) { + var matched = [], + cur = elem[ dir ]; + + while ( cur && cur.nodeType !== 9 && (until === undefined || cur.nodeType !== 1 || !jQuery( cur ).is( until )) ) { + if ( cur.nodeType === 1 ) { + matched.push( cur ); + } + cur = cur[dir]; + } + return matched; + }, + + nth: function( cur, result, dir, elem ) { + result = result || 1; + var num = 0; + + for ( ; cur; cur = cur[dir] ) { + if ( cur.nodeType === 1 && ++num === result ) { + break; + } + } + + return cur; + }, + + sibling: function( n, elem ) { + var r = []; + + for ( ; n; n = n.nextSibling ) { + if ( n.nodeType === 1 && n !== elem ) { + r.push( n ); + } + } + + return r; + } +}); + +// Implement the identical functionality for filter and not +function winnow( elements, qualifier, keep ) { + + // Can't pass null or undefined to indexOf in Firefox 4 + // Set to 0 to skip string check + qualifier = qualifier || 0; + + if ( jQuery.isFunction( qualifier ) ) { + return jQuery.grep(elements, function( elem, i ) { + var retVal = !!qualifier.call( elem, i, elem ); + return retVal === keep; + }); + + } else if ( qualifier.nodeType ) { + return jQuery.grep(elements, function( elem, i ) { + return (elem === qualifier) === keep; + }); + + } else if ( typeof qualifier === "string" ) { + var filtered = jQuery.grep(elements, function( elem ) { + return elem.nodeType === 1; + }); + + if ( isSimple.test( qualifier ) ) { + return jQuery.filter(qualifier, filtered, !keep); + } else { + qualifier = jQuery.filter( qualifier, filtered ); + } + } + + return jQuery.grep(elements, function( elem, i ) { + return (jQuery.inArray( elem, qualifier ) >= 0) === keep; + }); +} + + + + +var rinlinejQuery = / jQuery\d+="(?:\d+|null)"/g, + rleadingWhitespace = /^\s+/, + rxhtmlTag = /<(?!area|br|col|embed|hr|img|input|link|meta|param)(([\w:]+)[^>]*)\/>/ig, + rtagName = /<([\w:]+)/, + rtbody = /<tbody/i, + rhtml = /<|&#?\w+;/, + rnocache = /<(?:script|object|embed|option|style)/i, + // checked="checked" or checked + rchecked = /checked\s*(?:[^=]|=\s*.checked.)/i, + rscriptType = /\/(java|ecma)script/i, + rcleanScript = /^\s*<!(?:\[CDATA\[|\-\-)/, + wrapMap = { + option: [ 1, "<select multiple='multiple'>", "</select>" ], + legend: [ 1, "<fieldset>", "</fieldset>" ], + thead: [ 1, "<table>", "</table>" ], + tr: [ 2, "<table><tbody>", "</tbody></table>" ], + td: [ 3, "<table><tbody><tr>", "</tr></tbody></table>" ], + col: [ 2, "<table><tbody></tbody><colgroup>", "</colgroup></table>" ], + area: [ 1, "<map>", "</map>" ], + _default: [ 0, "", "" ] + }; + +wrapMap.optgroup = wrapMap.option; +wrapMap.tbody = wrapMap.tfoot = wrapMap.colgroup = wrapMap.caption = wrapMap.thead; +wrapMap.th = wrapMap.td; + +// IE can't serialize <link> and <script> tags normally +if ( !jQuery.support.htmlSerialize ) { + wrapMap._default = [ 1, "div<div>", "</div>" ]; +} + +jQuery.fn.extend({ + text: function( text ) { + if ( jQuery.isFunction(text) ) { + return this.each(function(i) { + var self = jQuery( this ); + + self.text( text.call(this, i, self.text()) ); + }); + } + + if ( typeof text !== "object" && text !== undefined ) { + return this.empty().append( (this[0] && this[0].ownerDocument || document).createTextNode( text ) ); + } + + return jQuery.text( this ); + }, + + wrapAll: function( html ) { + if ( jQuery.isFunction( html ) ) { + return this.each(function(i) { + jQuery(this).wrapAll( html.call(this, i) ); + }); + } + + if ( this[0] ) { + // The elements to wrap the target around + var wrap = jQuery( html, this[0].ownerDocument ).eq(0).clone(true); + + if ( this[0].parentNode ) { + wrap.insertBefore( this[0] ); + } + + wrap.map(function() { + var elem = this; + + while ( elem.firstChild && elem.firstChild.nodeType === 1 ) { + elem = elem.firstChild; + } + + return elem; + }).append( this ); + } + + return this; + }, + + wrapInner: function( html ) { + if ( jQuery.isFunction( html ) ) { + return this.each(function(i) { + jQuery(this).wrapInner( html.call(this, i) ); + }); + } + + return this.each(function() { + var self = jQuery( this ), + contents = self.contents(); + + if ( contents.length ) { + contents.wrapAll( html ); + + } else { + self.append( html ); + } + }); + }, + + wrap: function( html ) { + return this.each(function() { + jQuery( this ).wrapAll( html ); + }); + }, + + unwrap: function() { + return this.parent().each(function() { + if ( !jQuery.nodeName( this, "body" ) ) { + jQuery( this ).replaceWith( this.childNodes ); + } + }).end(); + }, + + append: function() { + return this.domManip(arguments, true, function( elem ) { + if ( this.nodeType === 1 ) { + this.appendChild( elem ); + } + }); + }, + + prepend: function() { + return this.domManip(arguments, true, function( elem ) { + if ( this.nodeType === 1 ) { + this.insertBefore( elem, this.firstChild ); + } + }); + }, + + before: function() { + if ( this[0] && this[0].parentNode ) { + return this.domManip(arguments, false, function( elem ) { + this.parentNode.insertBefore( elem, this ); + }); + } else if ( arguments.length ) { + var set = jQuery(arguments[0]); + set.push.apply( set, this.toArray() ); + return this.pushStack( set, "before", arguments ); + } + }, + + after: function() { + if ( this[0] && this[0].parentNode ) { + return this.domManip(arguments, false, function( elem ) { + this.parentNode.insertBefore( elem, this.nextSibling ); + }); + } else if ( arguments.length ) { + var set = this.pushStack( this, "after", arguments ); + set.push.apply( set, jQuery(arguments[0]).toArray() ); + return set; + } + }, + + // keepData is for internal use only--do not document + remove: function( selector, keepData ) { + for ( var i = 0, elem; (elem = this[i]) != null; i++ ) { + if ( !selector || jQuery.filter( selector, [ elem ] ).length ) { + if ( !keepData && elem.nodeType === 1 ) { + jQuery.cleanData( elem.getElementsByTagName("*") ); + jQuery.cleanData( [ elem ] ); + } + + if ( elem.parentNode ) { + elem.parentNode.removeChild( elem ); + } + } + } + + return this; + }, + + empty: function() { + for ( var i = 0, elem; (elem = this[i]) != null; i++ ) { + // Remove element nodes and prevent memory leaks + if ( elem.nodeType === 1 ) { + jQuery.cleanData( elem.getElementsByTagName("*") ); + } + + // Remove any remaining nodes + while ( elem.firstChild ) { + elem.removeChild( elem.firstChild ); + } + } + + return this; + }, + + clone: function( dataAndEvents, deepDataAndEvents ) { + dataAndEvents = dataAndEvents == null ? false : dataAndEvents; + deepDataAndEvents = deepDataAndEvents == null ? dataAndEvents : deepDataAndEvents; + + return this.map( function () { + return jQuery.clone( this, dataAndEvents, deepDataAndEvents ); + }); + }, + + html: function( value ) { + if ( value === undefined ) { + return this[0] && this[0].nodeType === 1 ? + this[0].innerHTML.replace(rinlinejQuery, "") : + null; + + // See if we can take a shortcut and just use innerHTML + } else if ( typeof value === "string" && !rnocache.test( value ) && + (jQuery.support.leadingWhitespace || !rleadingWhitespace.test( value )) && + !wrapMap[ (rtagName.exec( value ) || ["", ""])[1].toLowerCase() ] ) { + + value = value.replace(rxhtmlTag, "<$1></$2>"); + + try { + for ( var i = 0, l = this.length; i < l; i++ ) { + // Remove element nodes and prevent memory leaks + if ( this[i].nodeType === 1 ) { + jQuery.cleanData( this[i].getElementsByTagName("*") ); + this[i].innerHTML = value; + } + } + + // If using innerHTML throws an exception, use the fallback method + } catch(e) { + this.empty().append( value ); + } + + } else if ( jQuery.isFunction( value ) ) { + this.each(function(i){ + var self = jQuery( this ); + + self.html( value.call(this, i, self.html()) ); + }); + + } else { + this.empty().append( value ); + } + + return this; + }, + + replaceWith: function( value ) { + if ( this[0] && this[0].parentNode ) { + // Make sure that the elements are removed from the DOM before they are inserted + // this can help fix replacing a parent with child elements + if ( jQuery.isFunction( value ) ) { + return this.each(function(i) { + var self = jQuery(this), old = self.html(); + self.replaceWith( value.call( this, i, old ) ); + }); + } + + if ( typeof value !== "string" ) { + value = jQuery( value ).detach(); + } + + return this.each(function() { + var next = this.nextSibling, + parent = this.parentNode; + + jQuery( this ).remove(); + + if ( next ) { + jQuery(next).before( value ); + } else { + jQuery(parent).append( value ); + } + }); + } else { + return this.length ? + this.pushStack( jQuery(jQuery.isFunction(value) ? value() : value), "replaceWith", value ) : + this; + } + }, + + detach: function( selector ) { + return this.remove( selector, true ); + }, + + domManip: function( args, table, callback ) { + var results, first, fragment, parent, + value = args[0], + scripts = []; + + // We can't cloneNode fragments that contain checked, in WebKit + if ( !jQuery.support.checkClone && arguments.length === 3 && typeof value === "string" && rchecked.test( value ) ) { + return this.each(function() { + jQuery(this).domManip( args, table, callback, true ); + }); + } + + if ( jQuery.isFunction(value) ) { + return this.each(function(i) { + var self = jQuery(this); + args[0] = value.call(this, i, table ? self.html() : undefined); + self.domManip( args, table, callback ); + }); + } + + if ( this[0] ) { + parent = value && value.parentNode; + + // If we're in a fragment, just use that instead of building a new one + if ( jQuery.support.parentNode && parent && parent.nodeType === 11 && parent.childNodes.length === this.length ) { + results = { fragment: parent }; + + } else { + results = jQuery.buildFragment( args, this, scripts ); + } + + fragment = results.fragment; + + if ( fragment.childNodes.length === 1 ) { + first = fragment = fragment.firstChild; + } else { + first = fragment.firstChild; + } + + if ( first ) { + table = table && jQuery.nodeName( first, "tr" ); + + for ( var i = 0, l = this.length, lastIndex = l - 1; i < l; i++ ) { + callback.call( + table ? + root(this[i], first) : + this[i], + // Make sure that we do not leak memory by inadvertently discarding + // the original fragment (which might have attached data) instead of + // using it; in addition, use the original fragment object for the last + // item instead of first because it can end up being emptied incorrectly + // in certain situations (Bug #8070). + // Fragments from the fragment cache must always be cloned and never used + // in place. + results.cacheable || (l > 1 && i < lastIndex) ? + jQuery.clone( fragment, true, true ) : + fragment + ); + } + } + + if ( scripts.length ) { + jQuery.each( scripts, evalScript ); + } + } + + return this; + } +}); + +function root( elem, cur ) { + return jQuery.nodeName(elem, "table") ? + (elem.getElementsByTagName("tbody")[0] || + elem.appendChild(elem.ownerDocument.createElement("tbody"))) : + elem; +} + +function cloneCopyEvent( src, dest ) { + + if ( dest.nodeType !== 1 || !jQuery.hasData( src ) ) { + return; + } + + var internalKey = jQuery.expando, + oldData = jQuery.data( src ), + curData = jQuery.data( dest, oldData ); + + // Switch to use the internal data object, if it exists, for the next + // stage of data copying + if ( (oldData = oldData[ internalKey ]) ) { + var events = oldData.events; + curData = curData[ internalKey ] = jQuery.extend({}, oldData); + + if ( events ) { + delete curData.handle; + curData.events = {}; + + for ( var type in events ) { + for ( var i = 0, l = events[ type ].length; i < l; i++ ) { + jQuery.event.add( dest, type + ( events[ type ][ i ].namespace ? "." : "" ) + events[ type ][ i ].namespace, events[ type ][ i ], events[ type ][ i ].data ); + } + } + } + } +} + +function cloneFixAttributes( src, dest ) { + var nodeName; + + // We do not need to do anything for non-Elements + if ( dest.nodeType !== 1 ) { + return; + } + + // clearAttributes removes the attributes, which we don't want, + // but also removes the attachEvent events, which we *do* want + if ( dest.clearAttributes ) { + dest.clearAttributes(); + } + + // mergeAttributes, in contrast, only merges back on the + // original attributes, not the events + if ( dest.mergeAttributes ) { + dest.mergeAttributes( src ); + } + + nodeName = dest.nodeName.toLowerCase(); + + // IE6-8 fail to clone children inside object elements that use + // the proprietary classid attribute value (rather than the type + // attribute) to identify the type of content to display + if ( nodeName === "object" ) { + dest.outerHTML = src.outerHTML; + + } else if ( nodeName === "input" && (src.type === "checkbox" || src.type === "radio") ) { + // IE6-8 fails to persist the checked state of a cloned checkbox + // or radio button. Worse, IE6-7 fail to give the cloned element + // a checked appearance if the defaultChecked value isn't also set + if ( src.checked ) { + dest.defaultChecked = dest.checked = src.checked; + } + + // IE6-7 get confused and end up setting the value of a cloned + // checkbox/radio button to an empty string instead of "on" + if ( dest.value !== src.value ) { + dest.value = src.value; + } + + // IE6-8 fails to return the selected option to the default selected + // state when cloning options + } else if ( nodeName === "option" ) { + dest.selected = src.defaultSelected; + + // IE6-8 fails to set the defaultValue to the correct value when + // cloning other types of input fields + } else if ( nodeName === "input" || nodeName === "textarea" ) { + dest.defaultValue = src.defaultValue; + } + + // Event data gets referenced instead of copied if the expando + // gets copied too + dest.removeAttribute( jQuery.expando ); +} + +jQuery.buildFragment = function( args, nodes, scripts ) { + var fragment, cacheable, cacheresults, doc; + + // nodes may contain either an explicit document object, + // a jQuery collection or context object. + // If nodes[0] contains a valid object to assign to doc + if ( nodes && nodes[0] ) { + doc = nodes[0].ownerDocument || nodes[0]; + } + + // Ensure that an attr object doesn't incorrectly stand in as a document object + // Chrome and Firefox seem to allow this to occur and will throw exception + // Fixes #8950 + if ( !doc.createDocumentFragment ) { + doc = document; + } + + // Only cache "small" (1/2 KB) HTML strings that are associated with the main document + // Cloning options loses the selected state, so don't cache them + // IE 6 doesn't like it when you put <object> or <embed> elements in a fragment + // Also, WebKit does not clone 'checked' attributes on cloneNode, so don't cache + if ( args.length === 1 && typeof args[0] === "string" && args[0].length < 512 && doc === document && + args[0].charAt(0) === "<" && !rnocache.test( args[0] ) && (jQuery.support.checkClone || !rchecked.test( args[0] )) ) { + + cacheable = true; + + cacheresults = jQuery.fragments[ args[0] ]; + if ( cacheresults && cacheresults !== 1 ) { + fragment = cacheresults; + } + } + + if ( !fragment ) { + fragment = doc.createDocumentFragment(); + jQuery.clean( args, doc, fragment, scripts ); + } + + if ( cacheable ) { + jQuery.fragments[ args[0] ] = cacheresults ? fragment : 1; + } + + return { fragment: fragment, cacheable: cacheable }; +}; + +jQuery.fragments = {}; + +jQuery.each({ + appendTo: "append", + prependTo: "prepend", + insertBefore: "before", + insertAfter: "after", + replaceAll: "replaceWith" +}, function( name, original ) { + jQuery.fn[ name ] = function( selector ) { + var ret = [], + insert = jQuery( selector ), + parent = this.length === 1 && this[0].parentNode; + + if ( parent && parent.nodeType === 11 && parent.childNodes.length === 1 && insert.length === 1 ) { + insert[ original ]( this[0] ); + return this; + + } else { + for ( var i = 0, l = insert.length; i < l; i++ ) { + var elems = (i > 0 ? this.clone(true) : this).get(); + jQuery( insert[i] )[ original ]( elems ); + ret = ret.concat( elems ); + } + + return this.pushStack( ret, name, insert.selector ); + } + }; +}); + +function getAll( elem ) { + if ( "getElementsByTagName" in elem ) { + return elem.getElementsByTagName( "*" ); + + } else if ( "querySelectorAll" in elem ) { + return elem.querySelectorAll( "*" ); + + } else { + return []; + } +} + +// Used in clean, fixes the defaultChecked property +function fixDefaultChecked( elem ) { + if ( elem.type === "checkbox" || elem.type === "radio" ) { + elem.defaultChecked = elem.checked; + } +} +// Finds all inputs and passes them to fixDefaultChecked +function findInputs( elem ) { + if ( jQuery.nodeName( elem, "input" ) ) { + fixDefaultChecked( elem ); + } else if ( "getElementsByTagName" in elem ) { + jQuery.grep( elem.getElementsByTagName("input"), fixDefaultChecked ); + } +} + +jQuery.extend({ + clone: function( elem, dataAndEvents, deepDataAndEvents ) { + var clone = elem.cloneNode(true), + srcElements, + destElements, + i; + + if ( (!jQuery.support.noCloneEvent || !jQuery.support.noCloneChecked) && + (elem.nodeType === 1 || elem.nodeType === 11) && !jQuery.isXMLDoc(elem) ) { + // IE copies events bound via attachEvent when using cloneNode. + // Calling detachEvent on the clone will also remove the events + // from the original. In order to get around this, we use some + // proprietary methods to clear the events. Thanks to MooTools + // guys for this hotness. + + cloneFixAttributes( elem, clone ); + + // Using Sizzle here is crazy slow, so we use getElementsByTagName + // instead + srcElements = getAll( elem ); + destElements = getAll( clone ); + + // Weird iteration because IE will replace the length property + // with an element if you are cloning the body and one of the + // elements on the page has a name or id of "length" + for ( i = 0; srcElements[i]; ++i ) { + cloneFixAttributes( srcElements[i], destElements[i] ); + } + } + + // Copy the events from the original to the clone + if ( dataAndEvents ) { + cloneCopyEvent( elem, clone ); + + if ( deepDataAndEvents ) { + srcElements = getAll( elem ); + destElements = getAll( clone ); + + for ( i = 0; srcElements[i]; ++i ) { + cloneCopyEvent( srcElements[i], destElements[i] ); + } + } + } + + srcElements = destElements = null; + + // Return the cloned set + return clone; + }, + + clean: function( elems, context, fragment, scripts ) { + var checkScriptType; + + context = context || document; + + // !context.createElement fails in IE with an error but returns typeof 'object' + if ( typeof context.createElement === "undefined" ) { + context = context.ownerDocument || context[0] && context[0].ownerDocument || document; + } + + var ret = [], j; + + for ( var i = 0, elem; (elem = elems[i]) != null; i++ ) { + if ( typeof elem === "number" ) { + elem += ""; + } + + if ( !elem ) { + continue; + } + + // Convert html string into DOM nodes + if ( typeof elem === "string" ) { + if ( !rhtml.test( elem ) ) { + elem = context.createTextNode( elem ); + } else { + // Fix "XHTML"-style tags in all browsers + elem = elem.replace(rxhtmlTag, "<$1></$2>"); + + // Trim whitespace, otherwise indexOf won't work as expected + var tag = (rtagName.exec( elem ) || ["", ""])[1].toLowerCase(), + wrap = wrapMap[ tag ] || wrapMap._default, + depth = wrap[0], + div = context.createElement("div"); + + // Go to html and back, then peel off extra wrappers + div.innerHTML = wrap[1] + elem + wrap[2]; + + // Move to the right depth + while ( depth-- ) { + div = div.lastChild; + } + + // Remove IE's autoinserted <tbody> from table fragments + if ( !jQuery.support.tbody ) { + + // String was a <table>, *may* have spurious <tbody> + var hasBody = rtbody.test(elem), + tbody = tag === "table" && !hasBody ? + div.firstChild && div.firstChild.childNodes : + + // String was a bare <thead> or <tfoot> + wrap[1] === "<table>" && !hasBody ? + div.childNodes : + []; + + for ( j = tbody.length - 1; j >= 0 ; --j ) { + if ( jQuery.nodeName( tbody[ j ], "tbody" ) && !tbody[ j ].childNodes.length ) { + tbody[ j ].parentNode.removeChild( tbody[ j ] ); + } + } + } + + // IE completely kills leading whitespace when innerHTML is used + if ( !jQuery.support.leadingWhitespace && rleadingWhitespace.test( elem ) ) { + div.insertBefore( context.createTextNode( rleadingWhitespace.exec(elem)[0] ), div.firstChild ); + } + + elem = div.childNodes; + } + } + + // Resets defaultChecked for any radios and checkboxes + // about to be appended to the DOM in IE 6/7 (#8060) + var len; + if ( !jQuery.support.appendChecked ) { + if ( elem[0] && typeof (len = elem.length) === "number" ) { + for ( j = 0; j < len; j++ ) { + findInputs( elem[j] ); + } + } else { + findInputs( elem ); + } + } + + if ( elem.nodeType ) { + ret.push( elem ); + } else { + ret = jQuery.merge( ret, elem ); + } + } + + if ( fragment ) { + checkScriptType = function( elem ) { + return !elem.type || rscriptType.test( elem.type ); + }; + for ( i = 0; ret[i]; i++ ) { + if ( scripts && jQuery.nodeName( ret[i], "script" ) && (!ret[i].type || ret[i].type.toLowerCase() === "text/javascript") ) { + scripts.push( ret[i].parentNode ? ret[i].parentNode.removeChild( ret[i] ) : ret[i] ); + + } else { + if ( ret[i].nodeType === 1 ) { + var jsTags = jQuery.grep( ret[i].getElementsByTagName( "script" ), checkScriptType ); + + ret.splice.apply( ret, [i + 1, 0].concat( jsTags ) ); + } + fragment.appendChild( ret[i] ); + } + } + } + + return ret; + }, + + cleanData: function( elems ) { + var data, id, cache = jQuery.cache, internalKey = jQuery.expando, special = jQuery.event.special, + deleteExpando = jQuery.support.deleteExpando; + + for ( var i = 0, elem; (elem = elems[i]) != null; i++ ) { + if ( elem.nodeName && jQuery.noData[elem.nodeName.toLowerCase()] ) { + continue; + } + + id = elem[ jQuery.expando ]; + + if ( id ) { + data = cache[ id ] && cache[ id ][ internalKey ]; + + if ( data && data.events ) { + for ( var type in data.events ) { + if ( special[ type ] ) { + jQuery.event.remove( elem, type ); + + // This is a shortcut to avoid jQuery.event.remove's overhead + } else { + jQuery.removeEvent( elem, type, data.handle ); + } + } + + // Null the DOM reference to avoid IE6/7/8 leak (#7054) + if ( data.handle ) { + data.handle.elem = null; + } + } + + if ( deleteExpando ) { + delete elem[ jQuery.expando ]; + + } else if ( elem.removeAttribute ) { + elem.removeAttribute( jQuery.expando ); + } + + delete cache[ id ]; + } + } + } +}); + +function evalScript( i, elem ) { + if ( elem.src ) { + jQuery.ajax({ + url: elem.src, + async: false, + dataType: "script" + }); + } else { + jQuery.globalEval( ( elem.text || elem.textContent || elem.innerHTML || "" ).replace( rcleanScript, "/*$0*/" ) ); + } + + if ( elem.parentNode ) { + elem.parentNode.removeChild( elem ); + } +} + + + +var ralpha = /alpha\([^)]*\)/i, + ropacity = /opacity=([^)]*)/, + // fixed for IE9, see #8346 + rupper = /([A-Z]|^ms)/g, + rnumpx = /^-?\d+(?:px)?$/i, + rnum = /^-?\d/, + rrelNum = /^[+\-]=/, + rrelNumFilter = /[^+\-\.\de]+/g, + + cssShow = { position: "absolute", visibility: "hidden", display: "block" }, + cssWidth = [ "Left", "Right" ], + cssHeight = [ "Top", "Bottom" ], + curCSS, + + getComputedStyle, + currentStyle; + +jQuery.fn.css = function( name, value ) { + // Setting 'undefined' is a no-op + if ( arguments.length === 2 && value === undefined ) { + return this; + } + + return jQuery.access( this, name, value, true, function( elem, name, value ) { + return value !== undefined ? + jQuery.style( elem, name, value ) : + jQuery.css( elem, name ); + }); +}; + +jQuery.extend({ + // Add in style property hooks for overriding the default + // behavior of getting and setting a style property + cssHooks: { + opacity: { + get: function( elem, computed ) { + if ( computed ) { + // We should always get a number back from opacity + var ret = curCSS( elem, "opacity", "opacity" ); + return ret === "" ? "1" : ret; + + } else { + return elem.style.opacity; + } + } + } + }, + + // Exclude the following css properties to add px + cssNumber: { + "fillOpacity": true, + "fontWeight": true, + "lineHeight": true, + "opacity": true, + "orphans": true, + "widows": true, + "zIndex": true, + "zoom": true + }, + + // Add in properties whose names you wish to fix before + // setting or getting the value + cssProps: { + // normalize float css property + "float": jQuery.support.cssFloat ? "cssFloat" : "styleFloat" + }, + + // Get and set the style property on a DOM Node + style: function( elem, name, value, extra ) { + // Don't set styles on text and comment nodes + if ( !elem || elem.nodeType === 3 || elem.nodeType === 8 || !elem.style ) { + return; + } + + // Make sure that we're working with the right name + var ret, type, origName = jQuery.camelCase( name ), + style = elem.style, hooks = jQuery.cssHooks[ origName ]; + + name = jQuery.cssProps[ origName ] || origName; + + // Check if we're setting a value + if ( value !== undefined ) { + type = typeof value; + + // Make sure that NaN and null values aren't set. See: #7116 + if ( type === "number" && isNaN( value ) || value == null ) { + return; + } + + // convert relative number strings (+= or -=) to relative numbers. #7345 + if ( type === "string" && rrelNum.test( value ) ) { + value = +value.replace( rrelNumFilter, "" ) + parseFloat( jQuery.css( elem, name ) ); + // Fixes bug #9237 + type = "number"; + } + + // If a number was passed in, add 'px' to the (except for certain CSS properties) + if ( type === "number" && !jQuery.cssNumber[ origName ] ) { + value += "px"; + } + + // If a hook was provided, use that value, otherwise just set the specified value + if ( !hooks || !("set" in hooks) || (value = hooks.set( elem, value )) !== undefined ) { + // Wrapped to prevent IE from throwing errors when 'invalid' values are provided + // Fixes bug #5509 + try { + style[ name ] = value; + } catch(e) {} + } + + } else { + // If a hook was provided get the non-computed value from there + if ( hooks && "get" in hooks && (ret = hooks.get( elem, false, extra )) !== undefined ) { + return ret; + } + + // Otherwise just get the value from the style object + return style[ name ]; + } + }, + + css: function( elem, name, extra ) { + var ret, hooks; + + // Make sure that we're working with the right name + name = jQuery.camelCase( name ); + hooks = jQuery.cssHooks[ name ]; + name = jQuery.cssProps[ name ] || name; + + // cssFloat needs a special treatment + if ( name === "cssFloat" ) { + name = "float"; + } + + // If a hook was provided get the computed value from there + if ( hooks && "get" in hooks && (ret = hooks.get( elem, true, extra )) !== undefined ) { + return ret; + + // Otherwise, if a way to get the computed value exists, use that + } else if ( curCSS ) { + return curCSS( elem, name ); + } + }, + + // A method for quickly swapping in/out CSS properties to get correct calculations + swap: function( elem, options, callback ) { + var old = {}; + + // Remember the old values, and insert the new ones + for ( var name in options ) { + old[ name ] = elem.style[ name ]; + elem.style[ name ] = options[ name ]; + } + + callback.call( elem ); + + // Revert the old values + for ( name in options ) { + elem.style[ name ] = old[ name ]; + } + } +}); + +// DEPRECATED, Use jQuery.css() instead +jQuery.curCSS = jQuery.css; + +jQuery.each(["height", "width"], function( i, name ) { + jQuery.cssHooks[ name ] = { + get: function( elem, computed, extra ) { + var val; + + if ( computed ) { + if ( elem.offsetWidth !== 0 ) { + return getWH( elem, name, extra ); + } else { + jQuery.swap( elem, cssShow, function() { + val = getWH( elem, name, extra ); + }); + } + + return val; + } + }, + + set: function( elem, value ) { + if ( rnumpx.test( value ) ) { + // ignore negative width and height values #1599 + value = parseFloat( value ); + + if ( value >= 0 ) { + return value + "px"; + } + + } else { + return value; + } + } + }; +}); + +if ( !jQuery.support.opacity ) { + jQuery.cssHooks.opacity = { + get: function( elem, computed ) { + // IE uses filters for opacity + return ropacity.test( (computed && elem.currentStyle ? elem.currentStyle.filter : elem.style.filter) || "" ) ? + ( parseFloat( RegExp.$1 ) / 100 ) + "" : + computed ? "1" : ""; + }, + + set: function( elem, value ) { + var style = elem.style, + currentStyle = elem.currentStyle; + + // IE has trouble with opacity if it does not have layout + // Force it by setting the zoom level + style.zoom = 1; + + // Set the alpha filter to set the opacity + var opacity = jQuery.isNaN( value ) ? + "" : + "alpha(opacity=" + value * 100 + ")", + filter = currentStyle && currentStyle.filter || style.filter || ""; + + style.filter = ralpha.test( filter ) ? + filter.replace( ralpha, opacity ) : + filter + " " + opacity; + } + }; +} + +jQuery(function() { + // This hook cannot be added until DOM ready because the support test + // for it is not run until after DOM ready + if ( !jQuery.support.reliableMarginRight ) { + jQuery.cssHooks.marginRight = { + get: function( elem, computed ) { + // WebKit Bug 13343 - getComputedStyle returns wrong value for margin-right + // Work around by temporarily setting element display to inline-block + var ret; + jQuery.swap( elem, { "display": "inline-block" }, function() { + if ( computed ) { + ret = curCSS( elem, "margin-right", "marginRight" ); + } else { + ret = elem.style.marginRight; + } + }); + return ret; + } + }; + } +}); + +if ( document.defaultView && document.defaultView.getComputedStyle ) { + getComputedStyle = function( elem, name ) { + var ret, defaultView, computedStyle; + + name = name.replace( rupper, "-$1" ).toLowerCase(); + + if ( !(defaultView = elem.ownerDocument.defaultView) ) { + return undefined; + } + + if ( (computedStyle = defaultView.getComputedStyle( elem, null )) ) { + ret = computedStyle.getPropertyValue( name ); + if ( ret === "" && !jQuery.contains( elem.ownerDocument.documentElement, elem ) ) { + ret = jQuery.style( elem, name ); + } + } + + return ret; + }; +} + +if ( document.documentElement.currentStyle ) { + currentStyle = function( elem, name ) { + var left, + ret = elem.currentStyle && elem.currentStyle[ name ], + rsLeft = elem.runtimeStyle && elem.runtimeStyle[ name ], + style = elem.style; + + // From the awesome hack by Dean Edwards + // http://erik.eae.net/archives/2007/07/27/18.54.15/#comment-102291 + + // If we're not dealing with a regular pixel number + // but a number that has a weird ending, we need to convert it to pixels + if ( !rnumpx.test( ret ) && rnum.test( ret ) ) { + // Remember the original values + left = style.left; + + // Put in the new values to get a computed value out + if ( rsLeft ) { + elem.runtimeStyle.left = elem.currentStyle.left; + } + style.left = name === "fontSize" ? "1em" : (ret || 0); + ret = style.pixelLeft + "px"; + + // Revert the changed values + style.left = left; + if ( rsLeft ) { + elem.runtimeStyle.left = rsLeft; + } + } + + return ret === "" ? "auto" : ret; + }; +} + +curCSS = getComputedStyle || currentStyle; + +function getWH( elem, name, extra ) { + + // Start with offset property + var val = name === "width" ? elem.offsetWidth : elem.offsetHeight, + which = name === "width" ? cssWidth : cssHeight; + + if ( val > 0 ) { + if ( extra !== "border" ) { + jQuery.each( which, function() { + if ( !extra ) { + val -= parseFloat( jQuery.css( elem, "padding" + this ) ) || 0; + } + if ( extra === "margin" ) { + val += parseFloat( jQuery.css( elem, extra + this ) ) || 0; + } else { + val -= parseFloat( jQuery.css( elem, "border" + this + "Width" ) ) || 0; + } + }); + } + + return val + "px"; + } + + // Fall back to computed then uncomputed css if necessary + val = curCSS( elem, name, name ); + if ( val < 0 || val == null ) { + val = elem.style[ name ] || 0; + } + // Normalize "", auto, and prepare for extra + val = parseFloat( val ) || 0; + + // Add padding, border, margin + if ( extra ) { + jQuery.each( which, function() { + val += parseFloat( jQuery.css( elem, "padding" + this ) ) || 0; + if ( extra !== "padding" ) { + val += parseFloat( jQuery.css( elem, "border" + this + "Width" ) ) || 0; + } + if ( extra === "margin" ) { + val += parseFloat( jQuery.css( elem, extra + this ) ) || 0; + } + }); + } + + return val + "px"; +} + +if ( jQuery.expr && jQuery.expr.filters ) { + jQuery.expr.filters.hidden = function( elem ) { + var width = elem.offsetWidth, + height = elem.offsetHeight; + + return (width === 0 && height === 0) || (!jQuery.support.reliableHiddenOffsets && (elem.style.display || jQuery.css( elem, "display" )) === "none"); + }; + + jQuery.expr.filters.visible = function( elem ) { + return !jQuery.expr.filters.hidden( elem ); + }; +} + + + + +var r20 = /%20/g, + rbracket = /\[\]$/, + rCRLF = /\r?\n/g, + rhash = /#.*$/, + rheaders = /^(.*?):[ \t]*([^\r\n]*)\r?$/mg, // IE leaves an \r character at EOL + rinput = /^(?:color|date|datetime|email|hidden|month|number|password|range|search|tel|text|time|url|week)$/i, + // #7653, #8125, #8152: local protocol detection + rlocalProtocol = /^(?:about|app|app\-storage|.+\-extension|file|widget):$/, + rnoContent = /^(?:GET|HEAD)$/, + rprotocol = /^\/\//, + rquery = /\?/, + rscript = /<script\b[^<]*(?:(?!<\/script>)<[^<]*)*<\/script>/gi, + rselectTextarea = /^(?:select|textarea)/i, + rspacesAjax = /\s+/, + rts = /([?&])_=[^&]*/, + rurl = /^([\w\+\.\-]+:)(?:\/\/([^\/?#:]*)(?::(\d+))?)?/, + + // Keep a copy of the old load method + _load = jQuery.fn.load, + + /* Prefilters + * 1) They are useful to introduce custom dataTypes (see ajax/jsonp.js for an example) + * 2) These are called: + * - BEFORE asking for a transport + * - AFTER param serialization (s.data is a string if s.processData is true) + * 3) key is the dataType + * 4) the catchall symbol "*" can be used + * 5) execution will start with transport dataType and THEN continue down to "*" if needed + */ + prefilters = {}, + + /* Transports bindings + * 1) key is the dataType + * 2) the catchall symbol "*" can be used + * 3) selection will start with transport dataType and THEN go to "*" if needed + */ + transports = {}, + + // Document location + ajaxLocation, + + // Document location segments + ajaxLocParts; + +// #8138, IE may throw an exception when accessing +// a field from window.location if document.domain has been set +try { + ajaxLocation = location.href; +} catch( e ) { + // Use the href attribute of an A element + // since IE will modify it given document.location + ajaxLocation = document.createElement( "a" ); + ajaxLocation.href = ""; + ajaxLocation = ajaxLocation.href; +} + +// Segment location into parts +ajaxLocParts = rurl.exec( ajaxLocation.toLowerCase() ) || []; + +// Base "constructor" for jQuery.ajaxPrefilter and jQuery.ajaxTransport +function addToPrefiltersOrTransports( structure ) { + + // dataTypeExpression is optional and defaults to "*" + return function( dataTypeExpression, func ) { + + if ( typeof dataTypeExpression !== "string" ) { + func = dataTypeExpression; + dataTypeExpression = "*"; + } + + if ( jQuery.isFunction( func ) ) { + var dataTypes = dataTypeExpression.toLowerCase().split( rspacesAjax ), + i = 0, + length = dataTypes.length, + dataType, + list, + placeBefore; + + // For each dataType in the dataTypeExpression + for(; i < length; i++ ) { + dataType = dataTypes[ i ]; + // We control if we're asked to add before + // any existing element + placeBefore = /^\+/.test( dataType ); + if ( placeBefore ) { + dataType = dataType.substr( 1 ) || "*"; + } + list = structure[ dataType ] = structure[ dataType ] || []; + // then we add to the structure accordingly + list[ placeBefore ? "unshift" : "push" ]( func ); + } + } + }; +} + +// Base inspection function for prefilters and transports +function inspectPrefiltersOrTransports( structure, options, originalOptions, jqXHR, + dataType /* internal */, inspected /* internal */ ) { + + dataType = dataType || options.dataTypes[ 0 ]; + inspected = inspected || {}; + + inspected[ dataType ] = true; + + var list = structure[ dataType ], + i = 0, + length = list ? list.length : 0, + executeOnly = ( structure === prefilters ), + selection; + + for(; i < length && ( executeOnly || !selection ); i++ ) { + selection = list[ i ]( options, originalOptions, jqXHR ); + // If we got redirected to another dataType + // we try there if executing only and not done already + if ( typeof selection === "string" ) { + if ( !executeOnly || inspected[ selection ] ) { + selection = undefined; + } else { + options.dataTypes.unshift( selection ); + selection = inspectPrefiltersOrTransports( + structure, options, originalOptions, jqXHR, selection, inspected ); + } + } + } + // If we're only executing or nothing was selected + // we try the catchall dataType if not done already + if ( ( executeOnly || !selection ) && !inspected[ "*" ] ) { + selection = inspectPrefiltersOrTransports( + structure, options, originalOptions, jqXHR, "*", inspected ); + } + // unnecessary when only executing (prefilters) + // but it'll be ignored by the caller in that case + return selection; +} + +jQuery.fn.extend({ + load: function( url, params, callback ) { + if ( typeof url !== "string" && _load ) { + return _load.apply( this, arguments ); + + // Don't do a request if no elements are being requested + } else if ( !this.length ) { + return this; + } + + var off = url.indexOf( " " ); + if ( off >= 0 ) { + var selector = url.slice( off, url.length ); + url = url.slice( 0, off ); + } + + // Default to a GET request + var type = "GET"; + + // If the second parameter was provided + if ( params ) { + // If it's a function + if ( jQuery.isFunction( params ) ) { + // We assume that it's the callback + callback = params; + params = undefined; + + // Otherwise, build a param string + } else if ( typeof params === "object" ) { + params = jQuery.param( params, jQuery.ajaxSettings.traditional ); + type = "POST"; + } + } + + var self = this; + + // Request the remote document + jQuery.ajax({ + url: url, + type: type, + dataType: "html", + data: params, + // Complete callback (responseText is used internally) + complete: function( jqXHR, status, responseText ) { + // Store the response as specified by the jqXHR object + responseText = jqXHR.responseText; + // If successful, inject the HTML into all the matched elements + if ( jqXHR.isResolved() ) { + // #4825: Get the actual response in case + // a dataFilter is present in ajaxSettings + jqXHR.done(function( r ) { + responseText = r; + }); + // See if a selector was specified + self.html( selector ? + // Create a dummy div to hold the results + jQuery("<div>") + // inject the contents of the document in, removing the scripts + // to avoid any 'Permission Denied' errors in IE + .append(responseText.replace(rscript, "")) + + // Locate the specified elements + .find(selector) : + + // If not, just inject the full result + responseText ); + } + + if ( callback ) { + self.each( callback, [ responseText, status, jqXHR ] ); + } + } + }); + + return this; + }, + + serialize: function() { + return jQuery.param( this.serializeArray() ); + }, + + serializeArray: function() { + return this.map(function(){ + return this.elements ? jQuery.makeArray( this.elements ) : this; + }) + .filter(function(){ + return this.name && !this.disabled && + ( this.checked || rselectTextarea.test( this.nodeName ) || + rinput.test( this.type ) ); + }) + .map(function( i, elem ){ + var val = jQuery( this ).val(); + + return val == null ? + null : + jQuery.isArray( val ) ? + jQuery.map( val, function( val, i ){ + return { name: elem.name, value: val.replace( rCRLF, "\r\n" ) }; + }) : + { name: elem.name, value: val.replace( rCRLF, "\r\n" ) }; + }).get(); + } +}); + +// Attach a bunch of functions for handling common AJAX events +jQuery.each( "ajaxStart ajaxStop ajaxComplete ajaxError ajaxSuccess ajaxSend".split( " " ), function( i, o ){ + jQuery.fn[ o ] = function( f ){ + return this.bind( o, f ); + }; +}); + +jQuery.each( [ "get", "post" ], function( i, method ) { + jQuery[ method ] = function( url, data, callback, type ) { + // shift arguments if data argument was omitted + if ( jQuery.isFunction( data ) ) { + type = type || callback; + callback = data; + data = undefined; + } + + return jQuery.ajax({ + type: method, + url: url, + data: data, + success: callback, + dataType: type + }); + }; +}); + +jQuery.extend({ + + getScript: function( url, callback ) { + return jQuery.get( url, undefined, callback, "script" ); + }, + + getJSON: function( url, data, callback ) { + return jQuery.get( url, data, callback, "json" ); + }, + + // Creates a full fledged settings object into target + // with both ajaxSettings and settings fields. + // If target is omitted, writes into ajaxSettings. + ajaxSetup: function ( target, settings ) { + if ( !settings ) { + // Only one parameter, we extend ajaxSettings + settings = target; + target = jQuery.extend( true, jQuery.ajaxSettings, settings ); + } else { + // target was provided, we extend into it + jQuery.extend( true, target, jQuery.ajaxSettings, settings ); + } + // Flatten fields we don't want deep extended + for( var field in { context: 1, url: 1 } ) { + if ( field in settings ) { + target[ field ] = settings[ field ]; + } else if( field in jQuery.ajaxSettings ) { + target[ field ] = jQuery.ajaxSettings[ field ]; + } + } + return target; + }, + + ajaxSettings: { + url: ajaxLocation, + isLocal: rlocalProtocol.test( ajaxLocParts[ 1 ] ), + global: true, + type: "GET", + contentType: "application/x-www-form-urlencoded", + processData: true, + async: true, + /* + timeout: 0, + data: null, + dataType: null, + username: null, + password: null, + cache: null, + traditional: false, + headers: {}, + */ + + accepts: { + xml: "application/xml, text/xml", + html: "text/html", + text: "text/plain", + json: "application/json, text/javascript", + "*": "*/*" + }, + + contents: { + xml: /xml/, + html: /html/, + json: /json/ + }, + + responseFields: { + xml: "responseXML", + text: "responseText" + }, + + // List of data converters + // 1) key format is "source_type destination_type" (a single space in-between) + // 2) the catchall symbol "*" can be used for source_type + converters: { + + // Convert anything to text + "* text": window.String, + + // Text to html (true = no transformation) + "text html": true, + + // Evaluate text as a json expression + "text json": jQuery.parseJSON, + + // Parse text as xml + "text xml": jQuery.parseXML + } + }, + + ajaxPrefilter: addToPrefiltersOrTransports( prefilters ), + ajaxTransport: addToPrefiltersOrTransports( transports ), + + // Main method + ajax: function( url, options ) { + + // If url is an object, simulate pre-1.5 signature + if ( typeof url === "object" ) { + options = url; + url = undefined; + } + + // Force options to be an object + options = options || {}; + + var // Create the final options object + s = jQuery.ajaxSetup( {}, options ), + // Callbacks context + callbackContext = s.context || s, + // Context for global events + // It's the callbackContext if one was provided in the options + // and if it's a DOM node or a jQuery collection + globalEventContext = callbackContext !== s && + ( callbackContext.nodeType || callbackContext instanceof jQuery ) ? + jQuery( callbackContext ) : jQuery.event, + // Deferreds + deferred = jQuery.Deferred(), + completeDeferred = jQuery._Deferred(), + // Status-dependent callbacks + statusCode = s.statusCode || {}, + // ifModified key + ifModifiedKey, + // Headers (they are sent all at once) + requestHeaders = {}, + requestHeadersNames = {}, + // Response headers + responseHeadersString, + responseHeaders, + // transport + transport, + // timeout handle + timeoutTimer, + // Cross-domain detection vars + parts, + // The jqXHR state + state = 0, + // To know if global events are to be dispatched + fireGlobals, + // Loop variable + i, + // Fake xhr + jqXHR = { + + readyState: 0, + + // Caches the header + setRequestHeader: function( name, value ) { + if ( !state ) { + var lname = name.toLowerCase(); + name = requestHeadersNames[ lname ] = requestHeadersNames[ lname ] || name; + requestHeaders[ name ] = value; + } + return this; + }, + + // Raw string + getAllResponseHeaders: function() { + return state === 2 ? responseHeadersString : null; + }, + + // Builds headers hashtable if needed + getResponseHeader: function( key ) { + var match; + if ( state === 2 ) { + if ( !responseHeaders ) { + responseHeaders = {}; + while( ( match = rheaders.exec( responseHeadersString ) ) ) { + responseHeaders[ match[1].toLowerCase() ] = match[ 2 ]; + } + } + match = responseHeaders[ key.toLowerCase() ]; + } + return match === undefined ? null : match; + }, + + // Overrides response content-type header + overrideMimeType: function( type ) { + if ( !state ) { + s.mimeType = type; + } + return this; + }, + + // Cancel the request + abort: function( statusText ) { + statusText = statusText || "abort"; + if ( transport ) { + transport.abort( statusText ); + } + done( 0, statusText ); + return this; + } + }; + + // Callback for when everything is done + // It is defined here because jslint complains if it is declared + // at the end of the function (which would be more logical and readable) + function done( status, statusText, responses, headers ) { + + // Called once + if ( state === 2 ) { + return; + } + + // State is "done" now + state = 2; + + // Clear timeout if it exists + if ( timeoutTimer ) { + clearTimeout( timeoutTimer ); + } + + // Dereference transport for early garbage collection + // (no matter how long the jqXHR object will be used) + transport = undefined; + + // Cache response headers + responseHeadersString = headers || ""; + + // Set readyState + jqXHR.readyState = status ? 4 : 0; + + var isSuccess, + success, + error, + response = responses ? ajaxHandleResponses( s, jqXHR, responses ) : undefined, + lastModified, + etag; + + // If successful, handle type chaining + if ( status >= 200 && status < 300 || status === 304 ) { + + // Set the If-Modified-Since and/or If-None-Match header, if in ifModified mode. + if ( s.ifModified ) { + + if ( ( lastModified = jqXHR.getResponseHeader( "Last-Modified" ) ) ) { + jQuery.lastModified[ ifModifiedKey ] = lastModified; + } + if ( ( etag = jqXHR.getResponseHeader( "Etag" ) ) ) { + jQuery.etag[ ifModifiedKey ] = etag; + } + } + + // If not modified + if ( status === 304 ) { + + statusText = "notmodified"; + isSuccess = true; + + // If we have data + } else { + + try { + success = ajaxConvert( s, response ); + statusText = "success"; + isSuccess = true; + } catch(e) { + // We have a parsererror + statusText = "parsererror"; + error = e; + } + } + } else { + // We extract error from statusText + // then normalize statusText and status for non-aborts + error = statusText; + if( !statusText || status ) { + statusText = "error"; + if ( status < 0 ) { + status = 0; + } + } + } + + // Set data for the fake xhr object + jqXHR.status = status; + jqXHR.statusText = statusText; + + // Success/Error + if ( isSuccess ) { + deferred.resolveWith( callbackContext, [ success, statusText, jqXHR ] ); + } else { + deferred.rejectWith( callbackContext, [ jqXHR, statusText, error ] ); + } + + // Status-dependent callbacks + jqXHR.statusCode( statusCode ); + statusCode = undefined; + + if ( fireGlobals ) { + globalEventContext.trigger( "ajax" + ( isSuccess ? "Success" : "Error" ), + [ jqXHR, s, isSuccess ? success : error ] ); + } + + // Complete + completeDeferred.resolveWith( callbackContext, [ jqXHR, statusText ] ); + + if ( fireGlobals ) { + globalEventContext.trigger( "ajaxComplete", [ jqXHR, s] ); + // Handle the global AJAX counter + if ( !( --jQuery.active ) ) { + jQuery.event.trigger( "ajaxStop" ); + } + } + } + + // Attach deferreds + deferred.promise( jqXHR ); + jqXHR.success = jqXHR.done; + jqXHR.error = jqXHR.fail; + jqXHR.complete = completeDeferred.done; + + // Status-dependent callbacks + jqXHR.statusCode = function( map ) { + if ( map ) { + var tmp; + if ( state < 2 ) { + for( tmp in map ) { + statusCode[ tmp ] = [ statusCode[tmp], map[tmp] ]; + } + } else { + tmp = map[ jqXHR.status ]; + jqXHR.then( tmp, tmp ); + } + } + return this; + }; + + // Remove hash character (#7531: and string promotion) + // Add protocol if not provided (#5866: IE7 issue with protocol-less urls) + // We also use the url parameter if available + s.url = ( ( url || s.url ) + "" ).replace( rhash, "" ).replace( rprotocol, ajaxLocParts[ 1 ] + "//" ); + + // Extract dataTypes list + s.dataTypes = jQuery.trim( s.dataType || "*" ).toLowerCase().split( rspacesAjax ); + + // Determine if a cross-domain request is in order + if ( s.crossDomain == null ) { + parts = rurl.exec( s.url.toLowerCase() ); + s.crossDomain = !!( parts && + ( parts[ 1 ] != ajaxLocParts[ 1 ] || parts[ 2 ] != ajaxLocParts[ 2 ] || + ( parts[ 3 ] || ( parts[ 1 ] === "http:" ? 80 : 443 ) ) != + ( ajaxLocParts[ 3 ] || ( ajaxLocParts[ 1 ] === "http:" ? 80 : 443 ) ) ) + ); + } + + // Convert data if not already a string + if ( s.data && s.processData && typeof s.data !== "string" ) { + s.data = jQuery.param( s.data, s.traditional ); + } + + // Apply prefilters + inspectPrefiltersOrTransports( prefilters, s, options, jqXHR ); + + // If request was aborted inside a prefiler, stop there + if ( state === 2 ) { + return false; + } + + // We can fire global events as of now if asked to + fireGlobals = s.global; + + // Uppercase the type + s.type = s.type.toUpperCase(); + + // Determine if request has content + s.hasContent = !rnoContent.test( s.type ); + + // Watch for a new set of requests + if ( fireGlobals && jQuery.active++ === 0 ) { + jQuery.event.trigger( "ajaxStart" ); + } + + // More options handling for requests with no content + if ( !s.hasContent ) { + + // If data is available, append data to url + if ( s.data ) { + s.url += ( rquery.test( s.url ) ? "&" : "?" ) + s.data; + } + + // Get ifModifiedKey before adding the anti-cache parameter + ifModifiedKey = s.url; + + // Add anti-cache in url if needed + if ( s.cache === false ) { + + var ts = jQuery.now(), + // try replacing _= if it is there + ret = s.url.replace( rts, "$1_=" + ts ); + + // if nothing was replaced, add timestamp to the end + s.url = ret + ( (ret === s.url ) ? ( rquery.test( s.url ) ? "&" : "?" ) + "_=" + ts : "" ); + } + } + + // Set the correct header, if data is being sent + if ( s.data && s.hasContent && s.contentType !== false || options.contentType ) { + jqXHR.setRequestHeader( "Content-Type", s.contentType ); + } + + // Set the If-Modified-Since and/or If-None-Match header, if in ifModified mode. + if ( s.ifModified ) { + ifModifiedKey = ifModifiedKey || s.url; + if ( jQuery.lastModified[ ifModifiedKey ] ) { + jqXHR.setRequestHeader( "If-Modified-Since", jQuery.lastModified[ ifModifiedKey ] ); + } + if ( jQuery.etag[ ifModifiedKey ] ) { + jqXHR.setRequestHeader( "If-None-Match", jQuery.etag[ ifModifiedKey ] ); + } + } + + // Set the Accepts header for the server, depending on the dataType + jqXHR.setRequestHeader( + "Accept", + s.dataTypes[ 0 ] && s.accepts[ s.dataTypes[0] ] ? + s.accepts[ s.dataTypes[0] ] + ( s.dataTypes[ 0 ] !== "*" ? ", */*; q=0.01" : "" ) : + s.accepts[ "*" ] + ); + + // Check for headers option + for ( i in s.headers ) { + jqXHR.setRequestHeader( i, s.headers[ i ] ); + } + + // Allow custom headers/mimetypes and early abort + if ( s.beforeSend && ( s.beforeSend.call( callbackContext, jqXHR, s ) === false || state === 2 ) ) { + // Abort if not done already + jqXHR.abort(); + return false; + + } + + // Install callbacks on deferreds + for ( i in { success: 1, error: 1, complete: 1 } ) { + jqXHR[ i ]( s[ i ] ); + } + + // Get transport + transport = inspectPrefiltersOrTransports( transports, s, options, jqXHR ); + + // If no transport, we auto-abort + if ( !transport ) { + done( -1, "No Transport" ); + } else { + jqXHR.readyState = 1; + // Send global event + if ( fireGlobals ) { + globalEventContext.trigger( "ajaxSend", [ jqXHR, s ] ); + } + // Timeout + if ( s.async && s.timeout > 0 ) { + timeoutTimer = setTimeout( function(){ + jqXHR.abort( "timeout" ); + }, s.timeout ); + } + + try { + state = 1; + transport.send( requestHeaders, done ); + } catch (e) { + // Propagate exception as error if not done + if ( status < 2 ) { + done( -1, e ); + // Simply rethrow otherwise + } else { + jQuery.error( e ); + } + } + } + + return jqXHR; + }, + + // Serialize an array of form elements or a set of + // key/values into a query string + param: function( a, traditional ) { + var s = [], + add = function( key, value ) { + // If value is a function, invoke it and return its value + value = jQuery.isFunction( value ) ? value() : value; + s[ s.length ] = encodeURIComponent( key ) + "=" + encodeURIComponent( value ); + }; + + // Set traditional to true for jQuery <= 1.3.2 behavior. + if ( traditional === undefined ) { + traditional = jQuery.ajaxSettings.traditional; + } + + // If an array was passed in, assume that it is an array of form elements. + if ( jQuery.isArray( a ) || ( a.jquery && !jQuery.isPlainObject( a ) ) ) { + // Serialize the form elements + jQuery.each( a, function() { + add( this.name, this.value ); + }); + + } else { + // If traditional, encode the "old" way (the way 1.3.2 or older + // did it), otherwise encode params recursively. + for ( var prefix in a ) { + buildParams( prefix, a[ prefix ], traditional, add ); + } + } + + // Return the resulting serialization + return s.join( "&" ).replace( r20, "+" ); + } +}); + +function buildParams( prefix, obj, traditional, add ) { + if ( jQuery.isArray( obj ) ) { + // Serialize array item. + jQuery.each( obj, function( i, v ) { + if ( traditional || rbracket.test( prefix ) ) { + // Treat each array item as a scalar. + add( prefix, v ); + + } else { + // If array item is non-scalar (array or object), encode its + // numeric index to resolve deserialization ambiguity issues. + // Note that rack (as of 1.0.0) can't currently deserialize + // nested arrays properly, and attempting to do so may cause + // a server error. Possible fixes are to modify rack's + // deserialization algorithm or to provide an option or flag + // to force array serialization to be shallow. + buildParams( prefix + "[" + ( typeof v === "object" || jQuery.isArray(v) ? i : "" ) + "]", v, traditional, add ); + } + }); + + } else if ( !traditional && obj != null && typeof obj === "object" ) { + // Serialize object item. + for ( var name in obj ) { + buildParams( prefix + "[" + name + "]", obj[ name ], traditional, add ); + } + + } else { + // Serialize scalar item. + add( prefix, obj ); + } +} + +// This is still on the jQuery object... for now +// Want to move this to jQuery.ajax some day +jQuery.extend({ + + // Counter for holding the number of active queries + active: 0, + + // Last-Modified header cache for next request + lastModified: {}, + etag: {} + +}); + +/* Handles responses to an ajax request: + * - sets all responseXXX fields accordingly + * - finds the right dataType (mediates between content-type and expected dataType) + * - returns the corresponding response + */ +function ajaxHandleResponses( s, jqXHR, responses ) { + + var contents = s.contents, + dataTypes = s.dataTypes, + responseFields = s.responseFields, + ct, + type, + finalDataType, + firstDataType; + + // Fill responseXXX fields + for( type in responseFields ) { + if ( type in responses ) { + jqXHR[ responseFields[type] ] = responses[ type ]; + } + } + + // Remove auto dataType and get content-type in the process + while( dataTypes[ 0 ] === "*" ) { + dataTypes.shift(); + if ( ct === undefined ) { + ct = s.mimeType || jqXHR.getResponseHeader( "content-type" ); + } + } + + // Check if we're dealing with a known content-type + if ( ct ) { + for ( type in contents ) { + if ( contents[ type ] && contents[ type ].test( ct ) ) { + dataTypes.unshift( type ); + break; + } + } + } + + // Check to see if we have a response for the expected dataType + if ( dataTypes[ 0 ] in responses ) { + finalDataType = dataTypes[ 0 ]; + } else { + // Try convertible dataTypes + for ( type in responses ) { + if ( !dataTypes[ 0 ] || s.converters[ type + " " + dataTypes[0] ] ) { + finalDataType = type; + break; + } + if ( !firstDataType ) { + firstDataType = type; + } + } + // Or just use first one + finalDataType = finalDataType || firstDataType; + } + + // If we found a dataType + // We add the dataType to the list if needed + // and return the corresponding response + if ( finalDataType ) { + if ( finalDataType !== dataTypes[ 0 ] ) { + dataTypes.unshift( finalDataType ); + } + return responses[ finalDataType ]; + } +} + +// Chain conversions given the request and the original response +function ajaxConvert( s, response ) { + + // Apply the dataFilter if provided + if ( s.dataFilter ) { + response = s.dataFilter( response, s.dataType ); + } + + var dataTypes = s.dataTypes, + converters = {}, + i, + key, + length = dataTypes.length, + tmp, + // Current and previous dataTypes + current = dataTypes[ 0 ], + prev, + // Conversion expression + conversion, + // Conversion function + conv, + // Conversion functions (transitive conversion) + conv1, + conv2; + + // For each dataType in the chain + for( i = 1; i < length; i++ ) { + + // Create converters map + // with lowercased keys + if ( i === 1 ) { + for( key in s.converters ) { + if( typeof key === "string" ) { + converters[ key.toLowerCase() ] = s.converters[ key ]; + } + } + } + + // Get the dataTypes + prev = current; + current = dataTypes[ i ]; + + // If current is auto dataType, update it to prev + if( current === "*" ) { + current = prev; + // If no auto and dataTypes are actually different + } else if ( prev !== "*" && prev !== current ) { + + // Get the converter + conversion = prev + " " + current; + conv = converters[ conversion ] || converters[ "* " + current ]; + + // If there is no direct converter, search transitively + if ( !conv ) { + conv2 = undefined; + for( conv1 in converters ) { + tmp = conv1.split( " " ); + if ( tmp[ 0 ] === prev || tmp[ 0 ] === "*" ) { + conv2 = converters[ tmp[1] + " " + current ]; + if ( conv2 ) { + conv1 = converters[ conv1 ]; + if ( conv1 === true ) { + conv = conv2; + } else if ( conv2 === true ) { + conv = conv1; + } + break; + } + } + } + } + // If we found no converter, dispatch an error + if ( !( conv || conv2 ) ) { + jQuery.error( "No conversion from " + conversion.replace(" "," to ") ); + } + // If found converter is not an equivalence + if ( conv !== true ) { + // Convert with 1 or 2 converters accordingly + response = conv ? conv( response ) : conv2( conv1(response) ); + } + } + } + return response; +} + + + + +var jsc = jQuery.now(), + jsre = /(\=)\?(&|$)|\?\?/i; + +// Default jsonp settings +jQuery.ajaxSetup({ + jsonp: "callback", + jsonpCallback: function() { + return jQuery.expando + "_" + ( jsc++ ); + } +}); + +// Detect, normalize options and install callbacks for jsonp requests +jQuery.ajaxPrefilter( "json jsonp", function( s, originalSettings, jqXHR ) { + + var inspectData = s.contentType === "application/x-www-form-urlencoded" && + ( typeof s.data === "string" ); + + if ( s.dataTypes[ 0 ] === "jsonp" || + s.jsonp !== false && ( jsre.test( s.url ) || + inspectData && jsre.test( s.data ) ) ) { + + var responseContainer, + jsonpCallback = s.jsonpCallback = + jQuery.isFunction( s.jsonpCallback ) ? s.jsonpCallback() : s.jsonpCallback, + previous = window[ jsonpCallback ], + url = s.url, + data = s.data, + replace = "$1" + jsonpCallback + "$2"; + + if ( s.jsonp !== false ) { + url = url.replace( jsre, replace ); + if ( s.url === url ) { + if ( inspectData ) { + data = data.replace( jsre, replace ); + } + if ( s.data === data ) { + // Add callback manually + url += (/\?/.test( url ) ? "&" : "?") + s.jsonp + "=" + jsonpCallback; + } + } + } + + s.url = url; + s.data = data; + + // Install callback + window[ jsonpCallback ] = function( response ) { + responseContainer = [ response ]; + }; + + // Clean-up function + jqXHR.always(function() { + // Set callback back to previous value + window[ jsonpCallback ] = previous; + // Call if it was a function and we have a response + if ( responseContainer && jQuery.isFunction( previous ) ) { + window[ jsonpCallback ]( responseContainer[ 0 ] ); + } + }); + + // Use data converter to retrieve json after script execution + s.converters["script json"] = function() { + if ( !responseContainer ) { + jQuery.error( jsonpCallback + " was not called" ); + } + return responseContainer[ 0 ]; + }; + + // force json dataType + s.dataTypes[ 0 ] = "json"; + + // Delegate to script + return "script"; + } +}); + + + + +// Install script dataType +jQuery.ajaxSetup({ + accepts: { + script: "text/javascript, application/javascript, application/ecmascript, application/x-ecmascript" + }, + contents: { + script: /javascript|ecmascript/ + }, + converters: { + "text script": function( text ) { + jQuery.globalEval( text ); + return text; + } + } +}); + +// Handle cache's special case and global +jQuery.ajaxPrefilter( "script", function( s ) { + if ( s.cache === undefined ) { + s.cache = false; + } + if ( s.crossDomain ) { + s.type = "GET"; + s.global = false; + } +}); + +// Bind script tag hack transport +jQuery.ajaxTransport( "script", function(s) { + + // This transport only deals with cross domain requests + if ( s.crossDomain ) { + + var script, + head = document.head || document.getElementsByTagName( "head" )[0] || document.documentElement; + + return { + + send: function( _, callback ) { + + script = document.createElement( "script" ); + + script.async = "async"; + + if ( s.scriptCharset ) { + script.charset = s.scriptCharset; + } + + script.src = s.url; + + // Attach handlers for all browsers + script.onload = script.onreadystatechange = function( _, isAbort ) { + + if ( isAbort || !script.readyState || /loaded|complete/.test( script.readyState ) ) { + + // Handle memory leak in IE + script.onload = script.onreadystatechange = null; + + // Remove the script + if ( head && script.parentNode ) { + head.removeChild( script ); + } + + // Dereference the script + script = undefined; + + // Callback if not abort + if ( !isAbort ) { + callback( 200, "success" ); + } + } + }; + // Use insertBefore instead of appendChild to circumvent an IE6 bug. + // This arises when a base node is used (#2709 and #4378). + head.insertBefore( script, head.firstChild ); + }, + + abort: function() { + if ( script ) { + script.onload( 0, 1 ); + } + } + }; + } +}); + + + + +var // #5280: Internet Explorer will keep connections alive if we don't abort on unload + xhrOnUnloadAbort = window.ActiveXObject ? function() { + // Abort all pending requests + for ( var key in xhrCallbacks ) { + xhrCallbacks[ key ]( 0, 1 ); + } + } : false, + xhrId = 0, + xhrCallbacks; + +// Functions to create xhrs +function createStandardXHR() { + try { + return new window.XMLHttpRequest(); + } catch( e ) {} +} + +function createActiveXHR() { + try { + return new window.ActiveXObject( "Microsoft.XMLHTTP" ); + } catch( e ) {} +} + +// Create the request object +// (This is still attached to ajaxSettings for backward compatibility) +jQuery.ajaxSettings.xhr = window.ActiveXObject ? + /* Microsoft failed to properly + * implement the XMLHttpRequest in IE7 (can't request local files), + * so we use the ActiveXObject when it is available + * Additionally XMLHttpRequest can be disabled in IE7/IE8 so + * we need a fallback. + */ + function() { + return !this.isLocal && createStandardXHR() || createActiveXHR(); + } : + // For all other browsers, use the standard XMLHttpRequest object + createStandardXHR; + +// Determine support properties +(function( xhr ) { + jQuery.extend( jQuery.support, { + ajax: !!xhr, + cors: !!xhr && ( "withCredentials" in xhr ) + }); +})( jQuery.ajaxSettings.xhr() ); + +// Create transport if the browser can provide an xhr +if ( jQuery.support.ajax ) { + + jQuery.ajaxTransport(function( s ) { + // Cross domain only allowed if supported through XMLHttpRequest + if ( !s.crossDomain || jQuery.support.cors ) { + + var callback; + + return { + send: function( headers, complete ) { + + // Get a new xhr + var xhr = s.xhr(), + handle, + i; + + // Open the socket + // Passing null username, generates a login popup on Opera (#2865) + if ( s.username ) { + xhr.open( s.type, s.url, s.async, s.username, s.password ); + } else { + xhr.open( s.type, s.url, s.async ); + } + + // Apply custom fields if provided + if ( s.xhrFields ) { + for ( i in s.xhrFields ) { + xhr[ i ] = s.xhrFields[ i ]; + } + } + + // Override mime type if needed + if ( s.mimeType && xhr.overrideMimeType ) { + xhr.overrideMimeType( s.mimeType ); + } + + // X-Requested-With header + // For cross-domain requests, seeing as conditions for a preflight are + // akin to a jigsaw puzzle, we simply never set it to be sure. + // (it can always be set on a per-request basis or even using ajaxSetup) + // For same-domain requests, won't change header if already provided. + if ( !s.crossDomain && !headers["X-Requested-With"] ) { + headers[ "X-Requested-With" ] = "XMLHttpRequest"; + } + + // Need an extra try/catch for cross domain requests in Firefox 3 + try { + for ( i in headers ) { + xhr.setRequestHeader( i, headers[ i ] ); + } + } catch( _ ) {} + + // Do send the request + // This may raise an exception which is actually + // handled in jQuery.ajax (so no try/catch here) + xhr.send( ( s.hasContent && s.data ) || null ); + + // Listener + callback = function( _, isAbort ) { + + var status, + statusText, + responseHeaders, + responses, + xml; + + // Firefox throws exceptions when accessing properties + // of an xhr when a network error occured + // http://helpful.knobs-dials.com/index.php/Component_returned_failure_code:_0x80040111_(NS_ERROR_NOT_AVAILABLE) + try { + + // Was never called and is aborted or complete + if ( callback && ( isAbort || xhr.readyState === 4 ) ) { + + // Only called once + callback = undefined; + + // Do not keep as active anymore + if ( handle ) { + xhr.onreadystatechange = jQuery.noop; + if ( xhrOnUnloadAbort ) { + delete xhrCallbacks[ handle ]; + } + } + + // If it's an abort + if ( isAbort ) { + // Abort it manually if needed + if ( xhr.readyState !== 4 ) { + xhr.abort(); + } + } else { + status = xhr.status; + responseHeaders = xhr.getAllResponseHeaders(); + responses = {}; + xml = xhr.responseXML; + + // Construct response list + if ( xml && xml.documentElement /* #4958 */ ) { + responses.xml = xml; + } + responses.text = xhr.responseText; + + // Firefox throws an exception when accessing + // statusText for faulty cross-domain requests + try { + statusText = xhr.statusText; + } catch( e ) { + // We normalize with Webkit giving an empty statusText + statusText = ""; + } + + // Filter status for non standard behaviors + + // If the request is local and we have data: assume a success + // (success with no data won't get notified, that's the best we + // can do given current implementations) + if ( !status && s.isLocal && !s.crossDomain ) { + status = responses.text ? 200 : 404; + // IE - #1450: sometimes returns 1223 when it should be 204 + } else if ( status === 1223 ) { + status = 204; + } + } + } + } catch( firefoxAccessException ) { + if ( !isAbort ) { + complete( -1, firefoxAccessException ); + } + } + + // Call complete if needed + if ( responses ) { + complete( status, statusText, responses, responseHeaders ); + } + }; + + // if we're in sync mode or it's in cache + // and has been retrieved directly (IE6 & IE7) + // we need to manually fire the callback + if ( !s.async || xhr.readyState === 4 ) { + callback(); + } else { + handle = ++xhrId; + if ( xhrOnUnloadAbort ) { + // Create the active xhrs callbacks list if needed + // and attach the unload handler + if ( !xhrCallbacks ) { + xhrCallbacks = {}; + jQuery( window ).unload( xhrOnUnloadAbort ); + } + // Add to list of active xhrs callbacks + xhrCallbacks[ handle ] = callback; + } + xhr.onreadystatechange = callback; + } + }, + + abort: function() { + if ( callback ) { + callback(0,1); + } + } + }; + } + }); +} + + + + +var elemdisplay = {}, + iframe, iframeDoc, + rfxtypes = /^(?:toggle|show|hide)$/, + rfxnum = /^([+\-]=)?([\d+.\-]+)([a-z%]*)$/i, + timerId, + fxAttrs = [ + // height animations + [ "height", "marginTop", "marginBottom", "paddingTop", "paddingBottom" ], + // width animations + [ "width", "marginLeft", "marginRight", "paddingLeft", "paddingRight" ], + // opacity animations + [ "opacity" ] + ], + fxNow, + requestAnimationFrame = window.webkitRequestAnimationFrame || + window.mozRequestAnimationFrame || + window.oRequestAnimationFrame; + +jQuery.fn.extend({ + show: function( speed, easing, callback ) { + var elem, display; + + if ( speed || speed === 0 ) { + return this.animate( genFx("show", 3), speed, easing, callback); + + } else { + for ( var i = 0, j = this.length; i < j; i++ ) { + elem = this[i]; + + if ( elem.style ) { + display = elem.style.display; + + // Reset the inline display of this element to learn if it is + // being hidden by cascaded rules or not + if ( !jQuery._data(elem, "olddisplay") && display === "none" ) { + display = elem.style.display = ""; + } + + // Set elements which have been overridden with display: none + // in a stylesheet to whatever the default browser style is + // for such an element + if ( display === "" && jQuery.css( elem, "display" ) === "none" ) { + jQuery._data(elem, "olddisplay", defaultDisplay(elem.nodeName)); + } + } + } + + // Set the display of most of the elements in a second loop + // to avoid the constant reflow + for ( i = 0; i < j; i++ ) { + elem = this[i]; + + if ( elem.style ) { + display = elem.style.display; + + if ( display === "" || display === "none" ) { + elem.style.display = jQuery._data(elem, "olddisplay") || ""; + } + } + } + + return this; + } + }, + + hide: function( speed, easing, callback ) { + if ( speed || speed === 0 ) { + return this.animate( genFx("hide", 3), speed, easing, callback); + + } else { + for ( var i = 0, j = this.length; i < j; i++ ) { + if ( this[i].style ) { + var display = jQuery.css( this[i], "display" ); + + if ( display !== "none" && !jQuery._data( this[i], "olddisplay" ) ) { + jQuery._data( this[i], "olddisplay", display ); + } + } + } + + // Set the display of the elements in a second loop + // to avoid the constant reflow + for ( i = 0; i < j; i++ ) { + if ( this[i].style ) { + this[i].style.display = "none"; + } + } + + return this; + } + }, + + // Save the old toggle function + _toggle: jQuery.fn.toggle, + + toggle: function( fn, fn2, callback ) { + var bool = typeof fn === "boolean"; + + if ( jQuery.isFunction(fn) && jQuery.isFunction(fn2) ) { + this._toggle.apply( this, arguments ); + + } else if ( fn == null || bool ) { + this.each(function() { + var state = bool ? fn : jQuery(this).is(":hidden"); + jQuery(this)[ state ? "show" : "hide" ](); + }); + + } else { + this.animate(genFx("toggle", 3), fn, fn2, callback); + } + + return this; + }, + + fadeTo: function( speed, to, easing, callback ) { + return this.filter(":hidden").css("opacity", 0).show().end() + .animate({opacity: to}, speed, easing, callback); + }, + + animate: function( prop, speed, easing, callback ) { + var optall = jQuery.speed(speed, easing, callback); + + if ( jQuery.isEmptyObject( prop ) ) { + return this.each( optall.complete, [ false ] ); + } + + // Do not change referenced properties as per-property easing will be lost + prop = jQuery.extend( {}, prop ); + + return this[ optall.queue === false ? "each" : "queue" ](function() { + // XXX 'this' does not always have a nodeName when running the + // test suite + + if ( optall.queue === false ) { + jQuery._mark( this ); + } + + var opt = jQuery.extend( {}, optall ), + isElement = this.nodeType === 1, + hidden = isElement && jQuery(this).is(":hidden"), + name, val, p, + display, e, + parts, start, end, unit; + + // will store per property easing and be used to determine when an animation is complete + opt.animatedProperties = {}; + + for ( p in prop ) { + + // property name normalization + name = jQuery.camelCase( p ); + if ( p !== name ) { + prop[ name ] = prop[ p ]; + delete prop[ p ]; + } + + val = prop[ name ]; + + // easing resolution: per property > opt.specialEasing > opt.easing > 'swing' (default) + if ( jQuery.isArray( val ) ) { + opt.animatedProperties[ name ] = val[ 1 ]; + val = prop[ name ] = val[ 0 ]; + } else { + opt.animatedProperties[ name ] = opt.specialEasing && opt.specialEasing[ name ] || opt.easing || 'swing'; + } + + if ( val === "hide" && hidden || val === "show" && !hidden ) { + return opt.complete.call( this ); + } + + if ( isElement && ( name === "height" || name === "width" ) ) { + // Make sure that nothing sneaks out + // Record all 3 overflow attributes because IE does not + // change the overflow attribute when overflowX and + // overflowY are set to the same value + opt.overflow = [ this.style.overflow, this.style.overflowX, this.style.overflowY ]; + + // Set display property to inline-block for height/width + // animations on inline elements that are having width/height + // animated + if ( jQuery.css( this, "display" ) === "inline" && + jQuery.css( this, "float" ) === "none" ) { + if ( !jQuery.support.inlineBlockNeedsLayout ) { + this.style.display = "inline-block"; + + } else { + display = defaultDisplay( this.nodeName ); + + // inline-level elements accept inline-block; + // block-level elements need to be inline with layout + if ( display === "inline" ) { + this.style.display = "inline-block"; + + } else { + this.style.display = "inline"; + this.style.zoom = 1; + } + } + } + } + } + + if ( opt.overflow != null ) { + this.style.overflow = "hidden"; + } + + for ( p in prop ) { + e = new jQuery.fx( this, opt, p ); + val = prop[ p ]; + + if ( rfxtypes.test(val) ) { + e[ val === "toggle" ? hidden ? "show" : "hide" : val ](); + + } else { + parts = rfxnum.exec( val ); + start = e.cur(); + + if ( parts ) { + end = parseFloat( parts[2] ); + unit = parts[3] || ( jQuery.cssNumber[ p ] ? "" : "px" ); + + // We need to compute starting value + if ( unit !== "px" ) { + jQuery.style( this, p, (end || 1) + unit); + start = ((end || 1) / e.cur()) * start; + jQuery.style( this, p, start + unit); + } + + // If a +=/-= token was provided, we're doing a relative animation + if ( parts[1] ) { + end = ( (parts[ 1 ] === "-=" ? -1 : 1) * end ) + start; + } + + e.custom( start, end, unit ); + + } else { + e.custom( start, val, "" ); + } + } + } + + // For JS strict compliance + return true; + }); + }, + + stop: function( clearQueue, gotoEnd ) { + if ( clearQueue ) { + this.queue([]); + } + + this.each(function() { + var timers = jQuery.timers, + i = timers.length; + // clear marker counters if we know they won't be + if ( !gotoEnd ) { + jQuery._unmark( true, this ); + } + while ( i-- ) { + if ( timers[i].elem === this ) { + if (gotoEnd) { + // force the next step to be the last + timers[i](true); + } + + timers.splice(i, 1); + } + } + }); + + // start the next in the queue if the last step wasn't forced + if ( !gotoEnd ) { + this.dequeue(); + } + + return this; + } + +}); + +// Animations created synchronously will run synchronously +function createFxNow() { + setTimeout( clearFxNow, 0 ); + return ( fxNow = jQuery.now() ); +} + +function clearFxNow() { + fxNow = undefined; +} + +// Generate parameters to create a standard animation +function genFx( type, num ) { + var obj = {}; + + jQuery.each( fxAttrs.concat.apply([], fxAttrs.slice(0,num)), function() { + obj[ this ] = type; + }); + + return obj; +} + +// Generate shortcuts for custom animations +jQuery.each({ + slideDown: genFx("show", 1), + slideUp: genFx("hide", 1), + slideToggle: genFx("toggle", 1), + fadeIn: { opacity: "show" }, + fadeOut: { opacity: "hide" }, + fadeToggle: { opacity: "toggle" } +}, function( name, props ) { + jQuery.fn[ name ] = function( speed, easing, callback ) { + return this.animate( props, speed, easing, callback ); + }; +}); + +jQuery.extend({ + speed: function( speed, easing, fn ) { + var opt = speed && typeof speed === "object" ? jQuery.extend({}, speed) : { + complete: fn || !fn && easing || + jQuery.isFunction( speed ) && speed, + duration: speed, + easing: fn && easing || easing && !jQuery.isFunction(easing) && easing + }; + + opt.duration = jQuery.fx.off ? 0 : typeof opt.duration === "number" ? opt.duration : + opt.duration in jQuery.fx.speeds ? jQuery.fx.speeds[opt.duration] : jQuery.fx.speeds._default; + + // Queueing + opt.old = opt.complete; + opt.complete = function( noUnmark ) { + if ( jQuery.isFunction( opt.old ) ) { + opt.old.call( this ); + } + + if ( opt.queue !== false ) { + jQuery.dequeue( this ); + } else if ( noUnmark !== false ) { + jQuery._unmark( this ); + } + }; + + return opt; + }, + + easing: { + linear: function( p, n, firstNum, diff ) { + return firstNum + diff * p; + }, + swing: function( p, n, firstNum, diff ) { + return ((-Math.cos(p*Math.PI)/2) + 0.5) * diff + firstNum; + } + }, + + timers: [], + + fx: function( elem, options, prop ) { + this.options = options; + this.elem = elem; + this.prop = prop; + + options.orig = options.orig || {}; + } + +}); + +jQuery.fx.prototype = { + // Simple function for setting a style value + update: function() { + if ( this.options.step ) { + this.options.step.call( this.elem, this.now, this ); + } + + (jQuery.fx.step[this.prop] || jQuery.fx.step._default)( this ); + }, + + // Get the current size + cur: function() { + if ( this.elem[this.prop] != null && (!this.elem.style || this.elem.style[this.prop] == null) ) { + return this.elem[ this.prop ]; + } + + var parsed, + r = jQuery.css( this.elem, this.prop ); + // Empty strings, null, undefined and "auto" are converted to 0, + // complex values such as "rotate(1rad)" are returned as is, + // simple values such as "10px" are parsed to Float. + return isNaN( parsed = parseFloat( r ) ) ? !r || r === "auto" ? 0 : r : parsed; + }, + + // Start an animation from one number to another + custom: function( from, to, unit ) { + var self = this, + fx = jQuery.fx, + raf; + + this.startTime = fxNow || createFxNow(); + this.start = from; + this.end = to; + this.unit = unit || this.unit || ( jQuery.cssNumber[ this.prop ] ? "" : "px" ); + this.now = this.start; + this.pos = this.state = 0; + + function t( gotoEnd ) { + return self.step(gotoEnd); + } + + t.elem = this.elem; + + if ( t() && jQuery.timers.push(t) && !timerId ) { + // Use requestAnimationFrame instead of setInterval if available + if ( requestAnimationFrame ) { + timerId = true; + raf = function() { + // When timerId gets set to null at any point, this stops + if ( timerId ) { + requestAnimationFrame( raf ); + fx.tick(); + } + }; + requestAnimationFrame( raf ); + } else { + timerId = setInterval( fx.tick, fx.interval ); + } + } + }, + + // Simple 'show' function + show: function() { + // Remember where we started, so that we can go back to it later + this.options.orig[this.prop] = jQuery.style( this.elem, this.prop ); + this.options.show = true; + + // Begin the animation + // Make sure that we start at a small width/height to avoid any + // flash of content + this.custom(this.prop === "width" || this.prop === "height" ? 1 : 0, this.cur()); + + // Start by showing the element + jQuery( this.elem ).show(); + }, + + // Simple 'hide' function + hide: function() { + // Remember where we started, so that we can go back to it later + this.options.orig[this.prop] = jQuery.style( this.elem, this.prop ); + this.options.hide = true; + + // Begin the animation + this.custom(this.cur(), 0); + }, + + // Each step of an animation + step: function( gotoEnd ) { + var t = fxNow || createFxNow(), + done = true, + elem = this.elem, + options = this.options, + i, n; + + if ( gotoEnd || t >= options.duration + this.startTime ) { + this.now = this.end; + this.pos = this.state = 1; + this.update(); + + options.animatedProperties[ this.prop ] = true; + + for ( i in options.animatedProperties ) { + if ( options.animatedProperties[i] !== true ) { + done = false; + } + } + + if ( done ) { + // Reset the overflow + if ( options.overflow != null && !jQuery.support.shrinkWrapBlocks ) { + + jQuery.each( [ "", "X", "Y" ], function (index, value) { + elem.style[ "overflow" + value ] = options.overflow[index]; + }); + } + + // Hide the element if the "hide" operation was done + if ( options.hide ) { + jQuery(elem).hide(); + } + + // Reset the properties, if the item has been hidden or shown + if ( options.hide || options.show ) { + for ( var p in options.animatedProperties ) { + jQuery.style( elem, p, options.orig[p] ); + } + } + + // Execute the complete function + options.complete.call( elem ); + } + + return false; + + } else { + // classical easing cannot be used with an Infinity duration + if ( options.duration == Infinity ) { + this.now = t; + } else { + n = t - this.startTime; + this.state = n / options.duration; + + // Perform the easing function, defaults to swing + this.pos = jQuery.easing[ options.animatedProperties[ this.prop ] ]( this.state, n, 0, 1, options.duration ); + this.now = this.start + ((this.end - this.start) * this.pos); + } + // Perform the next step of the animation + this.update(); + } + + return true; + } +}; + +jQuery.extend( jQuery.fx, { + tick: function() { + for ( var timers = jQuery.timers, i = 0 ; i < timers.length ; ++i ) { + if ( !timers[i]() ) { + timers.splice(i--, 1); + } + } + + if ( !timers.length ) { + jQuery.fx.stop(); + } + }, + + interval: 13, + + stop: function() { + clearInterval( timerId ); + timerId = null; + }, + + speeds: { + slow: 600, + fast: 200, + // Default speed + _default: 400 + }, + + step: { + opacity: function( fx ) { + jQuery.style( fx.elem, "opacity", fx.now ); + }, + + _default: function( fx ) { + if ( fx.elem.style && fx.elem.style[ fx.prop ] != null ) { + fx.elem.style[ fx.prop ] = (fx.prop === "width" || fx.prop === "height" ? Math.max(0, fx.now) : fx.now) + fx.unit; + } else { + fx.elem[ fx.prop ] = fx.now; + } + } + } +}); + +if ( jQuery.expr && jQuery.expr.filters ) { + jQuery.expr.filters.animated = function( elem ) { + return jQuery.grep(jQuery.timers, function( fn ) { + return elem === fn.elem; + }).length; + }; +} + +// Try to restore the default display value of an element +function defaultDisplay( nodeName ) { + + if ( !elemdisplay[ nodeName ] ) { + + var body = document.body, + elem = jQuery( "<" + nodeName + ">" ).appendTo( body ), + display = elem.css( "display" ); + + elem.remove(); + + // If the simple way fails, + // get element's real default display by attaching it to a temp iframe + if ( display === "none" || display === "" ) { + // No iframe to use yet, so create it + if ( !iframe ) { + iframe = document.createElement( "iframe" ); + iframe.frameBorder = iframe.width = iframe.height = 0; + } + + body.appendChild( iframe ); + + // Create a cacheable copy of the iframe document on first call. + // IE and Opera will allow us to reuse the iframeDoc without re-writing the fake HTML + // document to it; WebKit & Firefox won't allow reusing the iframe document. + if ( !iframeDoc || !iframe.createElement ) { + iframeDoc = ( iframe.contentWindow || iframe.contentDocument ).document; + iframeDoc.write( ( document.compatMode === "CSS1Compat" ? "<!doctype html>" : "" ) + "<html><body>" ); + iframeDoc.close(); + } + + elem = iframeDoc.createElement( nodeName ); + + iframeDoc.body.appendChild( elem ); + + display = jQuery.css( elem, "display" ); + + body.removeChild( iframe ); + } + + // Store the correct default display + elemdisplay[ nodeName ] = display; + } + + return elemdisplay[ nodeName ]; +} + + + + +var rtable = /^t(?:able|d|h)$/i, + rroot = /^(?:body|html)$/i; + +if ( "getBoundingClientRect" in document.documentElement ) { + jQuery.fn.offset = function( options ) { + var elem = this[0], box; + + if ( options ) { + return this.each(function( i ) { + jQuery.offset.setOffset( this, options, i ); + }); + } + + if ( !elem || !elem.ownerDocument ) { + return null; + } + + if ( elem === elem.ownerDocument.body ) { + return jQuery.offset.bodyOffset( elem ); + } + + try { + box = elem.getBoundingClientRect(); + } catch(e) {} + + var doc = elem.ownerDocument, + docElem = doc.documentElement; + + // Make sure we're not dealing with a disconnected DOM node + if ( !box || !jQuery.contains( docElem, elem ) ) { + return box ? { top: box.top, left: box.left } : { top: 0, left: 0 }; + } + + var body = doc.body, + win = getWindow(doc), + clientTop = docElem.clientTop || body.clientTop || 0, + clientLeft = docElem.clientLeft || body.clientLeft || 0, + scrollTop = win.pageYOffset || jQuery.support.boxModel && docElem.scrollTop || body.scrollTop, + scrollLeft = win.pageXOffset || jQuery.support.boxModel && docElem.scrollLeft || body.scrollLeft, + top = box.top + scrollTop - clientTop, + left = box.left + scrollLeft - clientLeft; + + return { top: top, left: left }; + }; + +} else { + jQuery.fn.offset = function( options ) { + var elem = this[0]; + + if ( options ) { + return this.each(function( i ) { + jQuery.offset.setOffset( this, options, i ); + }); + } + + if ( !elem || !elem.ownerDocument ) { + return null; + } + + if ( elem === elem.ownerDocument.body ) { + return jQuery.offset.bodyOffset( elem ); + } + + jQuery.offset.initialize(); + + var computedStyle, + offsetParent = elem.offsetParent, + prevOffsetParent = elem, + doc = elem.ownerDocument, + docElem = doc.documentElement, + body = doc.body, + defaultView = doc.defaultView, + prevComputedStyle = defaultView ? defaultView.getComputedStyle( elem, null ) : elem.currentStyle, + top = elem.offsetTop, + left = elem.offsetLeft; + + while ( (elem = elem.parentNode) && elem !== body && elem !== docElem ) { + if ( jQuery.offset.supportsFixedPosition && prevComputedStyle.position === "fixed" ) { + break; + } + + computedStyle = defaultView ? defaultView.getComputedStyle(elem, null) : elem.currentStyle; + top -= elem.scrollTop; + left -= elem.scrollLeft; + + if ( elem === offsetParent ) { + top += elem.offsetTop; + left += elem.offsetLeft; + + if ( jQuery.offset.doesNotAddBorder && !(jQuery.offset.doesAddBorderForTableAndCells && rtable.test(elem.nodeName)) ) { + top += parseFloat( computedStyle.borderTopWidth ) || 0; + left += parseFloat( computedStyle.borderLeftWidth ) || 0; + } + + prevOffsetParent = offsetParent; + offsetParent = elem.offsetParent; + } + + if ( jQuery.offset.subtractsBorderForOverflowNotVisible && computedStyle.overflow !== "visible" ) { + top += parseFloat( computedStyle.borderTopWidth ) || 0; + left += parseFloat( computedStyle.borderLeftWidth ) || 0; + } + + prevComputedStyle = computedStyle; + } + + if ( prevComputedStyle.position === "relative" || prevComputedStyle.position === "static" ) { + top += body.offsetTop; + left += body.offsetLeft; + } + + if ( jQuery.offset.supportsFixedPosition && prevComputedStyle.position === "fixed" ) { + top += Math.max( docElem.scrollTop, body.scrollTop ); + left += Math.max( docElem.scrollLeft, body.scrollLeft ); + } + + return { top: top, left: left }; + }; +} + +jQuery.offset = { + initialize: function() { + var body = document.body, container = document.createElement("div"), innerDiv, checkDiv, table, td, bodyMarginTop = parseFloat( jQuery.css(body, "marginTop") ) || 0, + html = "<div style='position:absolute;top:0;left:0;margin:0;border:5px solid #000;padding:0;width:1px;height:1px;'><div></div></div><table style='position:absolute;top:0;left:0;margin:0;border:5px solid #000;padding:0;width:1px;height:1px;' cellpadding='0' cellspacing='0'><tr><td></td></tr></table>"; + + jQuery.extend( container.style, { position: "absolute", top: 0, left: 0, margin: 0, border: 0, width: "1px", height: "1px", visibility: "hidden" } ); + + container.innerHTML = html; + body.insertBefore( container, body.firstChild ); + innerDiv = container.firstChild; + checkDiv = innerDiv.firstChild; + td = innerDiv.nextSibling.firstChild.firstChild; + + this.doesNotAddBorder = (checkDiv.offsetTop !== 5); + this.doesAddBorderForTableAndCells = (td.offsetTop === 5); + + checkDiv.style.position = "fixed"; + checkDiv.style.top = "20px"; + + // safari subtracts parent border width here which is 5px + this.supportsFixedPosition = (checkDiv.offsetTop === 20 || checkDiv.offsetTop === 15); + checkDiv.style.position = checkDiv.style.top = ""; + + innerDiv.style.overflow = "hidden"; + innerDiv.style.position = "relative"; + + this.subtractsBorderForOverflowNotVisible = (checkDiv.offsetTop === -5); + + this.doesNotIncludeMarginInBodyOffset = (body.offsetTop !== bodyMarginTop); + + body.removeChild( container ); + jQuery.offset.initialize = jQuery.noop; + }, + + bodyOffset: function( body ) { + var top = body.offsetTop, + left = body.offsetLeft; + + jQuery.offset.initialize(); + + if ( jQuery.offset.doesNotIncludeMarginInBodyOffset ) { + top += parseFloat( jQuery.css(body, "marginTop") ) || 0; + left += parseFloat( jQuery.css(body, "marginLeft") ) || 0; + } + + return { top: top, left: left }; + }, + + setOffset: function( elem, options, i ) { + var position = jQuery.css( elem, "position" ); + + // set position first, in-case top/left are set even on static elem + if ( position === "static" ) { + elem.style.position = "relative"; + } + + var curElem = jQuery( elem ), + curOffset = curElem.offset(), + curCSSTop = jQuery.css( elem, "top" ), + curCSSLeft = jQuery.css( elem, "left" ), + calculatePosition = (position === "absolute" || position === "fixed") && jQuery.inArray("auto", [curCSSTop, curCSSLeft]) > -1, + props = {}, curPosition = {}, curTop, curLeft; + + // need to be able to calculate position if either top or left is auto and position is either absolute or fixed + if ( calculatePosition ) { + curPosition = curElem.position(); + curTop = curPosition.top; + curLeft = curPosition.left; + } else { + curTop = parseFloat( curCSSTop ) || 0; + curLeft = parseFloat( curCSSLeft ) || 0; + } + + if ( jQuery.isFunction( options ) ) { + options = options.call( elem, i, curOffset ); + } + + if (options.top != null) { + props.top = (options.top - curOffset.top) + curTop; + } + if (options.left != null) { + props.left = (options.left - curOffset.left) + curLeft; + } + + if ( "using" in options ) { + options.using.call( elem, props ); + } else { + curElem.css( props ); + } + } +}; + + +jQuery.fn.extend({ + position: function() { + if ( !this[0] ) { + return null; + } + + var elem = this[0], + + // Get *real* offsetParent + offsetParent = this.offsetParent(), + + // Get correct offsets + offset = this.offset(), + parentOffset = rroot.test(offsetParent[0].nodeName) ? { top: 0, left: 0 } : offsetParent.offset(); + + // Subtract element margins + // note: when an element has margin: auto the offsetLeft and marginLeft + // are the same in Safari causing offset.left to incorrectly be 0 + offset.top -= parseFloat( jQuery.css(elem, "marginTop") ) || 0; + offset.left -= parseFloat( jQuery.css(elem, "marginLeft") ) || 0; + + // Add offsetParent borders + parentOffset.top += parseFloat( jQuery.css(offsetParent[0], "borderTopWidth") ) || 0; + parentOffset.left += parseFloat( jQuery.css(offsetParent[0], "borderLeftWidth") ) || 0; + + // Subtract the two offsets + return { + top: offset.top - parentOffset.top, + left: offset.left - parentOffset.left + }; + }, + + offsetParent: function() { + return this.map(function() { + var offsetParent = this.offsetParent || document.body; + while ( offsetParent && (!rroot.test(offsetParent.nodeName) && jQuery.css(offsetParent, "position") === "static") ) { + offsetParent = offsetParent.offsetParent; + } + return offsetParent; + }); + } +}); + + +// Create scrollLeft and scrollTop methods +jQuery.each( ["Left", "Top"], function( i, name ) { + var method = "scroll" + name; + + jQuery.fn[ method ] = function( val ) { + var elem, win; + + if ( val === undefined ) { + elem = this[ 0 ]; + + if ( !elem ) { + return null; + } + + win = getWindow( elem ); + + // Return the scroll offset + return win ? ("pageXOffset" in win) ? win[ i ? "pageYOffset" : "pageXOffset" ] : + jQuery.support.boxModel && win.document.documentElement[ method ] || + win.document.body[ method ] : + elem[ method ]; + } + + // Set the scroll offset + return this.each(function() { + win = getWindow( this ); + + if ( win ) { + win.scrollTo( + !i ? val : jQuery( win ).scrollLeft(), + i ? val : jQuery( win ).scrollTop() + ); + + } else { + this[ method ] = val; + } + }); + }; +}); + +function getWindow( elem ) { + return jQuery.isWindow( elem ) ? + elem : + elem.nodeType === 9 ? + elem.defaultView || elem.parentWindow : + false; +} + + + + +// Create width, height, innerHeight, innerWidth, outerHeight and outerWidth methods +jQuery.each([ "Height", "Width" ], function( i, name ) { + + var type = name.toLowerCase(); + + // innerHeight and innerWidth + jQuery.fn[ "inner" + name ] = function() { + var elem = this[0]; + return elem && elem.style ? + parseFloat( jQuery.css( elem, type, "padding" ) ) : + null; + }; + + // outerHeight and outerWidth + jQuery.fn[ "outer" + name ] = function( margin ) { + var elem = this[0]; + return elem && elem.style ? + parseFloat( jQuery.css( elem, type, margin ? "margin" : "border" ) ) : + null; + }; + + jQuery.fn[ type ] = function( size ) { + // Get window width or height + var elem = this[0]; + if ( !elem ) { + return size == null ? null : this; + } + + if ( jQuery.isFunction( size ) ) { + return this.each(function( i ) { + var self = jQuery( this ); + self[ type ]( size.call( this, i, self[ type ]() ) ); + }); + } + + if ( jQuery.isWindow( elem ) ) { + // Everyone else use document.documentElement or document.body depending on Quirks vs Standards mode + // 3rd condition allows Nokia support, as it supports the docElem prop but not CSS1Compat + var docElemProp = elem.document.documentElement[ "client" + name ]; + return elem.document.compatMode === "CSS1Compat" && docElemProp || + elem.document.body[ "client" + name ] || docElemProp; + + // Get document width or height + } else if ( elem.nodeType === 9 ) { + // Either scroll[Width/Height] or offset[Width/Height], whichever is greater + return Math.max( + elem.documentElement["client" + name], + elem.body["scroll" + name], elem.documentElement["scroll" + name], + elem.body["offset" + name], elem.documentElement["offset" + name] + ); + + // Get or set width or height on the element + } else if ( size === undefined ) { + var orig = jQuery.css( elem, type ), + ret = parseFloat( orig ); + + return jQuery.isNaN( ret ) ? orig : ret; + + // Set the width or height on the element (default to pixels if value is unitless) + } else { + return this.css( type, typeof size === "string" ? size : size + "px" ); + } + }; + +}); + + +// Expose jQuery to the global object +window.jQuery = window.$ = jQuery; +})(window); From f1c7c475f6eab1a74dcf5b11aaeac9dd6ad986f8 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Fri, 27 Jul 2012 00:17:04 -0400 Subject: [PATCH 128/331] automatically close the webapp window after 3 errors It's unlikely an error would occur unless the server is stopped. But retrying a few times seems like a good idea anyway. --- templates/longpolling.julius | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/templates/longpolling.julius b/templates/longpolling.julius index 26356f5e93..351f2f8c60 100644 --- a/templates/longpolling.julius +++ b/templates/longpolling.julius @@ -7,6 +7,8 @@ (function( $ ) { +numerrs=0; + $.LongPoll = (function() { return { send : function() { @@ -16,6 +18,16 @@ $.LongPoll = (function() { 'success': function(data, status, jqxhr) { $('##{poll}').replaceWith(data); setTimeout($.LongPoll.send, #{delay}); + numerrs=0; + }, + 'error': function(jqxhr, msg, e) { + numerrs=numerrs+1; + if (numerrs > 3) { + window.close(); + } + else { + setTimeout($.LongPoll.send, #{delay}); + } }, }); } From 1f47c1f6d8f9b799fc85cfb12bf73030fe455167 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Fri, 27 Jul 2012 00:35:09 -0400 Subject: [PATCH 129/331] update --- debian/copyright | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/debian/copyright b/debian/copyright index 72b6333671..1b00d07e77 100644 --- a/debian/copyright +++ b/debian/copyright @@ -20,7 +20,7 @@ Copyright: 1980, 1989, 1993, 1994 The Regents of the University of California 2001 David Rufino <daverufino@btinternet.com> 2012 Joey Hess <joey@kitenet.net> License: BSD-3-clause - The full test of the 3 clause BSD license is distributed inside + The full text of the 3 clause BSD license is distributed inside Utility/libmounts.c in this package's source, or in /usr/share/common-licenses/BSD on Debian systems. @@ -35,7 +35,8 @@ Copyright: © 2005-2011 by John Resig, Branden Aaron & Jörn Zaefferer © 2011 The Dojo Foundation License: MIT or GPL-2 The full text of version 2 of the GPL is distributed in - /usr/share/common-licenses/GPL-2 on Debian systems. + /usr/share/common-licenses/GPL-2 on Debian systems. The text of the MIT + license follows: . Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the From 2ba02d260b4a2c4df523079e76fcba8342befa7b Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Fri, 27 Jul 2012 00:40:18 -0400 Subject: [PATCH 130/331] add README --- templates/README | 7 +++++++ 1 file changed, 7 insertions(+) create mode 100644 templates/README diff --git a/templates/README b/templates/README new file mode 100644 index 0000000000..eb0ca037b6 --- /dev/null +++ b/templates/README @@ -0,0 +1,7 @@ +These are template files for the git-annex webapp. They use the +Shakespearean template library, which is documented here: +http://www.yesodweb.com/book/shakespearean-templates + +Note that for most of the templates, it will use files ending in +.hamlet, .julius, and .cassius if they exist. So if you need to add CSS, +or javascript, you can create the missing template files. From d92f5ff44c6c20af50c2363e754a1ecae3df8d6a Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Fri, 27 Jul 2012 01:36:01 -0400 Subject: [PATCH 131/331] add bootstrap --- debian/copyright | 398 +++ static/bootstrap.css | 3990 +++++++++++++++++++++++++ static/glyphicons-halflings-white.png | Bin 0 -> 4352 bytes static/glyphicons-halflings.png | Bin 0 -> 4352 bytes 4 files changed, 4388 insertions(+) create mode 100644 static/bootstrap.css create mode 100644 static/glyphicons-halflings-white.png create mode 100644 static/glyphicons-halflings.png diff --git a/debian/copyright b/debian/copyright index 1b00d07e77..7f906a64aa 100644 --- a/debian/copyright +++ b/debian/copyright @@ -56,3 +56,401 @@ License: MIT or GPL-2 LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. + +Files: static/bootstrap.css +Copyright: 2011-2012 Twitter, Inc. +License: Apache-2.0 + Licensed under the Apache License, Version 2.0 (the "License"); + you may not use this file except in compliance with the License. + You may obtain a copy of the License at + . + http://www.apache.org/licenses/LICENSE-2.0 + . + Unless required by applicable law or agreed to in writing, software + distributed under the License is distributed on an "AS IS" BASIS, + WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. + See the License for the specific language governing permissions and + limitations under the License. + . + The complete text of the Apache License is distributed in + /usr/share/common-licenses/Apache-2.0 on Debian systems. + +Files: static/glyphicons* +Copyright: 2010-2012 Jan Kovarik <glyphicons@gmail.com> +License: CC-BY-3.0 + Creative Commons Attribution 3.0 License + . + THE WORK (AS DEFINED BELOW) IS PROVIDED UNDER THE TERMS + OF THIS CREATIVE COMMONS PUBLIC LICENSE ("CCPL" OR + "LICENSE"). THE WORK IS PROTECTED BY COPYRIGHT AND/OR OTHER + APPLICABLE LAW. ANY USE OF THE WORK OTHER THAN AS + AUTHORIZED UNDER THIS LICENSE OR COPYRIGHT LAW IS + PROHIBITED. + . + BY EXERCISING ANY RIGHTS TO THE WORK PROVIDED HERE, YOU + ACCEPT AND AGREE TO BE BOUND BY THE TERMS OF THIS LICENSE. + TO THE EXTENT THIS LICENSE MAY BE CONSIDERED TO BE A + CONTRACT, THE LICENSOR GRANTS YOU THE RIGHTS CONTAINED HERE + IN CONSIDERATION OF YOUR ACCEPTANCE OF SUCH TERMS AND + CONDITIONS. + . + 1. Definitions + . + a) "Adaptation" means a work based upon + the Work, or upon the Work and other pre-existing works, + such as a translation, adaptation, derivative work, + arrangement of music or other alterations of a literary + or artistic work, or phonogram or performance and + includes cinematographic adaptations or any other form in + which the Work may be recast, transformed, or adapted + including in any form recognizably derived from the + original, except that a work that constitutes a + Collection will not be considered an Adaptation for the + purpose of this License. For the avoidance of doubt, + where the Work is a musical work, performance or + phonogram, the synchronization of the Work in + timed-relation with a moving image ("synching") will be + considered an Adaptation for the purpose of this + License. + . + b) "Collection"</strong> means a collection of + literary or artistic works, such as encyclopedias and + anthologies, or performances, phonograms or broadcasts, + or other works or subject matter other than works listed + in Section 1(f) below, which, by reason of the selection + and arrangement of their contents, constitute + intellectual creations, in which the Work is included in + its entirety in unmodified form along with one or more + other contributions, each constituting separate and + independent works in themselves, which together are + assembled into a collective whole. A work that + constitutes a Collection will not be considered an + Adaptation (as defined above) for the purposes of this + License. + . + c) "Distribute" means to make available + to the public the original and copies of the Work or + Adaptation, as appropriate, through sale or other + transfer of ownership. + . + d) "Licensor" means the individual, + individuals, entity or entities that offer(s) the Work + under the terms of this License. + . + e) "Original Author" means, in the case + of a literary or artistic work, the individual, + individuals, entity or entities who created the Work or + if no individual or entity can be identified, the + publisher; and in addition (i) in the case of a + performance the actors, singers, musicians, dancers, and + other persons who act, sing, deliver, declaim, play in, + interpret or otherwise perform literary or artistic works + or expressions of folklore; (ii) in the case of a + phonogram the producer being the person or legal entity + who first fixes the sounds of a performance or other + sounds; and, (iii) in the case of broadcasts, the + organization that transmits the broadcast. + . + f) "Work" means the literary and/or + artistic work offered under the terms of this License + including without limitation any production in the + literary, scientific and artistic domain, whatever may be + the mode or form of its expression including digital + form, such as a book, pamphlet and other writing; a + lecture, address, sermon or other work of the same + nature; a dramatic or dramatico-musical work; a + choreographic work or entertainment in dumb show; a + musical composition with or without words; a + cinematographic work to which are assimilated works + expressed by a process analogous to cinematography; a + work of drawing, painting, architecture, sculpture, + engraving or lithography; a photographic work to which + are assimilated works expressed by a process analogous to + photography; a work of applied art; an illustration, map, + plan, sketch or three-dimensional work relative to + geography, topography, architecture or science; a + performance; a broadcast; a phonogram; a compilation of + data to the extent it is protected as a copyrightable + work; or a work performed by a variety or circus + performer to the extent it is not otherwise considered a + literary or artistic work. + . + g) "You"</strong> means an individual or entity + exercising rights under this License who has not + previously violated the terms of this License with + respect to the Work, or who has received express + permission from the Licensor to exercise rights under + this License despite a previous violation. + . + h) "Publicly Perform" means to perform + public recitations of the Work and to communicate to the + public those public recitations, by any means or process, + including by wire or wireless means or public digital + performances; to make available to the public Works in + such a way that members of the public may access these + Works from a place and at a place individually chosen by + them; to perform the Work to the public by any means or + process and the communication to the public of the + performances of the Work, including by public digital + performance; to broadcast and rebroadcast the Work by any + means including signs, sounds or images. + . + i) "Reproduce" means to make copies of + the Work by any means including without limitation by + sound or visual recordings and the right of fixation and + reproducing fixations of the Work, including storage of a + protected performance or phonogram in digital form or + other electronic medium. + . + 2. Fair Dealing Rights. Nothing in this + License is intended to reduce, limit, or restrict any uses + free from copyright or rights arising from limitations or + exceptions that are provided for in connection with the + copyright protection under copyright law or other + applicable laws. + . + 3. License Grant. Subject to the terms + and conditions of this License, Licensor hereby grants You + a worldwide, royalty-free, non-exclusive, perpetual (for + the duration of the applicable copyright) license to + exercise the rights in the Work as stated below:</p> + . + a) to Reproduce the Work, to incorporate the Work into + one or more Collections, and to Reproduce the Work as + incorporated in the Collections; + . + b) to create and Reproduce Adaptations provided that any + such Adaptation, including any translation in any medium, + takes reasonable steps to clearly label, demarcate or + otherwise identify that changes were made to the original + Work. For example, a translation could be marked "The + original work was translated from English to Spanish," or + a modification could indicate "The original work has been + modified."; + . + c) to Distribute and Publicly Perform the Work including + as incorporated in Collections; and, + . + d) to Distribute and Publicly Perform Adaptations. + . + e) For the avoidance of doubt: + . + i) Non-waivable Compulsory License + Schemes. In those jurisdictions in which the + right to collect royalties through any statutory or + compulsory licensing scheme cannot be waived, the + Licensor reserves the exclusive right to collect such + royalties for any exercise by You of the rights + granted under this License; + . + ii) Waivable Compulsory License + Schemes. In those jurisdictions in which the + right to collect royalties through any statutory or + compulsory licensing scheme can be waived, the + Licensor waives the exclusive right to collect such + royalties for any exercise by You of the rights + granted under this License; and, + . + iii) Voluntary License Schemes. The + Licensor waives the right to collect royalties, + whether individually or, in the event that the + Licensor is a member of a collecting society that + administers voluntary licensing schemes, via that + society, from any exercise by You of the rights + granted under this License. + . + The above rights may be exercised in all media and + formats whether now known or hereafter devised. The above + rights include the right to make such modifications as are + technically necessary to exercise the rights in other media + and formats. Subject to Section 8(f), all rights not + expressly granted by Licensor are hereby reserved. + . + 4. Restrictions. The license granted in + Section 3 above is expressly made subject to and limited by + the following restrictions: + . + a) You may Distribute or Publicly Perform the Work only + under the terms of this License. You must include a copy + of, or the Uniform Resource Identifier (URI) for, this + License with every copy of the Work You Distribute or + Publicly Perform. You may not offer or impose any terms + on the Work that restrict the terms of this License or + the ability of the recipient of the Work to exercise the + rights granted to that recipient under the terms of the + License. You may not sublicense the Work. You must keep + intact all notices that refer to this License and to the + disclaimer of warranties with every copy of the Work You + Distribute or Publicly Perform. When You Distribute or + Publicly Perform the Work, You may not impose any + effective technological measures on the Work that + restrict the ability of a recipient of the Work from You + to exercise the rights granted to that recipient under + the terms of the License. This Section 4(a) applies to + the Work as incorporated in a Collection, but this does + not require the Collection apart from the Work itself to + be made subject to the terms of this License. If You + create a Collection, upon notice from any Licensor You + must, to the extent practicable, remove from the + Collection any credit as required by Section 4(b), as + requested. If You create an Adaptation, upon notice from + any Licensor You must, to the extent practicable, remove + from the Adaptation any credit as required by Section + 4(b), as requested. + . + b) If You Distribute, or Publicly Perform the Work or + any Adaptations or Collections, You must, unless a + request has been made pursuant to Section 4(a), keep + intact all copyright notices for the Work and provide, + reasonable to the medium or means You are utilizing: (i) + the name of the Original Author (or pseudonym, if + applicable) if supplied, and/or if the Original Author + and/or Licensor designate another party or parties (e.g., + a sponsor institute, publishing entity, journal) for + attribution ("Attribution Parties") in Licensor's + copyright notice, terms of service or by other reasonable + means, the name of such party or parties; (ii) the title + of the Work if supplied; (iii) to the extent reasonably + practicable, the URI, if any, that Licensor specifies to + be associated with the Work, unless such URI does not + refer to the copyright notice or licensing information + for the Work; and (iv) , consistent with Section 3(b), in + the case of an Adaptation, a credit identifying the use + of the Work in the Adaptation (e.g., "French translation + of the Work by Original Author," or "Screenplay based on + original Work by Original Author"). The credit required + by this Section 4 (b) may be implemented in any + reasonable manner; provided, however, that in the case of + a Adaptation or Collection, at a minimum such credit will + appear, if a credit for all contributing authors of the + Adaptation or Collection appears, then as part of these + credits and in a manner at least as prominent as the + credits for the other contributing authors. For the + avoidance of doubt, You may only use the credit required + by this Section for the purpose of attribution in the + manner set out above and, by exercising Your rights under + this License, You may not implicitly or explicitly assert + or imply any connection with, sponsorship or endorsement + by the Original Author, Licensor and/or Attribution + Parties, as appropriate, of You or Your use of the Work, + without the separate, express prior written permission of + the Original Author, Licensor and/or Attribution + Parties. + . + c) Except as otherwise agreed in writing by the Licensor + or as may be otherwise permitted by applicable law, if + You Reproduce, Distribute or Publicly Perform the Work + either by itself or as part of any Adaptations or + Collections, You must not distort, mutilate, modify or + take other derogatory action in relation to the Work + which would be prejudicial to the Original Author's honor + or reputation. Licensor agrees that in those + jurisdictions (e.g. Japan), in which any exercise of the + right granted in Section 3(b) of this License (the right + to make Adaptations) would be deemed to be a distortion, + mutilation, modification or other derogatory action + prejudicial to the Original Author's honor and + reputation, the Licensor will waive or not assert, as + appropriate, this Section, to the fullest extent + permitted by the applicable national law, to enable You + to reasonably exercise Your right under Section 3(b) of + this License (right to make Adaptations) but not + otherwise. + . + 5. Representations, Warranties and + Disclaimer + . + UNLESS OTHERWISE MUTUALLY AGREED TO BY THE PARTIES IN + WRITING, LICENSOR OFFERS THE WORK AS-IS AND MAKES NO + REPRESENTATIONS OR WARRANTIES OF ANY KIND CONCERNING THE + WORK, EXPRESS, IMPLIED, STATUTORY OR OTHERWISE, INCLUDING, + WITHOUT LIMITATION, WARRANTIES OF TITLE, MERCHANTIBILITY, + FITNESS FOR A PARTICULAR PURPOSE, NONINFRINGEMENT, OR THE + ABSENCE OF LATENT OR OTHER DEFECTS, ACCURACY, OR THE + PRESENCE OF ABSENCE OF ERRORS, WHETHER OR NOT DISCOVERABLE. + SOME JURISDICTIONS DO NOT ALLOW THE EXCLUSION OF IMPLIED + WARRANTIES, SO SUCH EXCLUSION MAY NOT APPLY TO YOU. + . + 6. Limitation on Liability. EXCEPT TO + THE EXTENT REQUIRED BY APPLICABLE LAW, IN NO EVENT WILL + LICENSOR BE LIABLE TO YOU ON ANY LEGAL THEORY FOR ANY + SPECIAL, INCIDENTAL, CONSEQUENTIAL, PUNITIVE OR EXEMPLARY + DAMAGES ARISING OUT OF THIS LICENSE OR THE USE OF THE WORK, + EVEN IF LICENSOR HAS BEEN ADVISED OF THE POSSIBILITY OF + SUCH DAMAGES. + . + 7. Termination + . + a) This License and the rights granted hereunder will + terminate automatically upon any breach by You of the + terms of this License. Individuals or entities who have + received Adaptations or Collections from You under this + License, however, will not have their licenses terminated + provided such individuals or entities remain in full + compliance with those licenses. Sections 1, 2, 5, 6, 7, + and 8 will survive any termination of this License.</li> + . + b) Subject to the above terms and conditions, the + license granted here is perpetual (for the duration of + the applicable copyright in the Work). Notwithstanding + the above, Licensor reserves the right to release the + Work under different license terms or to stop + distributing the Work at any time; provided, however that + any such election will not serve to withdraw this License + (or any other license that has been, or is required to + be, granted under the terms of this License), and this + License will continue in full force and effect unless + terminated as stated above. + . + 8. Miscellaneous + . + a) Each time You Distribute or Publicly Perform the Work + or a Collection, the Licensor offers to the recipient a + license to the Work on the same terms and conditions as + the license granted to You under this License. + . + b) Each time You Distribute or Publicly Perform an + Adaptation, Licensor offers to the recipient a license to + the original Work on the same terms and conditions as the + license granted to You under this License. + . + c) If any provision of this License is invalid or + unenforceable under applicable law, it shall not affect + the validity or enforceability of the remainder of the + terms of this License, and without further action by the + parties to this agreement, such provision shall be + reformed to the minimum extent necessary to make such + provision valid and enforceable. + . + d) No term or provision of this License shall be deemed + waived and no breach consented to unless such waiver or + consent shall be in writing and signed by the party to be + charged with such waiver or consent. + . + e) This License constitutes the entire agreement between + the parties with respect to the Work licensed here. There + are no understandings, agreements or representations with + respect to the Work not specified here. Licensor shall + not be bound by any additional provisions that may appear + in any communication from You. This License may not be + modified without the mutual written agreement of the + Licensor and You. + . + f) The rights granted under, and the subject matter + referenced, in this License were drafted utilizing the + terminology of the Berne Convention for the Protection of + Literary and Artistic Works (as amended on September 28, + 1979), the Rome Convention of 1961, the WIPO Copyright + Treaty of 1996, the WIPO Performances and Phonograms + Treaty of 1996 and the Universal Copyright Convention (as + revised on July 24, 1971). These rights and subject + matter take effect in the relevant jurisdiction in which + the License terms are sought to be enforced according to + the corresponding provisions of the implementation of + those treaty provisions in the applicable national law. + If the standard suite of rights granted under applicable + copyright law includes additional rights not granted + under this License, such additional rights are deemed to + be included in the License; this License is not intended + to restrict the license of any rights under applicable + law. diff --git a/static/bootstrap.css b/static/bootstrap.css new file mode 100644 index 0000000000..495188af7f --- /dev/null +++ b/static/bootstrap.css @@ -0,0 +1,3990 @@ +/*! + * Bootstrap v2.0.2 + * + * Copyright 2012 Twitter, Inc + * Licensed under the Apache License v2.0 + * http://www.apache.org/licenses/LICENSE-2.0 + * + * Designed and built with all the love in the world @twitter by @mdo and @fat. + */ +article, +aside, +details, +figcaption, +figure, +footer, +header, +hgroup, +nav, +section { + display: block; +} +audio, +canvas, +video { + display: inline-block; + *display: inline; + *zoom: 1; +} +audio:not([controls]) { + display: none; +} +html { + font-size: 100%; + -webkit-text-size-adjust: 100%; + -ms-text-size-adjust: 100%; +} +a:focus { + outline: thin dotted #333; + outline: 5px auto -webkit-focus-ring-color; + outline-offset: -2px; +} +a:hover, +a:active { + outline: 0; +} +sub, +sup { + position: relative; + font-size: 75%; + line-height: 0; + vertical-align: baseline; +} +sup { + top: -0.5em; +} +sub { + bottom: -0.25em; +} +img { + height: auto; + border: 0; + -ms-interpolation-mode: bicubic; + vertical-align: middle; +} +button, +input, +select, +textarea { + margin: 0; + font-size: 100%; + vertical-align: middle; +} +button, +input { + *overflow: visible; + line-height: normal; +} +button::-moz-focus-inner, +input::-moz-focus-inner { + padding: 0; + border: 0; +} +button, +input[type="button"], +input[type="reset"], +input[type="submit"] { + cursor: pointer; + -webkit-appearance: button; +} +input[type="search"] { + -webkit-appearance: textfield; + -webkit-box-sizing: content-box; + -moz-box-sizing: content-box; + box-sizing: content-box; +} +input[type="search"]::-webkit-search-decoration, +input[type="search"]::-webkit-search-cancel-button { + -webkit-appearance: none; +} +textarea { + overflow: auto; + vertical-align: top; +} +.clearfix { + *zoom: 1; +} +.clearfix:before, +.clearfix:after { + display: table; + content: ""; +} +.clearfix:after { + clear: both; +} +.hide-text { + overflow: hidden; + text-indent: 100%; + white-space: nowrap; +} +.input-block-level { + display: block; + width: 100%; + min-height: 28px; + /* Make inputs at least the height of their button counterpart */ + + /* Makes inputs behave like true block-level elements */ + + -webkit-box-sizing: border-box; + -moz-box-sizing: border-box; + -ms-box-sizing: border-box; + box-sizing: border-box; +} +body { + margin: 0; + font-family: "Helvetica Neue", Helvetica, Arial, sans-serif; + font-size: 13px; + line-height: 18px; + color: #333333; + background-color: #ffffff; +} +a { + color: #0088cc; + text-decoration: none; +} +a:hover { + color: #005580; + text-decoration: underline; +} +.row { + margin-left: -20px; + *zoom: 1; +} +.row:before, +.row:after { + display: table; + content: ""; +} +.row:after { + clear: both; +} +[class*="span"] { + float: left; + margin-left: 20px; +} +.container, +.navbar-fixed-top .container, +.navbar-fixed-bottom .container { + width: 940px; +} +.span12 { + width: 940px; +} +.span11 { + width: 860px; +} +.span10 { + width: 780px; +} +.span9 { + width: 700px; +} +.span8 { + width: 620px; +} +.span7 { + width: 540px; +} +.span6 { + width: 460px; +} +.span5 { + width: 380px; +} +.span4 { + width: 300px; +} +.span3 { + width: 220px; +} +.span2 { + width: 140px; +} +.span1 { + width: 60px; +} +.offset12 { + margin-left: 980px; +} +.offset11 { + margin-left: 900px; +} +.offset10 { + margin-left: 820px; +} +.offset9 { + margin-left: 740px; +} +.offset8 { + margin-left: 660px; +} +.offset7 { + margin-left: 580px; +} +.offset6 { + margin-left: 500px; +} +.offset5 { + margin-left: 420px; +} +.offset4 { + margin-left: 340px; +} +.offset3 { + margin-left: 260px; +} +.offset2 { + margin-left: 180px; +} +.offset1 { + margin-left: 100px; +} +.row-fluid { + width: 100%; + *zoom: 1; +} +.row-fluid:before, +.row-fluid:after { + display: table; + content: ""; +} +.row-fluid:after { + clear: both; +} +.row-fluid > [class*="span"] { + float: left; + margin-left: 2.127659574%; +} +.row-fluid > [class*="span"]:first-child { + margin-left: 0; +} +.row-fluid > .span12 { + width: 99.99999998999999%; +} +.row-fluid > .span11 { + width: 91.489361693%; +} +.row-fluid > .span10 { + width: 82.97872339599999%; +} +.row-fluid > .span9 { + width: 74.468085099%; +} +.row-fluid > .span8 { + width: 65.95744680199999%; +} +.row-fluid > .span7 { + width: 57.446808505%; +} +.row-fluid > .span6 { + width: 48.93617020799999%; +} +.row-fluid > .span5 { + width: 40.425531911%; +} +.row-fluid > .span4 { + width: 31.914893614%; +} +.row-fluid > .span3 { + width: 23.404255317%; +} +.row-fluid > .span2 { + width: 14.89361702%; +} +.row-fluid > .span1 { + width: 6.382978723%; +} +.container { + margin-left: auto; + margin-right: auto; + *zoom: 1; +} +.container:before, +.container:after { + display: table; + content: ""; +} +.container:after { + clear: both; +} +.container-fluid { + padding-left: 20px; + padding-right: 20px; + *zoom: 1; +} +.container-fluid:before, +.container-fluid:after { + display: table; + content: ""; +} +.container-fluid:after { + clear: both; +} +p { + margin: 0 0 9px; + font-family: "Helvetica Neue", Helvetica, Arial, sans-serif; + font-size: 13px; + line-height: 18px; +} +p small { + font-size: 11px; + color: #999999; +} +.lead { + margin-bottom: 18px; + font-size: 20px; + font-weight: 200; + line-height: 27px; +} +h1, +h2, +h3, +h4, +h5, +h6 { + margin: 0; + font-family: inherit; + font-weight: bold; + color: inherit; + text-rendering: optimizelegibility; +} +h1 small, +h2 small, +h3 small, +h4 small, +h5 small, +h6 small { + font-weight: normal; + color: #999999; +} +h1 { + font-size: 30px; + line-height: 36px; +} +h1 small { + font-size: 18px; +} +h2 { + font-size: 24px; + line-height: 36px; +} +h2 small { + font-size: 18px; +} +h3 { + line-height: 27px; + font-size: 18px; +} +h3 small { + font-size: 14px; +} +h4, +h5, +h6 { + line-height: 18px; +} +h4 { + font-size: 14px; +} +h4 small { + font-size: 12px; +} +h5 { + font-size: 12px; +} +h6 { + font-size: 11px; + color: #999999; + text-transform: uppercase; +} +.page-header { + padding-bottom: 17px; + margin: 18px 0; + border-bottom: 1px solid #eeeeee; +} +.page-header h1 { + line-height: 1; +} +ul, +ol { + padding: 0; + margin: 0 0 9px 25px; +} +ul ul, +ul ol, +ol ol, +ol ul { + margin-bottom: 0; +} +ul { + list-style: disc; +} +ol { + list-style: decimal; +} +li { + line-height: 18px; +} +ul.unstyled, +ol.unstyled { + margin-left: 0; + list-style: none; +} +dl { + margin-bottom: 18px; +} +dt, +dd { + line-height: 18px; +} +dt { + font-weight: bold; + line-height: 17px; +} +dd { + margin-left: 9px; +} +.dl-horizontal dt { + float: left; + clear: left; + width: 120px; + text-align: right; +} +.dl-horizontal dd { + margin-left: 130px; +} +hr { + margin: 18px 0; + border: 0; + border-top: 1px solid #eeeeee; + border-bottom: 1px solid #ffffff; +} +strong { + font-weight: bold; +} +em { + font-style: italic; +} +.muted { + color: #999999; +} +abbr[title] { + border-bottom: 1px dotted #ddd; + cursor: help; +} +abbr.initialism { + font-size: 90%; + text-transform: uppercase; +} +blockquote { + padding: 0 0 0 15px; + margin: 0 0 18px; + border-left: 5px solid #eeeeee; +} +blockquote p { + margin-bottom: 0; + font-size: 16px; + font-weight: 300; + line-height: 22.5px; +} +blockquote small { + display: block; + line-height: 18px; + color: #999999; +} +blockquote small:before { + content: '\2014 \00A0'; +} +blockquote.pull-right { + float: right; + padding-left: 0; + padding-right: 15px; + border-left: 0; + border-right: 5px solid #eeeeee; +} +blockquote.pull-right p, +blockquote.pull-right small { + text-align: right; +} +q:before, +q:after, +blockquote:before, +blockquote:after { + content: ""; +} +address { + display: block; + margin-bottom: 18px; + line-height: 18px; + font-style: normal; +} +small { + font-size: 100%; +} +cite { + font-style: normal; +} +code, +pre { + padding: 0 3px 2px; + font-family: Menlo, Monaco, "Courier New", monospace; + font-size: 12px; + color: #333333; + -webkit-border-radius: 3px; + -moz-border-radius: 3px; + border-radius: 3px; +} +code { + padding: 2px 4px; + color: #d14; + background-color: #f7f7f9; + border: 1px solid #e1e1e8; +} +pre { + display: block; + padding: 8.5px; + margin: 0 0 9px; + font-size: 12.025px; + line-height: 18px; + background-color: #f5f5f5; + border: 1px solid #ccc; + border: 1px solid rgba(0, 0, 0, 0.15); + -webkit-border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; + white-space: pre; + white-space: pre-wrap; + word-break: break-all; + word-wrap: break-word; +} +pre.prettyprint { + margin-bottom: 18px; +} +pre code { + padding: 0; + color: inherit; + background-color: transparent; + border: 0; +} +.pre-scrollable { + max-height: 340px; + overflow-y: scroll; +} +form { + margin: 0 0 18px; +} +fieldset { + padding: 0; + margin: 0; + border: 0; +} +legend { + display: block; + width: 100%; + padding: 0; + margin-bottom: 27px; + font-size: 19.5px; + line-height: 36px; + color: #333333; + border: 0; + border-bottom: 1px solid #eee; +} +legend small { + font-size: 13.5px; + color: #999999; +} +label, +input, +button, +select, +textarea { + font-size: 13px; + font-weight: normal; + line-height: 18px; +} +input, +button, +select, +textarea { + font-family: "Helvetica Neue", Helvetica, Arial, sans-serif; +} +label { + display: block; + margin-bottom: 5px; + color: #333333; +} +input, +textarea, +select, +.uneditable-input { + display: inline-block; + width: 210px; + height: 18px; + padding: 4px; + margin-bottom: 9px; + font-size: 13px; + line-height: 18px; + color: #555555; + border: 1px solid #cccccc; + -webkit-border-radius: 3px; + -moz-border-radius: 3px; + border-radius: 3px; +} +.uneditable-textarea { + width: auto; + height: auto; +} +label input, +label textarea, +label select { + display: block; +} +input[type="image"], +input[type="checkbox"], +input[type="radio"] { + width: auto; + height: auto; + padding: 0; + margin: 3px 0; + *margin-top: 0; + /* IE7 */ + + line-height: normal; + cursor: pointer; + -webkit-border-radius: 0; + -moz-border-radius: 0; + border-radius: 0; + border: 0 \9; + /* IE9 and down */ + +} +input[type="image"] { + border: 0; +} +input[type="file"] { + width: auto; + padding: initial; + line-height: initial; + border: initial; + background-color: #ffffff; + background-color: initial; + -webkit-box-shadow: none; + -moz-box-shadow: none; + box-shadow: none; +} +input[type="button"], +input[type="reset"], +input[type="submit"] { + width: auto; + height: auto; +} +select, +input[type="file"] { + height: 28px; + /* In IE7, the height of the select element cannot be changed by height, only font-size */ + + *margin-top: 4px; + /* For IE7, add top margin to align select with labels */ + + line-height: 28px; +} +input[type="file"] { + line-height: 18px \9; +} +select { + width: 220px; + background-color: #ffffff; +} +select[multiple], +select[size] { + height: auto; +} +input[type="image"] { + -webkit-box-shadow: none; + -moz-box-shadow: none; + box-shadow: none; +} +textarea { + height: auto; +} +input[type="hidden"] { + display: none; +} +.radio, +.checkbox { + padding-left: 18px; +} +.radio input[type="radio"], +.checkbox input[type="checkbox"] { + float: left; + margin-left: -18px; +} +.controls > .radio:first-child, +.controls > .checkbox:first-child { + padding-top: 5px; +} +.radio.inline, +.checkbox.inline { + display: inline-block; + padding-top: 5px; + margin-bottom: 0; + vertical-align: middle; +} +.radio.inline + .radio.inline, +.checkbox.inline + .checkbox.inline { + margin-left: 10px; +} +input, +textarea { + -webkit-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075); + -moz-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075); + box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075); + -webkit-transition: border linear 0.2s, box-shadow linear 0.2s; + -moz-transition: border linear 0.2s, box-shadow linear 0.2s; + -ms-transition: border linear 0.2s, box-shadow linear 0.2s; + -o-transition: border linear 0.2s, box-shadow linear 0.2s; + transition: border linear 0.2s, box-shadow linear 0.2s; +} +input:focus, +textarea:focus { + border-color: rgba(82, 168, 236, 0.8); + -webkit-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 0 0 8px rgba(82, 168, 236, 0.6); + -moz-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 0 0 8px rgba(82, 168, 236, 0.6); + box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 0 0 8px rgba(82, 168, 236, 0.6); + outline: 0; + outline: thin dotted \9; + /* IE6-9 */ + +} +input[type="file"]:focus, +input[type="radio"]:focus, +input[type="checkbox"]:focus, +select:focus { + -webkit-box-shadow: none; + -moz-box-shadow: none; + box-shadow: none; + outline: thin dotted #333; + outline: 5px auto -webkit-focus-ring-color; + outline-offset: -2px; +} +.input-mini { + width: 60px; +} +.input-small { + width: 90px; +} +.input-medium { + width: 150px; +} +.input-large { + width: 210px; +} +.input-xlarge { + width: 270px; +} +.input-xxlarge { + width: 530px; +} +input[class*="span"], +select[class*="span"], +textarea[class*="span"], +.uneditable-input { + float: none; + margin-left: 0; +} +input, +textarea, +.uneditable-input { + margin-left: 0; +} +input.span12, textarea.span12, .uneditable-input.span12 { + width: 930px; +} +input.span11, textarea.span11, .uneditable-input.span11 { + width: 850px; +} +input.span10, textarea.span10, .uneditable-input.span10 { + width: 770px; +} +input.span9, textarea.span9, .uneditable-input.span9 { + width: 690px; +} +input.span8, textarea.span8, .uneditable-input.span8 { + width: 610px; +} +input.span7, textarea.span7, .uneditable-input.span7 { + width: 530px; +} +input.span6, textarea.span6, .uneditable-input.span6 { + width: 450px; +} +input.span5, textarea.span5, .uneditable-input.span5 { + width: 370px; +} +input.span4, textarea.span4, .uneditable-input.span4 { + width: 290px; +} +input.span3, textarea.span3, .uneditable-input.span3 { + width: 210px; +} +input.span2, textarea.span2, .uneditable-input.span2 { + width: 130px; +} +input.span1, textarea.span1, .uneditable-input.span1 { + width: 50px; +} +input[disabled], +select[disabled], +textarea[disabled], +input[readonly], +select[readonly], +textarea[readonly] { + background-color: #eeeeee; + border-color: #ddd; + cursor: not-allowed; +} +.control-group.warning > label, +.control-group.warning .help-block, +.control-group.warning .help-inline { + color: #c09853; +} +.control-group.warning input, +.control-group.warning select, +.control-group.warning textarea { + color: #c09853; + border-color: #c09853; +} +.control-group.warning input:focus, +.control-group.warning select:focus, +.control-group.warning textarea:focus { + border-color: #a47e3c; + -webkit-box-shadow: 0 0 6px #dbc59e; + -moz-box-shadow: 0 0 6px #dbc59e; + box-shadow: 0 0 6px #dbc59e; +} +.control-group.warning .input-prepend .add-on, +.control-group.warning .input-append .add-on { + color: #c09853; + background-color: #fcf8e3; + border-color: #c09853; +} +.control-group.error > label, +.control-group.error .help-block, +.control-group.error .help-inline { + color: #b94a48; +} +.control-group.error input, +.control-group.error select, +.control-group.error textarea { + color: #b94a48; + border-color: #b94a48; +} +.control-group.error input:focus, +.control-group.error select:focus, +.control-group.error textarea:focus { + border-color: #953b39; + -webkit-box-shadow: 0 0 6px #d59392; + -moz-box-shadow: 0 0 6px #d59392; + box-shadow: 0 0 6px #d59392; +} +.control-group.error .input-prepend .add-on, +.control-group.error .input-append .add-on { + color: #b94a48; + background-color: #f2dede; + border-color: #b94a48; +} +.control-group.success > label, +.control-group.success .help-block, +.control-group.success .help-inline { + color: #468847; +} +.control-group.success input, +.control-group.success select, +.control-group.success textarea { + color: #468847; + border-color: #468847; +} +.control-group.success input:focus, +.control-group.success select:focus, +.control-group.success textarea:focus { + border-color: #356635; + -webkit-box-shadow: 0 0 6px #7aba7b; + -moz-box-shadow: 0 0 6px #7aba7b; + box-shadow: 0 0 6px #7aba7b; +} +.control-group.success .input-prepend .add-on, +.control-group.success .input-append .add-on { + color: #468847; + background-color: #dff0d8; + border-color: #468847; +} +input:focus:required:invalid, +textarea:focus:required:invalid, +select:focus:required:invalid { + color: #b94a48; + border-color: #ee5f5b; +} +input:focus:required:invalid:focus, +textarea:focus:required:invalid:focus, +select:focus:required:invalid:focus { + border-color: #e9322d; + -webkit-box-shadow: 0 0 6px #f8b9b7; + -moz-box-shadow: 0 0 6px #f8b9b7; + box-shadow: 0 0 6px #f8b9b7; +} +.form-actions { + padding: 17px 20px 18px; + margin-top: 18px; + margin-bottom: 18px; + background-color: #eeeeee; + border-top: 1px solid #ddd; + *zoom: 1; +} +.form-actions:before, +.form-actions:after { + display: table; + content: ""; +} +.form-actions:after { + clear: both; +} +.uneditable-input { + display: block; + background-color: #ffffff; + border-color: #eee; + -webkit-box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.025); + -moz-box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.025); + box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.025); + cursor: not-allowed; +} +:-moz-placeholder { + color: #999999; +} +::-webkit-input-placeholder { + color: #999999; +} +.help-block, +.help-inline { + color: #555555; +} +.help-block { + display: block; + margin-bottom: 9px; +} +.help-inline { + display: inline-block; + *display: inline; + /* IE7 inline-block hack */ + + *zoom: 1; + vertical-align: middle; + padding-left: 5px; +} +.input-prepend, +.input-append { + margin-bottom: 5px; +} +.input-prepend input, +.input-append input, +.input-prepend select, +.input-append select, +.input-prepend .uneditable-input, +.input-append .uneditable-input { + *margin-left: 0; + -webkit-border-radius: 0 3px 3px 0; + -moz-border-radius: 0 3px 3px 0; + border-radius: 0 3px 3px 0; +} +.input-prepend input:focus, +.input-append input:focus, +.input-prepend select:focus, +.input-append select:focus, +.input-prepend .uneditable-input:focus, +.input-append .uneditable-input:focus { + position: relative; + z-index: 2; +} +.input-prepend .uneditable-input, +.input-append .uneditable-input { + border-left-color: #ccc; +} +.input-prepend .add-on, +.input-append .add-on { + display: inline-block; + width: auto; + min-width: 16px; + height: 18px; + padding: 4px 5px; + font-weight: normal; + line-height: 18px; + text-align: center; + text-shadow: 0 1px 0 #ffffff; + vertical-align: middle; + background-color: #eeeeee; + border: 1px solid #ccc; +} +.input-prepend .add-on, +.input-append .add-on, +.input-prepend .btn, +.input-append .btn { + -webkit-border-radius: 3px 0 0 3px; + -moz-border-radius: 3px 0 0 3px; + border-radius: 3px 0 0 3px; +} +.input-prepend .active, +.input-append .active { + background-color: #a9dba9; + border-color: #46a546; +} +.input-prepend .add-on, +.input-prepend .btn { + margin-right: -1px; +} +.input-append input, +.input-append select .uneditable-input { + -webkit-border-radius: 3px 0 0 3px; + -moz-border-radius: 3px 0 0 3px; + border-radius: 3px 0 0 3px; +} +.input-append .uneditable-input { + border-left-color: #eee; + border-right-color: #ccc; +} +.input-append .add-on, +.input-append .btn { + margin-left: -1px; + -webkit-border-radius: 0 3px 3px 0; + -moz-border-radius: 0 3px 3px 0; + border-radius: 0 3px 3px 0; +} +.input-prepend.input-append input, +.input-prepend.input-append select, +.input-prepend.input-append .uneditable-input { + -webkit-border-radius: 0; + -moz-border-radius: 0; + border-radius: 0; +} +.input-prepend.input-append .add-on:first-child, +.input-prepend.input-append .btn:first-child { + margin-right: -1px; + -webkit-border-radius: 3px 0 0 3px; + -moz-border-radius: 3px 0 0 3px; + border-radius: 3px 0 0 3px; +} +.input-prepend.input-append .add-on:last-child, +.input-prepend.input-append .btn:last-child { + margin-left: -1px; + -webkit-border-radius: 0 3px 3px 0; + -moz-border-radius: 0 3px 3px 0; + border-radius: 0 3px 3px 0; +} +.search-query { + padding-left: 14px; + padding-right: 14px; + margin-bottom: 0; + -webkit-border-radius: 14px; + -moz-border-radius: 14px; + border-radius: 14px; +} +.form-search input, +.form-inline input, +.form-horizontal input, +.form-search textarea, +.form-inline textarea, +.form-horizontal textarea, +.form-search select, +.form-inline select, +.form-horizontal select, +.form-search .help-inline, +.form-inline .help-inline, +.form-horizontal .help-inline, +.form-search .uneditable-input, +.form-inline .uneditable-input, +.form-horizontal .uneditable-input, +.form-search .input-prepend, +.form-inline .input-prepend, +.form-horizontal .input-prepend, +.form-search .input-append, +.form-inline .input-append, +.form-horizontal .input-append { + display: inline-block; + margin-bottom: 0; +} +.form-search .hide, +.form-inline .hide, +.form-horizontal .hide { + display: none; +} +.form-search label, +.form-inline label { + display: inline-block; +} +.form-search .input-append, +.form-inline .input-append, +.form-search .input-prepend, +.form-inline .input-prepend { + margin-bottom: 0; +} +.form-search .radio, +.form-search .checkbox, +.form-inline .radio, +.form-inline .checkbox { + padding-left: 0; + margin-bottom: 0; + vertical-align: middle; +} +.form-search .radio input[type="radio"], +.form-search .checkbox input[type="checkbox"], +.form-inline .radio input[type="radio"], +.form-inline .checkbox input[type="checkbox"] { + float: left; + margin-left: 0; + margin-right: 3px; +} +.control-group { + margin-bottom: 9px; +} +legend + .control-group { + margin-top: 18px; + -webkit-margin-top-collapse: separate; +} +.form-horizontal .control-group { + margin-bottom: 18px; + *zoom: 1; +} +.form-horizontal .control-group:before, +.form-horizontal .control-group:after { + display: table; + content: ""; +} +.form-horizontal .control-group:after { + clear: both; +} +.form-horizontal .control-label { + float: left; + width: 140px; + padding-top: 5px; + text-align: right; +} +.form-horizontal .controls { + margin-left: 160px; + /* Super jank IE7 fix to ensure the inputs in .input-append and input-prepend don't inherit the margin of the parent, in this case .controls */ + + *display: inline-block; + *margin-left: 0; + *padding-left: 20px; +} +.form-horizontal .help-block { + margin-top: 9px; + margin-bottom: 0; +} +.form-horizontal .form-actions { + padding-left: 160px; +} +table { + max-width: 100%; + border-collapse: collapse; + border-spacing: 0; + background-color: transparent; +} +.table { + width: 100%; + margin-bottom: 18px; +} +.table th, +.table td { + padding: 8px; + line-height: 18px; + text-align: left; + vertical-align: top; + border-top: 1px solid #dddddd; +} +.table th { + font-weight: bold; +} +.table thead th { + vertical-align: bottom; +} +.table colgroup + thead tr:first-child th, +.table colgroup + thead tr:first-child td, +.table thead:first-child tr:first-child th, +.table thead:first-child tr:first-child td { + border-top: 0; +} +.table tbody + tbody { + border-top: 2px solid #dddddd; +} +.table-condensed th, +.table-condensed td { + padding: 4px 5px; +} +.table-bordered { + border: 1px solid #dddddd; + border-left: 0; + border-collapse: separate; + *border-collapse: collapsed; + -webkit-border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; +} +.table-bordered th, +.table-bordered td { + border-left: 1px solid #dddddd; +} +.table-bordered thead:first-child tr:first-child th, +.table-bordered tbody:first-child tr:first-child th, +.table-bordered tbody:first-child tr:first-child td { + border-top: 0; +} +.table-bordered thead:first-child tr:first-child th:first-child, +.table-bordered tbody:first-child tr:first-child td:first-child { + -webkit-border-radius: 4px 0 0 0; + -moz-border-radius: 4px 0 0 0; + border-radius: 4px 0 0 0; +} +.table-bordered thead:first-child tr:first-child th:last-child, +.table-bordered tbody:first-child tr:first-child td:last-child { + -webkit-border-radius: 0 4px 0 0; + -moz-border-radius: 0 4px 0 0; + border-radius: 0 4px 0 0; +} +.table-bordered thead:last-child tr:last-child th:first-child, +.table-bordered tbody:last-child tr:last-child td:first-child { + -webkit-border-radius: 0 0 0 4px; + -moz-border-radius: 0 0 0 4px; + border-radius: 0 0 0 4px; +} +.table-bordered thead:last-child tr:last-child th:last-child, +.table-bordered tbody:last-child tr:last-child td:last-child { + -webkit-border-radius: 0 0 4px 0; + -moz-border-radius: 0 0 4px 0; + border-radius: 0 0 4px 0; +} +.table-striped tbody tr:nth-child(odd) td, +.table-striped tbody tr:nth-child(odd) th { + background-color: #f9f9f9; +} +.table tbody tr:hover td, +.table tbody tr:hover th { + background-color: #f5f5f5; +} +table .span1 { + float: none; + width: 44px; + margin-left: 0; +} +table .span2 { + float: none; + width: 124px; + margin-left: 0; +} +table .span3 { + float: none; + width: 204px; + margin-left: 0; +} +table .span4 { + float: none; + width: 284px; + margin-left: 0; +} +table .span5 { + float: none; + width: 364px; + margin-left: 0; +} +table .span6 { + float: none; + width: 444px; + margin-left: 0; +} +table .span7 { + float: none; + width: 524px; + margin-left: 0; +} +table .span8 { + float: none; + width: 604px; + margin-left: 0; +} +table .span9 { + float: none; + width: 684px; + margin-left: 0; +} +table .span10 { + float: none; + width: 764px; + margin-left: 0; +} +table .span11 { + float: none; + width: 844px; + margin-left: 0; +} +table .span12 { + float: none; + width: 924px; + margin-left: 0; +} +table .span13 { + float: none; + width: 1004px; + margin-left: 0; +} +table .span14 { + float: none; + width: 1084px; + margin-left: 0; +} +table .span15 { + float: none; + width: 1164px; + margin-left: 0; +} +table .span16 { + float: none; + width: 1244px; + margin-left: 0; +} +table .span17 { + float: none; + width: 1324px; + margin-left: 0; +} +table .span18 { + float: none; + width: 1404px; + margin-left: 0; +} +table .span19 { + float: none; + width: 1484px; + margin-left: 0; +} +table .span20 { + float: none; + width: 1564px; + margin-left: 0; +} +table .span21 { + float: none; + width: 1644px; + margin-left: 0; +} +table .span22 { + float: none; + width: 1724px; + margin-left: 0; +} +table .span23 { + float: none; + width: 1804px; + margin-left: 0; +} +table .span24 { + float: none; + width: 1884px; + margin-left: 0; +} +[class^="icon-"], +[class*=" icon-"] { + display: inline-block; + width: 14px; + height: 14px; + line-height: 14px; + vertical-align: text-top; + background-image: url("../img/glyphicons-halflings.png"); + background-position: 14px 14px; + background-repeat: no-repeat; + *margin-right: .3em; +} +[class^="icon-"]:last-child, +[class*=" icon-"]:last-child { + *margin-left: 0; +} +.icon-white { + background-image: url("../img/glyphicons-halflings-white.png"); +} +.icon-glass { + background-position: 0 0; +} +.icon-music { + background-position: -24px 0; +} +.icon-search { + background-position: -48px 0; +} +.icon-envelope { + background-position: -72px 0; +} +.icon-heart { + background-position: -96px 0; +} +.icon-star { + background-position: -120px 0; +} +.icon-star-empty { + background-position: -144px 0; +} +.icon-user { + background-position: -168px 0; +} +.icon-film { + background-position: -192px 0; +} +.icon-th-large { + background-position: -216px 0; +} +.icon-th { + background-position: -240px 0; +} +.icon-th-list { + background-position: -264px 0; +} +.icon-ok { + background-position: -288px 0; +} +.icon-remove { + background-position: -312px 0; +} +.icon-zoom-in { + background-position: -336px 0; +} +.icon-zoom-out { + background-position: -360px 0; +} +.icon-off { + background-position: -384px 0; +} +.icon-signal { + background-position: -408px 0; +} +.icon-cog { + background-position: -432px 0; +} +.icon-trash { + background-position: -456px 0; +} +.icon-home { + background-position: 0 -24px; +} +.icon-file { + background-position: -24px -24px; +} +.icon-time { + background-position: -48px -24px; +} +.icon-road { + background-position: -72px -24px; +} +.icon-download-alt { + background-position: -96px -24px; +} +.icon-download { + background-position: -120px -24px; +} +.icon-upload { + background-position: -144px -24px; +} +.icon-inbox { + background-position: -168px -24px; +} +.icon-play-circle { + background-position: -192px -24px; +} +.icon-repeat { + background-position: -216px -24px; +} +.icon-refresh { + background-position: -240px -24px; +} +.icon-list-alt { + background-position: -264px -24px; +} +.icon-lock { + background-position: -287px -24px; +} +.icon-flag { + background-position: -312px -24px; +} +.icon-headphones { + background-position: -336px -24px; +} +.icon-volume-off { + background-position: -360px -24px; +} +.icon-volume-down { + background-position: -384px -24px; +} +.icon-volume-up { + background-position: -408px -24px; +} +.icon-qrcode { + background-position: -432px -24px; +} +.icon-barcode { + background-position: -456px -24px; +} +.icon-tag { + background-position: 0 -48px; +} +.icon-tags { + background-position: -25px -48px; +} +.icon-book { + background-position: -48px -48px; +} +.icon-bookmark { + background-position: -72px -48px; +} +.icon-print { + background-position: -96px -48px; +} +.icon-camera { + background-position: -120px -48px; +} +.icon-font { + background-position: -144px -48px; +} +.icon-bold { + background-position: -167px -48px; +} +.icon-italic { + background-position: -192px -48px; +} +.icon-text-height { + background-position: -216px -48px; +} +.icon-text-width { + background-position: -240px -48px; +} +.icon-align-left { + background-position: -264px -48px; +} +.icon-align-center { + background-position: -288px -48px; +} +.icon-align-right { + background-position: -312px -48px; +} +.icon-align-justify { + background-position: -336px -48px; +} +.icon-list { + background-position: -360px -48px; +} +.icon-indent-left { + background-position: -384px -48px; +} +.icon-indent-right { + background-position: -408px -48px; +} +.icon-facetime-video { + background-position: -432px -48px; +} +.icon-picture { + background-position: -456px -48px; +} +.icon-pencil { + background-position: 0 -72px; +} +.icon-map-marker { + background-position: -24px -72px; +} +.icon-adjust { + background-position: -48px -72px; +} +.icon-tint { + background-position: -72px -72px; +} +.icon-edit { + background-position: -96px -72px; +} +.icon-share { + background-position: -120px -72px; +} +.icon-check { + background-position: -144px -72px; +} +.icon-move { + background-position: -168px -72px; +} +.icon-step-backward { + background-position: -192px -72px; +} +.icon-fast-backward { + background-position: -216px -72px; +} +.icon-backward { + background-position: -240px -72px; +} +.icon-play { + background-position: -264px -72px; +} +.icon-pause { + background-position: -288px -72px; +} +.icon-stop { + background-position: -312px -72px; +} +.icon-forward { + background-position: -336px -72px; +} +.icon-fast-forward { + background-position: -360px -72px; +} +.icon-step-forward { + background-position: -384px -72px; +} +.icon-eject { + background-position: -408px -72px; +} +.icon-chevron-left { + background-position: -432px -72px; +} +.icon-chevron-right { + background-position: -456px -72px; +} +.icon-plus-sign { + background-position: 0 -96px; +} +.icon-minus-sign { + background-position: -24px -96px; +} +.icon-remove-sign { + background-position: -48px -96px; +} +.icon-ok-sign { + background-position: -72px -96px; +} +.icon-question-sign { + background-position: -96px -96px; +} +.icon-info-sign { + background-position: -120px -96px; +} +.icon-screenshot { + background-position: -144px -96px; +} +.icon-remove-circle { + background-position: -168px -96px; +} +.icon-ok-circle { + background-position: -192px -96px; +} +.icon-ban-circle { + background-position: -216px -96px; +} +.icon-arrow-left { + background-position: -240px -96px; +} +.icon-arrow-right { + background-position: -264px -96px; +} +.icon-arrow-up { + background-position: -289px -96px; +} +.icon-arrow-down { + background-position: -312px -96px; +} +.icon-share-alt { + background-position: -336px -96px; +} +.icon-resize-full { + background-position: -360px -96px; +} +.icon-resize-small { + background-position: -384px -96px; +} +.icon-plus { + background-position: -408px -96px; +} +.icon-minus { + background-position: -433px -96px; +} +.icon-asterisk { + background-position: -456px -96px; +} +.icon-exclamation-sign { + background-position: 0 -120px; +} +.icon-gift { + background-position: -24px -120px; +} +.icon-leaf { + background-position: -48px -120px; +} +.icon-fire { + background-position: -72px -120px; +} +.icon-eye-open { + background-position: -96px -120px; +} +.icon-eye-close { + background-position: -120px -120px; +} +.icon-warning-sign { + background-position: -144px -120px; +} +.icon-plane { + background-position: -168px -120px; +} +.icon-calendar { + background-position: -192px -120px; +} +.icon-random { + background-position: -216px -120px; +} +.icon-comment { + background-position: -240px -120px; +} +.icon-magnet { + background-position: -264px -120px; +} +.icon-chevron-up { + background-position: -288px -120px; +} +.icon-chevron-down { + background-position: -313px -119px; +} +.icon-retweet { + background-position: -336px -120px; +} +.icon-shopping-cart { + background-position: -360px -120px; +} +.icon-folder-close { + background-position: -384px -120px; +} +.icon-folder-open { + background-position: -408px -120px; +} +.icon-resize-vertical { + background-position: -432px -119px; +} +.icon-resize-horizontal { + background-position: -456px -118px; +} +.dropdown { + position: relative; +} +.dropdown-toggle { + *margin-bottom: -3px; +} +.dropdown-toggle:active, +.open .dropdown-toggle { + outline: 0; +} +.caret { + display: inline-block; + width: 0; + height: 0; + vertical-align: top; + border-left: 4px solid transparent; + border-right: 4px solid transparent; + border-top: 4px solid #000000; + opacity: 0.3; + filter: alpha(opacity=30); + content: ""; +} +.dropdown .caret { + margin-top: 8px; + margin-left: 2px; +} +.dropdown:hover .caret, +.open.dropdown .caret { + opacity: 1; + filter: alpha(opacity=100); +} +.dropdown-menu { + position: absolute; + top: 100%; + left: 0; + z-index: 1000; + float: left; + display: none; + min-width: 160px; + padding: 4px 0; + margin: 0; + list-style: none; + background-color: #ffffff; + border-color: #ccc; + border-color: rgba(0, 0, 0, 0.2); + border-style: solid; + border-width: 1px; + -webkit-border-radius: 0 0 5px 5px; + -moz-border-radius: 0 0 5px 5px; + border-radius: 0 0 5px 5px; + -webkit-box-shadow: 0 5px 10px rgba(0, 0, 0, 0.2); + -moz-box-shadow: 0 5px 10px rgba(0, 0, 0, 0.2); + box-shadow: 0 5px 10px rgba(0, 0, 0, 0.2); + -webkit-background-clip: padding-box; + -moz-background-clip: padding; + background-clip: padding-box; + *border-right-width: 2px; + *border-bottom-width: 2px; +} +.dropdown-menu.pull-right { + right: 0; + left: auto; +} +.dropdown-menu .divider { + height: 1px; + margin: 8px 1px; + overflow: hidden; + background-color: #e5e5e5; + border-bottom: 1px solid #ffffff; + *width: 100%; + *margin: -5px 0 5px; +} +.dropdown-menu a { + display: block; + padding: 3px 15px; + clear: both; + font-weight: normal; + line-height: 18px; + color: #333333; + white-space: nowrap; +} +.dropdown-menu li > a:hover, +.dropdown-menu .active > a, +.dropdown-menu .active > a:hover { + color: #ffffff; + text-decoration: none; + background-color: #0088cc; +} +.dropdown.open { + *z-index: 1000; +} +.dropdown.open .dropdown-toggle { + color: #ffffff; + background: #ccc; + background: rgba(0, 0, 0, 0.3); +} +.dropdown.open .dropdown-menu { + display: block; +} +.pull-right .dropdown-menu { + left: auto; + right: 0; +} +.dropup .caret, +.navbar-fixed-bottom .dropdown .caret { + border-top: 0; + border-bottom: 4px solid #000000; + content: "\2191"; +} +.dropup .dropdown-menu, +.navbar-fixed-bottom .dropdown .dropdown-menu { + top: auto; + bottom: 100%; + margin-bottom: 1px; +} +.typeahead { + margin-top: 2px; + -webkit-border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; +} +.well { + min-height: 20px; + padding: 19px; + margin-bottom: 20px; + background-color: #f5f5f5; + border: 1px solid #eee; + border: 1px solid rgba(0, 0, 0, 0.05); + -webkit-border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; + -webkit-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.05); + -moz-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.05); + box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.05); +} +.well blockquote { + border-color: #ddd; + border-color: rgba(0, 0, 0, 0.15); +} +.well-large { + padding: 24px; + -webkit-border-radius: 6px; + -moz-border-radius: 6px; + border-radius: 6px; +} +.well-small { + padding: 9px; + -webkit-border-radius: 3px; + -moz-border-radius: 3px; + border-radius: 3px; +} +.fade { + -webkit-transition: opacity 0.15s linear; + -moz-transition: opacity 0.15s linear; + -ms-transition: opacity 0.15s linear; + -o-transition: opacity 0.15s linear; + transition: opacity 0.15s linear; + opacity: 0; +} +.fade.in { + opacity: 1; +} +.collapse { + -webkit-transition: height 0.35s ease; + -moz-transition: height 0.35s ease; + -ms-transition: height 0.35s ease; + -o-transition: height 0.35s ease; + transition: height 0.35s ease; + position: relative; + overflow: hidden; + height: 0; +} +.collapse.in { + height: auto; +} +.close { + float: right; + font-size: 20px; + font-weight: bold; + line-height: 18px; + color: #000000; + text-shadow: 0 1px 0 #ffffff; + opacity: 0.2; + filter: alpha(opacity=20); +} +.close:hover { + color: #000000; + text-decoration: none; + opacity: 0.4; + filter: alpha(opacity=40); + cursor: pointer; +} +.btn { + display: inline-block; + *display: inline; + /* IE7 inline-block hack */ + + *zoom: 1; + padding: 4px 10px 4px; + margin-bottom: 0; + font-size: 13px; + line-height: 18px; + color: #333333; + text-align: center; + text-shadow: 0 1px 1px rgba(255, 255, 255, 0.75); + vertical-align: middle; + background-color: #f5f5f5; + background-image: -moz-linear-gradient(top, #ffffff, #e6e6e6); + background-image: -ms-linear-gradient(top, #ffffff, #e6e6e6); + background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#ffffff), to(#e6e6e6)); + background-image: -webkit-linear-gradient(top, #ffffff, #e6e6e6); + background-image: -o-linear-gradient(top, #ffffff, #e6e6e6); + background-image: linear-gradient(top, #ffffff, #e6e6e6); + background-repeat: repeat-x; + filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#ffffff', endColorstr='#e6e6e6', GradientType=0); + border-color: #e6e6e6 #e6e6e6 #bfbfbf; + border-color: rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.25); + filter: progid:dximagetransform.microsoft.gradient(enabled=false); + border: 1px solid #cccccc; + border-bottom-color: #b3b3b3; + -webkit-border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; + -webkit-box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.2), 0 1px 2px rgba(0, 0, 0, 0.05); + -moz-box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.2), 0 1px 2px rgba(0, 0, 0, 0.05); + box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.2), 0 1px 2px rgba(0, 0, 0, 0.05); + cursor: pointer; + *margin-left: .3em; +} +.btn:hover, +.btn:active, +.btn.active, +.btn.disabled, +.btn[disabled] { + background-color: #e6e6e6; +} +.btn:active, +.btn.active { + background-color: #cccccc \9; +} +.btn:first-child { + *margin-left: 0; +} +.btn:hover { + color: #333333; + text-decoration: none; + background-color: #e6e6e6; + background-position: 0 -15px; + -webkit-transition: background-position 0.1s linear; + -moz-transition: background-position 0.1s linear; + -ms-transition: background-position 0.1s linear; + -o-transition: background-position 0.1s linear; + transition: background-position 0.1s linear; +} +.btn:focus { + outline: thin dotted #333; + outline: 5px auto -webkit-focus-ring-color; + outline-offset: -2px; +} +.btn.active, +.btn:active { + background-image: none; + -webkit-box-shadow: inset 0 2px 4px rgba(0, 0, 0, 0.15), 0 1px 2px rgba(0, 0, 0, 0.05); + -moz-box-shadow: inset 0 2px 4px rgba(0, 0, 0, 0.15), 0 1px 2px rgba(0, 0, 0, 0.05); + box-shadow: inset 0 2px 4px rgba(0, 0, 0, 0.15), 0 1px 2px rgba(0, 0, 0, 0.05); + background-color: #e6e6e6; + background-color: #d9d9d9 \9; + outline: 0; +} +.btn.disabled, +.btn[disabled] { + cursor: default; + background-image: none; + background-color: #e6e6e6; + opacity: 0.65; + filter: alpha(opacity=65); + -webkit-box-shadow: none; + -moz-box-shadow: none; + box-shadow: none; +} +.btn-large { + padding: 9px 14px; + font-size: 15px; + line-height: normal; + -webkit-border-radius: 5px; + -moz-border-radius: 5px; + border-radius: 5px; +} +.btn-large [class^="icon-"] { + margin-top: 1px; +} +.btn-small { + padding: 5px 9px; + font-size: 11px; + line-height: 16px; +} +.btn-small [class^="icon-"] { + margin-top: -1px; +} +.btn-mini { + padding: 2px 6px; + font-size: 11px; + line-height: 14px; +} +.btn-primary, +.btn-primary:hover, +.btn-warning, +.btn-warning:hover, +.btn-danger, +.btn-danger:hover, +.btn-success, +.btn-success:hover, +.btn-info, +.btn-info:hover, +.btn-inverse, +.btn-inverse:hover { + text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.25); + color: #ffffff; +} +.btn-primary.active, +.btn-warning.active, +.btn-danger.active, +.btn-success.active, +.btn-info.active, +.btn-inverse.active { + color: rgba(255, 255, 255, 0.75); +} +.btn-primary { + background-color: #0074cc; + background-image: -moz-linear-gradient(top, #0088cc, #0055cc); + background-image: -ms-linear-gradient(top, #0088cc, #0055cc); + background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#0088cc), to(#0055cc)); + background-image: -webkit-linear-gradient(top, #0088cc, #0055cc); + background-image: -o-linear-gradient(top, #0088cc, #0055cc); + background-image: linear-gradient(top, #0088cc, #0055cc); + background-repeat: repeat-x; + filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#0088cc', endColorstr='#0055cc', GradientType=0); + border-color: #0055cc #0055cc #003580; + border-color: rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.25); + filter: progid:dximagetransform.microsoft.gradient(enabled=false); +} +.btn-primary:hover, +.btn-primary:active, +.btn-primary.active, +.btn-primary.disabled, +.btn-primary[disabled] { + background-color: #0055cc; +} +.btn-primary:active, +.btn-primary.active { + background-color: #004099 \9; +} +.btn-warning { + background-color: #faa732; + background-image: -moz-linear-gradient(top, #fbb450, #f89406); + background-image: -ms-linear-gradient(top, #fbb450, #f89406); + background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#fbb450), to(#f89406)); + background-image: -webkit-linear-gradient(top, #fbb450, #f89406); + background-image: -o-linear-gradient(top, #fbb450, #f89406); + background-image: linear-gradient(top, #fbb450, #f89406); + background-repeat: repeat-x; + filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#fbb450', endColorstr='#f89406', GradientType=0); + border-color: #f89406 #f89406 #ad6704; + border-color: rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.25); + filter: progid:dximagetransform.microsoft.gradient(enabled=false); +} +.btn-warning:hover, +.btn-warning:active, +.btn-warning.active, +.btn-warning.disabled, +.btn-warning[disabled] { + background-color: #f89406; +} +.btn-warning:active, +.btn-warning.active { + background-color: #c67605 \9; +} +.btn-danger { + background-color: #da4f49; + background-image: -moz-linear-gradient(top, #ee5f5b, #bd362f); + background-image: -ms-linear-gradient(top, #ee5f5b, #bd362f); + background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#ee5f5b), to(#bd362f)); + background-image: -webkit-linear-gradient(top, #ee5f5b, #bd362f); + background-image: -o-linear-gradient(top, #ee5f5b, #bd362f); + background-image: linear-gradient(top, #ee5f5b, #bd362f); + background-repeat: repeat-x; + filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#ee5f5b', endColorstr='#bd362f', GradientType=0); + border-color: #bd362f #bd362f #802420; + border-color: rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.25); + filter: progid:dximagetransform.microsoft.gradient(enabled=false); +} +.btn-danger:hover, +.btn-danger:active, +.btn-danger.active, +.btn-danger.disabled, +.btn-danger[disabled] { + background-color: #bd362f; +} +.btn-danger:active, +.btn-danger.active { + background-color: #942a25 \9; +} +.btn-success { + background-color: #5bb75b; + background-image: -moz-linear-gradient(top, #62c462, #51a351); + background-image: -ms-linear-gradient(top, #62c462, #51a351); + background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#62c462), to(#51a351)); + background-image: -webkit-linear-gradient(top, #62c462, #51a351); + background-image: -o-linear-gradient(top, #62c462, #51a351); + background-image: linear-gradient(top, #62c462, #51a351); + background-repeat: repeat-x; + filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#62c462', endColorstr='#51a351', GradientType=0); + border-color: #51a351 #51a351 #387038; + border-color: rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.25); + filter: progid:dximagetransform.microsoft.gradient(enabled=false); +} +.btn-success:hover, +.btn-success:active, +.btn-success.active, +.btn-success.disabled, +.btn-success[disabled] { + background-color: #51a351; +} +.btn-success:active, +.btn-success.active { + background-color: #408140 \9; +} +.btn-info { + background-color: #49afcd; + background-image: -moz-linear-gradient(top, #5bc0de, #2f96b4); + background-image: -ms-linear-gradient(top, #5bc0de, #2f96b4); + background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#5bc0de), to(#2f96b4)); + background-image: -webkit-linear-gradient(top, #5bc0de, #2f96b4); + background-image: -o-linear-gradient(top, #5bc0de, #2f96b4); + background-image: linear-gradient(top, #5bc0de, #2f96b4); + background-repeat: repeat-x; + filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#5bc0de', endColorstr='#2f96b4', GradientType=0); + border-color: #2f96b4 #2f96b4 #1f6377; + border-color: rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.25); + filter: progid:dximagetransform.microsoft.gradient(enabled=false); +} +.btn-info:hover, +.btn-info:active, +.btn-info.active, +.btn-info.disabled, +.btn-info[disabled] { + background-color: #2f96b4; +} +.btn-info:active, +.btn-info.active { + background-color: #24748c \9; +} +.btn-inverse { + background-color: #414141; + background-image: -moz-linear-gradient(top, #555555, #222222); + background-image: -ms-linear-gradient(top, #555555, #222222); + background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#555555), to(#222222)); + background-image: -webkit-linear-gradient(top, #555555, #222222); + background-image: -o-linear-gradient(top, #555555, #222222); + background-image: linear-gradient(top, #555555, #222222); + background-repeat: repeat-x; + filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#555555', endColorstr='#222222', GradientType=0); + border-color: #222222 #222222 #000000; + border-color: rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.25); + filter: progid:dximagetransform.microsoft.gradient(enabled=false); +} +.btn-inverse:hover, +.btn-inverse:active, +.btn-inverse.active, +.btn-inverse.disabled, +.btn-inverse[disabled] { + background-color: #222222; +} +.btn-inverse:active, +.btn-inverse.active { + background-color: #080808 \9; +} +button.btn, +input[type="submit"].btn { + *padding-top: 2px; + *padding-bottom: 2px; +} +button.btn::-moz-focus-inner, +input[type="submit"].btn::-moz-focus-inner { + padding: 0; + border: 0; +} +button.btn.btn-large, +input[type="submit"].btn.btn-large { + *padding-top: 7px; + *padding-bottom: 7px; +} +button.btn.btn-small, +input[type="submit"].btn.btn-small { + *padding-top: 3px; + *padding-bottom: 3px; +} +button.btn.btn-mini, +input[type="submit"].btn.btn-mini { + *padding-top: 1px; + *padding-bottom: 1px; +} +.btn-group { + position: relative; + *zoom: 1; + *margin-left: .3em; +} +.btn-group:before, +.btn-group:after { + display: table; + content: ""; +} +.btn-group:after { + clear: both; +} +.btn-group:first-child { + *margin-left: 0; +} +.btn-group + .btn-group { + margin-left: 5px; +} +.btn-toolbar { + margin-top: 9px; + margin-bottom: 9px; +} +.btn-toolbar .btn-group { + display: inline-block; + *display: inline; + /* IE7 inline-block hack */ + + *zoom: 1; +} +.btn-group .btn { + position: relative; + float: left; + margin-left: -1px; + -webkit-border-radius: 0; + -moz-border-radius: 0; + border-radius: 0; +} +.btn-group .btn:first-child { + margin-left: 0; + -webkit-border-top-left-radius: 4px; + -moz-border-radius-topleft: 4px; + border-top-left-radius: 4px; + -webkit-border-bottom-left-radius: 4px; + -moz-border-radius-bottomleft: 4px; + border-bottom-left-radius: 4px; +} +.btn-group .btn:last-child, +.btn-group .dropdown-toggle { + -webkit-border-top-right-radius: 4px; + -moz-border-radius-topright: 4px; + border-top-right-radius: 4px; + -webkit-border-bottom-right-radius: 4px; + -moz-border-radius-bottomright: 4px; + border-bottom-right-radius: 4px; +} +.btn-group .btn.large:first-child { + margin-left: 0; + -webkit-border-top-left-radius: 6px; + -moz-border-radius-topleft: 6px; + border-top-left-radius: 6px; + -webkit-border-bottom-left-radius: 6px; + -moz-border-radius-bottomleft: 6px; + border-bottom-left-radius: 6px; +} +.btn-group .btn.large:last-child, +.btn-group .large.dropdown-toggle { + -webkit-border-top-right-radius: 6px; + -moz-border-radius-topright: 6px; + border-top-right-radius: 6px; + -webkit-border-bottom-right-radius: 6px; + -moz-border-radius-bottomright: 6px; + border-bottom-right-radius: 6px; +} +.btn-group .btn:hover, +.btn-group .btn:focus, +.btn-group .btn:active, +.btn-group .btn.active { + z-index: 2; +} +.btn-group .dropdown-toggle:active, +.btn-group.open .dropdown-toggle { + outline: 0; +} +.btn-group .dropdown-toggle { + padding-left: 8px; + padding-right: 8px; + -webkit-box-shadow: inset 1px 0 0 rgba(255, 255, 255, 0.125), inset 0 1px 0 rgba(255, 255, 255, 0.2), 0 1px 2px rgba(0, 0, 0, 0.05); + -moz-box-shadow: inset 1px 0 0 rgba(255, 255, 255, 0.125), inset 0 1px 0 rgba(255, 255, 255, 0.2), 0 1px 2px rgba(0, 0, 0, 0.05); + box-shadow: inset 1px 0 0 rgba(255, 255, 255, 0.125), inset 0 1px 0 rgba(255, 255, 255, 0.2), 0 1px 2px rgba(0, 0, 0, 0.05); + *padding-top: 3px; + *padding-bottom: 3px; +} +.btn-group .btn-mini.dropdown-toggle { + padding-left: 5px; + padding-right: 5px; + *padding-top: 1px; + *padding-bottom: 1px; +} +.btn-group .btn-small.dropdown-toggle { + *padding-top: 4px; + *padding-bottom: 4px; +} +.btn-group .btn-large.dropdown-toggle { + padding-left: 12px; + padding-right: 12px; +} +.btn-group.open { + *z-index: 1000; +} +.btn-group.open .dropdown-menu { + display: block; + margin-top: 1px; + -webkit-border-radius: 5px; + -moz-border-radius: 5px; + border-radius: 5px; +} +.btn-group.open .dropdown-toggle { + background-image: none; + -webkit-box-shadow: inset 0 1px 6px rgba(0, 0, 0, 0.15), 0 1px 2px rgba(0, 0, 0, 0.05); + -moz-box-shadow: inset 0 1px 6px rgba(0, 0, 0, 0.15), 0 1px 2px rgba(0, 0, 0, 0.05); + box-shadow: inset 0 1px 6px rgba(0, 0, 0, 0.15), 0 1px 2px rgba(0, 0, 0, 0.05); +} +.btn .caret { + margin-top: 7px; + margin-left: 0; +} +.btn:hover .caret, +.open.btn-group .caret { + opacity: 1; + filter: alpha(opacity=100); +} +.btn-mini .caret { + margin-top: 5px; +} +.btn-small .caret { + margin-top: 6px; +} +.btn-large .caret { + margin-top: 6px; + border-left: 5px solid transparent; + border-right: 5px solid transparent; + border-top: 5px solid #000000; +} +.btn-primary .caret, +.btn-warning .caret, +.btn-danger .caret, +.btn-info .caret, +.btn-success .caret, +.btn-inverse .caret { + border-top-color: #ffffff; + border-bottom-color: #ffffff; + opacity: 0.75; + filter: alpha(opacity=75); +} +.alert { + padding: 8px 35px 8px 14px; + margin-bottom: 18px; + text-shadow: 0 1px 0 rgba(255, 255, 255, 0.5); + background-color: #fcf8e3; + border: 1px solid #fbeed5; + -webkit-border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; + color: #c09853; +} +.alert-heading { + color: inherit; +} +.alert .close { + position: relative; + top: -2px; + right: -21px; + line-height: 18px; +} +.alert-success { + background-color: #dff0d8; + border-color: #d6e9c6; + color: #468847; +} +.alert-danger, +.alert-error { + background-color: #f2dede; + border-color: #eed3d7; + color: #b94a48; +} +.alert-info { + background-color: #d9edf7; + border-color: #bce8f1; + color: #3a87ad; +} +.alert-block { + padding-top: 14px; + padding-bottom: 14px; +} +.alert-block > p, +.alert-block > ul { + margin-bottom: 0; +} +.alert-block p + p { + margin-top: 5px; +} +.nav { + margin-left: 0; + margin-bottom: 18px; + list-style: none; +} +.nav > li > a { + display: block; +} +.nav > li > a:hover { + text-decoration: none; + background-color: #eeeeee; +} +.nav .nav-header { + display: block; + padding: 3px 15px; + font-size: 11px; + font-weight: bold; + line-height: 18px; + color: #999999; + text-shadow: 0 1px 0 rgba(255, 255, 255, 0.5); + text-transform: uppercase; +} +.nav li + .nav-header { + margin-top: 9px; +} +.nav-list { + padding-left: 15px; + padding-right: 15px; + margin-bottom: 0; +} +.nav-list > li > a, +.nav-list .nav-header { + margin-left: -15px; + margin-right: -15px; + text-shadow: 0 1px 0 rgba(255, 255, 255, 0.5); +} +.nav-list > li > a { + padding: 3px 15px; +} +.nav-list > .active > a, +.nav-list > .active > a:hover { + color: #ffffff; + text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.2); + background-color: #0088cc; +} +.nav-list [class^="icon-"] { + margin-right: 2px; +} +.nav-list .divider { + height: 1px; + margin: 8px 1px; + overflow: hidden; + background-color: #e5e5e5; + border-bottom: 1px solid #ffffff; + *width: 100%; + *margin: -5px 0 5px; +} +.nav-tabs, +.nav-pills { + *zoom: 1; +} +.nav-tabs:before, +.nav-pills:before, +.nav-tabs:after, +.nav-pills:after { + display: table; + content: ""; +} +.nav-tabs:after, +.nav-pills:after { + clear: both; +} +.nav-tabs > li, +.nav-pills > li { + float: left; +} +.nav-tabs > li > a, +.nav-pills > li > a { + padding-right: 12px; + padding-left: 12px; + margin-right: 2px; + line-height: 14px; +} +.nav-tabs { + border-bottom: 1px solid #ddd; +} +.nav-tabs > li { + margin-bottom: -1px; +} +.nav-tabs > li > a { + padding-top: 8px; + padding-bottom: 8px; + line-height: 18px; + border: 1px solid transparent; + -webkit-border-radius: 4px 4px 0 0; + -moz-border-radius: 4px 4px 0 0; + border-radius: 4px 4px 0 0; +} +.nav-tabs > li > a:hover { + border-color: #eeeeee #eeeeee #dddddd; +} +.nav-tabs > .active > a, +.nav-tabs > .active > a:hover { + color: #555555; + background-color: #ffffff; + border: 1px solid #ddd; + border-bottom-color: transparent; + cursor: default; +} +.nav-pills > li > a { + padding-top: 8px; + padding-bottom: 8px; + margin-top: 2px; + margin-bottom: 2px; + -webkit-border-radius: 5px; + -moz-border-radius: 5px; + border-radius: 5px; +} +.nav-pills > .active > a, +.nav-pills > .active > a:hover { + color: #ffffff; + background-color: #0088cc; +} +.nav-stacked > li { + float: none; +} +.nav-stacked > li > a { + margin-right: 0; +} +.nav-tabs.nav-stacked { + border-bottom: 0; +} +.nav-tabs.nav-stacked > li > a { + border: 1px solid #ddd; + -webkit-border-radius: 0; + -moz-border-radius: 0; + border-radius: 0; +} +.nav-tabs.nav-stacked > li:first-child > a { + -webkit-border-radius: 4px 4px 0 0; + -moz-border-radius: 4px 4px 0 0; + border-radius: 4px 4px 0 0; +} +.nav-tabs.nav-stacked > li:last-child > a { + -webkit-border-radius: 0 0 4px 4px; + -moz-border-radius: 0 0 4px 4px; + border-radius: 0 0 4px 4px; +} +.nav-tabs.nav-stacked > li > a:hover { + border-color: #ddd; + z-index: 2; +} +.nav-pills.nav-stacked > li > a { + margin-bottom: 3px; +} +.nav-pills.nav-stacked > li:last-child > a { + margin-bottom: 1px; +} +.nav-tabs .dropdown-menu, +.nav-pills .dropdown-menu { + margin-top: 1px; + border-width: 1px; +} +.nav-pills .dropdown-menu { + -webkit-border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; +} +.nav-tabs .dropdown-toggle .caret, +.nav-pills .dropdown-toggle .caret { + border-top-color: #0088cc; + border-bottom-color: #0088cc; + margin-top: 6px; +} +.nav-tabs .dropdown-toggle:hover .caret, +.nav-pills .dropdown-toggle:hover .caret { + border-top-color: #005580; + border-bottom-color: #005580; +} +.nav-tabs .active .dropdown-toggle .caret, +.nav-pills .active .dropdown-toggle .caret { + border-top-color: #333333; + border-bottom-color: #333333; +} +.nav > .dropdown.active > a:hover { + color: #000000; + cursor: pointer; +} +.nav-tabs .open .dropdown-toggle, +.nav-pills .open .dropdown-toggle, +.nav > .open.active > a:hover { + color: #ffffff; + background-color: #999999; + border-color: #999999; +} +.nav .open .caret, +.nav .open.active .caret, +.nav .open a:hover .caret { + border-top-color: #ffffff; + border-bottom-color: #ffffff; + opacity: 1; + filter: alpha(opacity=100); +} +.tabs-stacked .open > a:hover { + border-color: #999999; +} +.tabbable { + *zoom: 1; +} +.tabbable:before, +.tabbable:after { + display: table; + content: ""; +} +.tabbable:after { + clear: both; +} +.tab-content { + display: table; + width: 100%; +} +.tabs-below .nav-tabs, +.tabs-right .nav-tabs, +.tabs-left .nav-tabs { + border-bottom: 0; +} +.tab-content > .tab-pane, +.pill-content > .pill-pane { + display: none; +} +.tab-content > .active, +.pill-content > .active { + display: block; +} +.tabs-below .nav-tabs { + border-top: 1px solid #ddd; +} +.tabs-below .nav-tabs > li { + margin-top: -1px; + margin-bottom: 0; +} +.tabs-below .nav-tabs > li > a { + -webkit-border-radius: 0 0 4px 4px; + -moz-border-radius: 0 0 4px 4px; + border-radius: 0 0 4px 4px; +} +.tabs-below .nav-tabs > li > a:hover { + border-bottom-color: transparent; + border-top-color: #ddd; +} +.tabs-below .nav-tabs .active > a, +.tabs-below .nav-tabs .active > a:hover { + border-color: transparent #ddd #ddd #ddd; +} +.tabs-left .nav-tabs > li, +.tabs-right .nav-tabs > li { + float: none; +} +.tabs-left .nav-tabs > li > a, +.tabs-right .nav-tabs > li > a { + min-width: 74px; + margin-right: 0; + margin-bottom: 3px; +} +.tabs-left .nav-tabs { + float: left; + margin-right: 19px; + border-right: 1px solid #ddd; +} +.tabs-left .nav-tabs > li > a { + margin-right: -1px; + -webkit-border-radius: 4px 0 0 4px; + -moz-border-radius: 4px 0 0 4px; + border-radius: 4px 0 0 4px; +} +.tabs-left .nav-tabs > li > a:hover { + border-color: #eeeeee #dddddd #eeeeee #eeeeee; +} +.tabs-left .nav-tabs .active > a, +.tabs-left .nav-tabs .active > a:hover { + border-color: #ddd transparent #ddd #ddd; + *border-right-color: #ffffff; +} +.tabs-right .nav-tabs { + float: right; + margin-left: 19px; + border-left: 1px solid #ddd; +} +.tabs-right .nav-tabs > li > a { + margin-left: -1px; + -webkit-border-radius: 0 4px 4px 0; + -moz-border-radius: 0 4px 4px 0; + border-radius: 0 4px 4px 0; +} +.tabs-right .nav-tabs > li > a:hover { + border-color: #eeeeee #eeeeee #eeeeee #dddddd; +} +.tabs-right .nav-tabs .active > a, +.tabs-right .nav-tabs .active > a:hover { + border-color: #ddd #ddd #ddd transparent; + *border-left-color: #ffffff; +} +.navbar { + *position: relative; + *z-index: 2; + overflow: visible; + margin-bottom: 18px; +} +.navbar-inner { + padding-left: 20px; + padding-right: 20px; + background-color: #2c2c2c; + background-image: -moz-linear-gradient(top, #333333, #222222); + background-image: -ms-linear-gradient(top, #333333, #222222); + background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#333333), to(#222222)); + background-image: -webkit-linear-gradient(top, #333333, #222222); + background-image: -o-linear-gradient(top, #333333, #222222); + background-image: linear-gradient(top, #333333, #222222); + background-repeat: repeat-x; + filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#333333', endColorstr='#222222', GradientType=0); + -webkit-border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; + -webkit-box-shadow: 0 1px 3px rgba(0, 0, 0, 0.25), inset 0 -1px 0 rgba(0, 0, 0, 0.1); + -moz-box-shadow: 0 1px 3px rgba(0, 0, 0, 0.25), inset 0 -1px 0 rgba(0, 0, 0, 0.1); + box-shadow: 0 1px 3px rgba(0, 0, 0, 0.25), inset 0 -1px 0 rgba(0, 0, 0, 0.1); +} +.navbar .container { + width: auto; +} +.btn-navbar { + display: none; + float: right; + padding: 7px 10px; + margin-left: 5px; + margin-right: 5px; + background-color: #2c2c2c; + background-image: -moz-linear-gradient(top, #333333, #222222); + background-image: -ms-linear-gradient(top, #333333, #222222); + background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#333333), to(#222222)); + background-image: -webkit-linear-gradient(top, #333333, #222222); + background-image: -o-linear-gradient(top, #333333, #222222); + background-image: linear-gradient(top, #333333, #222222); + background-repeat: repeat-x; + filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#333333', endColorstr='#222222', GradientType=0); + border-color: #222222 #222222 #000000; + border-color: rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.25); + filter: progid:dximagetransform.microsoft.gradient(enabled=false); + -webkit-box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.1), 0 1px 0 rgba(255, 255, 255, 0.075); + -moz-box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.1), 0 1px 0 rgba(255, 255, 255, 0.075); + box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.1), 0 1px 0 rgba(255, 255, 255, 0.075); +} +.btn-navbar:hover, +.btn-navbar:active, +.btn-navbar.active, +.btn-navbar.disabled, +.btn-navbar[disabled] { + background-color: #222222; +} +.btn-navbar:active, +.btn-navbar.active { + background-color: #080808 \9; +} +.btn-navbar .icon-bar { + display: block; + width: 18px; + height: 2px; + background-color: #f5f5f5; + -webkit-border-radius: 1px; + -moz-border-radius: 1px; + border-radius: 1px; + -webkit-box-shadow: 0 1px 0 rgba(0, 0, 0, 0.25); + -moz-box-shadow: 0 1px 0 rgba(0, 0, 0, 0.25); + box-shadow: 0 1px 0 rgba(0, 0, 0, 0.25); +} +.btn-navbar .icon-bar + .icon-bar { + margin-top: 3px; +} +.nav-collapse.collapse { + height: auto; +} +.navbar { + color: #999999; +} +.navbar .brand:hover { + text-decoration: none; +} +.navbar .brand { + float: left; + display: block; + padding: 8px 20px 12px; + margin-left: -20px; + font-size: 20px; + font-weight: 200; + line-height: 1; + color: #ffffff; +} +.navbar .navbar-text { + margin-bottom: 0; + line-height: 40px; +} +.navbar .btn, +.navbar .btn-group { + margin-top: 5px; +} +.navbar .btn-group .btn { + margin-top: 0; +} +.navbar-form { + margin-bottom: 0; + *zoom: 1; +} +.navbar-form:before, +.navbar-form:after { + display: table; + content: ""; +} +.navbar-form:after { + clear: both; +} +.navbar-form input, +.navbar-form select, +.navbar-form .radio, +.navbar-form .checkbox { + margin-top: 5px; +} +.navbar-form input, +.navbar-form select { + display: inline-block; + margin-bottom: 0; +} +.navbar-form input[type="image"], +.navbar-form input[type="checkbox"], +.navbar-form input[type="radio"] { + margin-top: 3px; +} +.navbar-form .input-append, +.navbar-form .input-prepend { + margin-top: 6px; + white-space: nowrap; +} +.navbar-form .input-append input, +.navbar-form .input-prepend input { + margin-top: 0; +} +.navbar-search { + position: relative; + float: left; + margin-top: 6px; + margin-bottom: 0; +} +.navbar-search .search-query { + padding: 4px 9px; + font-family: "Helvetica Neue", Helvetica, Arial, sans-serif; + font-size: 13px; + font-weight: normal; + line-height: 1; + color: #ffffff; + background-color: #626262; + border: 1px solid #151515; + -webkit-box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.1), 0 1px 0px rgba(255, 255, 255, 0.15); + -moz-box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.1), 0 1px 0px rgba(255, 255, 255, 0.15); + box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.1), 0 1px 0px rgba(255, 255, 255, 0.15); + -webkit-transition: none; + -moz-transition: none; + -ms-transition: none; + -o-transition: none; + transition: none; +} +.navbar-search .search-query:-moz-placeholder { + color: #cccccc; +} +.navbar-search .search-query::-webkit-input-placeholder { + color: #cccccc; +} +.navbar-search .search-query:focus, +.navbar-search .search-query.focused { + padding: 5px 10px; + color: #333333; + text-shadow: 0 1px 0 #ffffff; + background-color: #ffffff; + border: 0; + -webkit-box-shadow: 0 0 3px rgba(0, 0, 0, 0.15); + -moz-box-shadow: 0 0 3px rgba(0, 0, 0, 0.15); + box-shadow: 0 0 3px rgba(0, 0, 0, 0.15); + outline: 0; +} +.navbar-fixed-top, +.navbar-fixed-bottom { + position: fixed; + right: 0; + left: 0; + z-index: 1030; + margin-bottom: 0; +} +.navbar-fixed-top .navbar-inner, +.navbar-fixed-bottom .navbar-inner { + padding-left: 0; + padding-right: 0; + -webkit-border-radius: 0; + -moz-border-radius: 0; + border-radius: 0; +} +.navbar-fixed-top .container, +.navbar-fixed-bottom .container { + width: 940px; +} +.navbar-fixed-top { + top: 0; +} +.navbar-fixed-bottom { + bottom: 0; +} +.navbar .nav { + position: relative; + left: 0; + display: block; + float: left; + margin: 0 10px 0 0; +} +.navbar .nav.pull-right { + float: right; +} +.navbar .nav > li { + display: block; + float: left; +} +.navbar .nav > li > a { + float: none; + padding: 10px 10px 11px; + line-height: 19px; + color: #999999; + text-decoration: none; + text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.25); +} +.navbar .nav > li > a:hover { + background-color: transparent; + color: #ffffff; + text-decoration: none; +} +.navbar .nav .active > a, +.navbar .nav .active > a:hover { + color: #ffffff; + text-decoration: none; + background-color: #222222; +} +.navbar .divider-vertical { + height: 40px; + width: 1px; + margin: 0 9px; + overflow: hidden; + background-color: #222222; + border-right: 1px solid #333333; +} +.navbar .nav.pull-right { + margin-left: 10px; + margin-right: 0; +} +.navbar .dropdown-menu { + margin-top: 1px; + -webkit-border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; +} +.navbar .dropdown-menu:before { + content: ''; + display: inline-block; + border-left: 7px solid transparent; + border-right: 7px solid transparent; + border-bottom: 7px solid #ccc; + border-bottom-color: rgba(0, 0, 0, 0.2); + position: absolute; + top: -7px; + left: 9px; +} +.navbar .dropdown-menu:after { + content: ''; + display: inline-block; + border-left: 6px solid transparent; + border-right: 6px solid transparent; + border-bottom: 6px solid #ffffff; + position: absolute; + top: -6px; + left: 10px; +} +.navbar-fixed-bottom .dropdown-menu:before { + border-top: 7px solid #ccc; + border-top-color: rgba(0, 0, 0, 0.2); + border-bottom: 0; + bottom: -7px; + top: auto; +} +.navbar-fixed-bottom .dropdown-menu:after { + border-top: 6px solid #ffffff; + border-bottom: 0; + bottom: -6px; + top: auto; +} +.navbar .nav .dropdown-toggle .caret, +.navbar .nav .open.dropdown .caret { + border-top-color: #ffffff; + border-bottom-color: #ffffff; +} +.navbar .nav .active .caret { + opacity: 1; + filter: alpha(opacity=100); +} +.navbar .nav .open > .dropdown-toggle, +.navbar .nav .active > .dropdown-toggle, +.navbar .nav .open.active > .dropdown-toggle { + background-color: transparent; +} +.navbar .nav .active > .dropdown-toggle:hover { + color: #ffffff; +} +.navbar .nav.pull-right .dropdown-menu, +.navbar .nav .dropdown-menu.pull-right { + left: auto; + right: 0; +} +.navbar .nav.pull-right .dropdown-menu:before, +.navbar .nav .dropdown-menu.pull-right:before { + left: auto; + right: 12px; +} +.navbar .nav.pull-right .dropdown-menu:after, +.navbar .nav .dropdown-menu.pull-right:after { + left: auto; + right: 13px; +} +.breadcrumb { + padding: 7px 14px; + margin: 0 0 18px; + list-style: none; + background-color: #fbfbfb; + background-image: -moz-linear-gradient(top, #ffffff, #f5f5f5); + background-image: -ms-linear-gradient(top, #ffffff, #f5f5f5); + background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#ffffff), to(#f5f5f5)); + background-image: -webkit-linear-gradient(top, #ffffff, #f5f5f5); + background-image: -o-linear-gradient(top, #ffffff, #f5f5f5); + background-image: linear-gradient(top, #ffffff, #f5f5f5); + background-repeat: repeat-x; + filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#ffffff', endColorstr='#f5f5f5', GradientType=0); + border: 1px solid #ddd; + -webkit-border-radius: 3px; + -moz-border-radius: 3px; + border-radius: 3px; + -webkit-box-shadow: inset 0 1px 0 #ffffff; + -moz-box-shadow: inset 0 1px 0 #ffffff; + box-shadow: inset 0 1px 0 #ffffff; +} +.breadcrumb li { + display: inline-block; + *display: inline; + /* IE7 inline-block hack */ + + *zoom: 1; + text-shadow: 0 1px 0 #ffffff; +} +.breadcrumb .divider { + padding: 0 5px; + color: #999999; +} +.breadcrumb .active a { + color: #333333; +} +.pagination { + height: 36px; + margin: 18px 0; +} +.pagination ul { + display: inline-block; + *display: inline; + /* IE7 inline-block hack */ + + *zoom: 1; + margin-left: 0; + margin-bottom: 0; + -webkit-border-radius: 3px; + -moz-border-radius: 3px; + border-radius: 3px; + -webkit-box-shadow: 0 1px 2px rgba(0, 0, 0, 0.05); + -moz-box-shadow: 0 1px 2px rgba(0, 0, 0, 0.05); + box-shadow: 0 1px 2px rgba(0, 0, 0, 0.05); +} +.pagination li { + display: inline; +} +.pagination a { + float: left; + padding: 0 14px; + line-height: 34px; + text-decoration: none; + border: 1px solid #ddd; + border-left-width: 0; +} +.pagination a:hover, +.pagination .active a { + background-color: #f5f5f5; +} +.pagination .active a { + color: #999999; + cursor: default; +} +.pagination .disabled span, +.pagination .disabled a, +.pagination .disabled a:hover { + color: #999999; + background-color: transparent; + cursor: default; +} +.pagination li:first-child a { + border-left-width: 1px; + -webkit-border-radius: 3px 0 0 3px; + -moz-border-radius: 3px 0 0 3px; + border-radius: 3px 0 0 3px; +} +.pagination li:last-child a { + -webkit-border-radius: 0 3px 3px 0; + -moz-border-radius: 0 3px 3px 0; + border-radius: 0 3px 3px 0; +} +.pagination-centered { + text-align: center; +} +.pagination-right { + text-align: right; +} +.pager { + margin-left: 0; + margin-bottom: 18px; + list-style: none; + text-align: center; + *zoom: 1; +} +.pager:before, +.pager:after { + display: table; + content: ""; +} +.pager:after { + clear: both; +} +.pager li { + display: inline; +} +.pager a { + display: inline-block; + padding: 5px 14px; + background-color: #fff; + border: 1px solid #ddd; + -webkit-border-radius: 15px; + -moz-border-radius: 15px; + border-radius: 15px; +} +.pager a:hover { + text-decoration: none; + background-color: #f5f5f5; +} +.pager .next a { + float: right; +} +.pager .previous a { + float: left; +} +.pager .disabled a, +.pager .disabled a:hover { + color: #999999; + background-color: #fff; + cursor: default; +} +.modal-open .dropdown-menu { + z-index: 2050; +} +.modal-open .dropdown.open { + *z-index: 2050; +} +.modal-open .popover { + z-index: 2060; +} +.modal-open .tooltip { + z-index: 2070; +} +.modal-backdrop { + position: fixed; + top: 0; + right: 0; + bottom: 0; + left: 0; + z-index: 1040; + background-color: #000000; +} +.modal-backdrop.fade { + opacity: 0; +} +.modal-backdrop, +.modal-backdrop.fade.in { + opacity: 0.8; + filter: alpha(opacity=80); +} +.modal { + position: fixed; + top: 50%; + left: 50%; + z-index: 1050; + overflow: auto; + width: 560px; + margin: -250px 0 0 -280px; + background-color: #ffffff; + border: 1px solid #999; + border: 1px solid rgba(0, 0, 0, 0.3); + *border: 1px solid #999; + /* IE6-7 */ + + -webkit-border-radius: 6px; + -moz-border-radius: 6px; + border-radius: 6px; + -webkit-box-shadow: 0 3px 7px rgba(0, 0, 0, 0.3); + -moz-box-shadow: 0 3px 7px rgba(0, 0, 0, 0.3); + box-shadow: 0 3px 7px rgba(0, 0, 0, 0.3); + -webkit-background-clip: padding-box; + -moz-background-clip: padding-box; + background-clip: padding-box; +} +.modal.fade { + -webkit-transition: opacity .3s linear, top .3s ease-out; + -moz-transition: opacity .3s linear, top .3s ease-out; + -ms-transition: opacity .3s linear, top .3s ease-out; + -o-transition: opacity .3s linear, top .3s ease-out; + transition: opacity .3s linear, top .3s ease-out; + top: -25%; +} +.modal.fade.in { + top: 50%; +} +.modal-header { + padding: 9px 15px; + border-bottom: 1px solid #eee; +} +.modal-header .close { + margin-top: 2px; +} +.modal-body { + overflow-y: auto; + max-height: 400px; + padding: 15px; +} +.modal-form { + margin-bottom: 0; +} +.modal-footer { + padding: 14px 15px 15px; + margin-bottom: 0; + text-align: right; + background-color: #f5f5f5; + border-top: 1px solid #ddd; + -webkit-border-radius: 0 0 6px 6px; + -moz-border-radius: 0 0 6px 6px; + border-radius: 0 0 6px 6px; + -webkit-box-shadow: inset 0 1px 0 #ffffff; + -moz-box-shadow: inset 0 1px 0 #ffffff; + box-shadow: inset 0 1px 0 #ffffff; + *zoom: 1; +} +.modal-footer:before, +.modal-footer:after { + display: table; + content: ""; +} +.modal-footer:after { + clear: both; +} +.modal-footer .btn + .btn { + margin-left: 5px; + margin-bottom: 0; +} +.modal-footer .btn-group .btn + .btn { + margin-left: -1px; +} +.tooltip { + position: absolute; + z-index: 1020; + display: block; + visibility: visible; + padding: 5px; + font-size: 11px; + opacity: 0; + filter: alpha(opacity=0); +} +.tooltip.in { + opacity: 0.8; + filter: alpha(opacity=80); +} +.tooltip.top { + margin-top: -2px; +} +.tooltip.right { + margin-left: 2px; +} +.tooltip.bottom { + margin-top: 2px; +} +.tooltip.left { + margin-left: -2px; +} +.tooltip.top .tooltip-arrow { + bottom: 0; + left: 50%; + margin-left: -5px; + border-left: 5px solid transparent; + border-right: 5px solid transparent; + border-top: 5px solid #000000; +} +.tooltip.left .tooltip-arrow { + top: 50%; + right: 0; + margin-top: -5px; + border-top: 5px solid transparent; + border-bottom: 5px solid transparent; + border-left: 5px solid #000000; +} +.tooltip.bottom .tooltip-arrow { + top: 0; + left: 50%; + margin-left: -5px; + border-left: 5px solid transparent; + border-right: 5px solid transparent; + border-bottom: 5px solid #000000; +} +.tooltip.right .tooltip-arrow { + top: 50%; + left: 0; + margin-top: -5px; + border-top: 5px solid transparent; + border-bottom: 5px solid transparent; + border-right: 5px solid #000000; +} +.tooltip-inner { + max-width: 200px; + padding: 3px 8px; + color: #ffffff; + text-align: center; + text-decoration: none; + background-color: #000000; + -webkit-border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; +} +.tooltip-arrow { + position: absolute; + width: 0; + height: 0; +} +.popover { + position: absolute; + top: 0; + left: 0; + z-index: 1010; + display: none; + padding: 5px; +} +.popover.top { + margin-top: -5px; +} +.popover.right { + margin-left: 5px; +} +.popover.bottom { + margin-top: 5px; +} +.popover.left { + margin-left: -5px; +} +.popover.top .arrow { + bottom: 0; + left: 50%; + margin-left: -5px; + border-left: 5px solid transparent; + border-right: 5px solid transparent; + border-top: 5px solid #000000; +} +.popover.right .arrow { + top: 50%; + left: 0; + margin-top: -5px; + border-top: 5px solid transparent; + border-bottom: 5px solid transparent; + border-right: 5px solid #000000; +} +.popover.bottom .arrow { + top: 0; + left: 50%; + margin-left: -5px; + border-left: 5px solid transparent; + border-right: 5px solid transparent; + border-bottom: 5px solid #000000; +} +.popover.left .arrow { + top: 50%; + right: 0; + margin-top: -5px; + border-top: 5px solid transparent; + border-bottom: 5px solid transparent; + border-left: 5px solid #000000; +} +.popover .arrow { + position: absolute; + width: 0; + height: 0; +} +.popover-inner { + padding: 3px; + width: 280px; + overflow: hidden; + background: #000000; + background: rgba(0, 0, 0, 0.8); + -webkit-border-radius: 6px; + -moz-border-radius: 6px; + border-radius: 6px; + -webkit-box-shadow: 0 3px 7px rgba(0, 0, 0, 0.3); + -moz-box-shadow: 0 3px 7px rgba(0, 0, 0, 0.3); + box-shadow: 0 3px 7px rgba(0, 0, 0, 0.3); +} +.popover-title { + padding: 9px 15px; + line-height: 1; + background-color: #f5f5f5; + border-bottom: 1px solid #eee; + -webkit-border-radius: 3px 3px 0 0; + -moz-border-radius: 3px 3px 0 0; + border-radius: 3px 3px 0 0; +} +.popover-content { + padding: 14px; + background-color: #ffffff; + -webkit-border-radius: 0 0 3px 3px; + -moz-border-radius: 0 0 3px 3px; + border-radius: 0 0 3px 3px; + -webkit-background-clip: padding-box; + -moz-background-clip: padding-box; + background-clip: padding-box; +} +.popover-content p, +.popover-content ul, +.popover-content ol { + margin-bottom: 0; +} +.thumbnails { + margin-left: -20px; + list-style: none; + *zoom: 1; +} +.thumbnails:before, +.thumbnails:after { + display: table; + content: ""; +} +.thumbnails:after { + clear: both; +} +.thumbnails > li { + float: left; + margin: 0 0 18px 20px; +} +.thumbnail { + display: block; + padding: 4px; + line-height: 1; + border: 1px solid #ddd; + -webkit-border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; + -webkit-box-shadow: 0 1px 1px rgba(0, 0, 0, 0.075); + -moz-box-shadow: 0 1px 1px rgba(0, 0, 0, 0.075); + box-shadow: 0 1px 1px rgba(0, 0, 0, 0.075); +} +a.thumbnail:hover { + border-color: #0088cc; + -webkit-box-shadow: 0 1px 4px rgba(0, 105, 214, 0.25); + -moz-box-shadow: 0 1px 4px rgba(0, 105, 214, 0.25); + box-shadow: 0 1px 4px rgba(0, 105, 214, 0.25); +} +.thumbnail > img { + display: block; + max-width: 100%; + margin-left: auto; + margin-right: auto; +} +.thumbnail .caption { + padding: 9px; +} +.label { + padding: 1px 4px 2px; + font-size: 10.998px; + font-weight: bold; + line-height: 13px; + color: #ffffff; + vertical-align: middle; + white-space: nowrap; + text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.25); + background-color: #999999; + -webkit-border-radius: 3px; + -moz-border-radius: 3px; + border-radius: 3px; +} +.label:hover { + color: #ffffff; + text-decoration: none; +} +.label-important { + background-color: #b94a48; +} +.label-important:hover { + background-color: #953b39; +} +.label-warning { + background-color: #f89406; +} +.label-warning:hover { + background-color: #c67605; +} +.label-success { + background-color: #468847; +} +.label-success:hover { + background-color: #356635; +} +.label-info { + background-color: #3a87ad; +} +.label-info:hover { + background-color: #2d6987; +} +.label-inverse { + background-color: #333333; +} +.label-inverse:hover { + background-color: #1a1a1a; +} +.badge { + padding: 1px 9px 2px; + font-size: 12.025px; + font-weight: bold; + white-space: nowrap; + color: #ffffff; + background-color: #999999; + -webkit-border-radius: 9px; + -moz-border-radius: 9px; + border-radius: 9px; +} +.badge:hover { + color: #ffffff; + text-decoration: none; + cursor: pointer; +} +.badge-error { + background-color: #b94a48; +} +.badge-error:hover { + background-color: #953b39; +} +.badge-warning { + background-color: #f89406; +} +.badge-warning:hover { + background-color: #c67605; +} +.badge-success { + background-color: #468847; +} +.badge-success:hover { + background-color: #356635; +} +.badge-info { + background-color: #3a87ad; +} +.badge-info:hover { + background-color: #2d6987; +} +.badge-inverse { + background-color: #333333; +} +.badge-inverse:hover { + background-color: #1a1a1a; +} +@-webkit-keyframes progress-bar-stripes { + from { + background-position: 0 0; + } + to { + background-position: 40px 0; + } +} +@-moz-keyframes progress-bar-stripes { + from { + background-position: 0 0; + } + to { + background-position: 40px 0; + } +} +@-ms-keyframes progress-bar-stripes { + from { + background-position: 0 0; + } + to { + background-position: 40px 0; + } +} +@keyframes progress-bar-stripes { + from { + background-position: 0 0; + } + to { + background-position: 40px 0; + } +} +.progress { + overflow: hidden; + height: 18px; + margin-bottom: 18px; + background-color: #f7f7f7; + background-image: -moz-linear-gradient(top, #f5f5f5, #f9f9f9); + background-image: -ms-linear-gradient(top, #f5f5f5, #f9f9f9); + background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#f5f5f5), to(#f9f9f9)); + background-image: -webkit-linear-gradient(top, #f5f5f5, #f9f9f9); + background-image: -o-linear-gradient(top, #f5f5f5, #f9f9f9); + background-image: linear-gradient(top, #f5f5f5, #f9f9f9); + background-repeat: repeat-x; + filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#f5f5f5', endColorstr='#f9f9f9', GradientType=0); + -webkit-box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.1); + -moz-box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.1); + box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.1); + -webkit-border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; +} +.progress .bar { + width: 0%; + height: 18px; + color: #ffffff; + font-size: 12px; + text-align: center; + text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.25); + background-color: #0e90d2; + background-image: -moz-linear-gradient(top, #149bdf, #0480be); + background-image: -ms-linear-gradient(top, #149bdf, #0480be); + background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#149bdf), to(#0480be)); + background-image: -webkit-linear-gradient(top, #149bdf, #0480be); + background-image: -o-linear-gradient(top, #149bdf, #0480be); + background-image: linear-gradient(top, #149bdf, #0480be); + background-repeat: repeat-x; + filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#149bdf', endColorstr='#0480be', GradientType=0); + -webkit-box-shadow: inset 0 -1px 0 rgba(0, 0, 0, 0.15); + -moz-box-shadow: inset 0 -1px 0 rgba(0, 0, 0, 0.15); + box-shadow: inset 0 -1px 0 rgba(0, 0, 0, 0.15); + -webkit-box-sizing: border-box; + -moz-box-sizing: border-box; + -ms-box-sizing: border-box; + box-sizing: border-box; + -webkit-transition: width 0.6s ease; + -moz-transition: width 0.6s ease; + -ms-transition: width 0.6s ease; + -o-transition: width 0.6s ease; + transition: width 0.6s ease; +} +.progress-striped .bar { + background-color: #149bdf; + background-image: -webkit-gradient(linear, 0 100%, 100% 0, color-stop(0.25, rgba(255, 255, 255, 0.15)), color-stop(0.25, transparent), color-stop(0.5, transparent), color-stop(0.5, rgba(255, 255, 255, 0.15)), color-stop(0.75, rgba(255, 255, 255, 0.15)), color-stop(0.75, transparent), to(transparent)); + background-image: -webkit-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: -moz-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: -ms-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: -o-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + -webkit-background-size: 40px 40px; + -moz-background-size: 40px 40px; + -o-background-size: 40px 40px; + background-size: 40px 40px; +} +.progress.active .bar { + -webkit-animation: progress-bar-stripes 2s linear infinite; + -moz-animation: progress-bar-stripes 2s linear infinite; + animation: progress-bar-stripes 2s linear infinite; +} +.progress-danger .bar { + background-color: #dd514c; + background-image: -moz-linear-gradient(top, #ee5f5b, #c43c35); + background-image: -ms-linear-gradient(top, #ee5f5b, #c43c35); + background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#ee5f5b), to(#c43c35)); + background-image: -webkit-linear-gradient(top, #ee5f5b, #c43c35); + background-image: -o-linear-gradient(top, #ee5f5b, #c43c35); + background-image: linear-gradient(top, #ee5f5b, #c43c35); + background-repeat: repeat-x; + filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#ee5f5b', endColorstr='#c43c35', GradientType=0); +} +.progress-danger.progress-striped .bar { + background-color: #ee5f5b; + background-image: -webkit-gradient(linear, 0 100%, 100% 0, color-stop(0.25, rgba(255, 255, 255, 0.15)), color-stop(0.25, transparent), color-stop(0.5, transparent), color-stop(0.5, rgba(255, 255, 255, 0.15)), color-stop(0.75, rgba(255, 255, 255, 0.15)), color-stop(0.75, transparent), to(transparent)); + background-image: -webkit-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: -moz-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: -ms-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: -o-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); +} +.progress-success .bar { + background-color: #5eb95e; + background-image: -moz-linear-gradient(top, #62c462, #57a957); + background-image: -ms-linear-gradient(top, #62c462, #57a957); + background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#62c462), to(#57a957)); + background-image: -webkit-linear-gradient(top, #62c462, #57a957); + background-image: -o-linear-gradient(top, #62c462, #57a957); + background-image: linear-gradient(top, #62c462, #57a957); + background-repeat: repeat-x; + filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#62c462', endColorstr='#57a957', GradientType=0); +} +.progress-success.progress-striped .bar { + background-color: #62c462; + background-image: -webkit-gradient(linear, 0 100%, 100% 0, color-stop(0.25, rgba(255, 255, 255, 0.15)), color-stop(0.25, transparent), color-stop(0.5, transparent), color-stop(0.5, rgba(255, 255, 255, 0.15)), color-stop(0.75, rgba(255, 255, 255, 0.15)), color-stop(0.75, transparent), to(transparent)); + background-image: -webkit-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: -moz-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: -ms-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: -o-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); +} +.progress-info .bar { + background-color: #4bb1cf; + background-image: -moz-linear-gradient(top, #5bc0de, #339bb9); + background-image: -ms-linear-gradient(top, #5bc0de, #339bb9); + background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#5bc0de), to(#339bb9)); + background-image: -webkit-linear-gradient(top, #5bc0de, #339bb9); + background-image: -o-linear-gradient(top, #5bc0de, #339bb9); + background-image: linear-gradient(top, #5bc0de, #339bb9); + background-repeat: repeat-x; + filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#5bc0de', endColorstr='#339bb9', GradientType=0); +} +.progress-info.progress-striped .bar { + background-color: #5bc0de; + background-image: -webkit-gradient(linear, 0 100%, 100% 0, color-stop(0.25, rgba(255, 255, 255, 0.15)), color-stop(0.25, transparent), color-stop(0.5, transparent), color-stop(0.5, rgba(255, 255, 255, 0.15)), color-stop(0.75, rgba(255, 255, 255, 0.15)), color-stop(0.75, transparent), to(transparent)); + background-image: -webkit-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: -moz-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: -ms-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: -o-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); +} +.progress-warning .bar { + background-color: #faa732; + background-image: -moz-linear-gradient(top, #fbb450, #f89406); + background-image: -ms-linear-gradient(top, #fbb450, #f89406); + background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#fbb450), to(#f89406)); + background-image: -webkit-linear-gradient(top, #fbb450, #f89406); + background-image: -o-linear-gradient(top, #fbb450, #f89406); + background-image: linear-gradient(top, #fbb450, #f89406); + background-repeat: repeat-x; + filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#fbb450', endColorstr='#f89406', GradientType=0); +} +.progress-warning.progress-striped .bar { + background-color: #fbb450; + background-image: -webkit-gradient(linear, 0 100%, 100% 0, color-stop(0.25, rgba(255, 255, 255, 0.15)), color-stop(0.25, transparent), color-stop(0.5, transparent), color-stop(0.5, rgba(255, 255, 255, 0.15)), color-stop(0.75, rgba(255, 255, 255, 0.15)), color-stop(0.75, transparent), to(transparent)); + background-image: -webkit-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: -moz-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: -ms-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: -o-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); +} +.accordion { + margin-bottom: 18px; +} +.accordion-group { + margin-bottom: 2px; + border: 1px solid #e5e5e5; + -webkit-border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; +} +.accordion-heading { + border-bottom: 0; +} +.accordion-heading .accordion-toggle { + display: block; + padding: 8px 15px; +} +.accordion-inner { + padding: 9px 15px; + border-top: 1px solid #e5e5e5; +} +.carousel { + position: relative; + margin-bottom: 18px; + line-height: 1; +} +.carousel-inner { + overflow: hidden; + width: 100%; + position: relative; +} +.carousel .item { + display: none; + position: relative; + -webkit-transition: 0.6s ease-in-out left; + -moz-transition: 0.6s ease-in-out left; + -ms-transition: 0.6s ease-in-out left; + -o-transition: 0.6s ease-in-out left; + transition: 0.6s ease-in-out left; +} +.carousel .item > img { + display: block; + line-height: 1; +} +.carousel .active, +.carousel .next, +.carousel .prev { + display: block; +} +.carousel .active { + left: 0; +} +.carousel .next, +.carousel .prev { + position: absolute; + top: 0; + width: 100%; +} +.carousel .next { + left: 100%; +} +.carousel .prev { + left: -100%; +} +.carousel .next.left, +.carousel .prev.right { + left: 0; +} +.carousel .active.left { + left: -100%; +} +.carousel .active.right { + left: 100%; +} +.carousel-control { + position: absolute; + top: 40%; + left: 15px; + width: 40px; + height: 40px; + margin-top: -20px; + font-size: 60px; + font-weight: 100; + line-height: 30px; + color: #ffffff; + text-align: center; + background: #222222; + border: 3px solid #ffffff; + -webkit-border-radius: 23px; + -moz-border-radius: 23px; + border-radius: 23px; + opacity: 0.5; + filter: alpha(opacity=50); +} +.carousel-control.right { + left: auto; + right: 15px; +} +.carousel-control:hover { + color: #ffffff; + text-decoration: none; + opacity: 0.9; + filter: alpha(opacity=90); +} +.carousel-caption { + position: absolute; + left: 0; + right: 0; + bottom: 0; + padding: 10px 15px 5px; + background: #333333; + background: rgba(0, 0, 0, 0.75); +} +.carousel-caption h4, +.carousel-caption p { + color: #ffffff; +} +.hero-unit { + padding: 60px; + margin-bottom: 30px; + background-color: #eeeeee; + -webkit-border-radius: 6px; + -moz-border-radius: 6px; + border-radius: 6px; +} +.hero-unit h1 { + margin-bottom: 0; + font-size: 60px; + line-height: 1; + color: inherit; + letter-spacing: -1px; +} +.hero-unit p { + font-size: 18px; + font-weight: 200; + line-height: 27px; + color: inherit; +} +.pull-right { + float: right; +} +.pull-left { + float: left; +} +.hide { + display: none; +} +.show { + display: block; +} +.invisible { + visibility: hidden; +} diff --git a/static/glyphicons-halflings-white.png b/static/glyphicons-halflings-white.png new file mode 100644 index 0000000000000000000000000000000000000000..a20760bfde58d1c92cee95116059fba03c68d689 GIT binary patch literal 4352 zcmd6r_dnEu|G?izMxtxU%uI5!l8nr<BF?zWUS(u;&WdwZC0F)1B-!J<$%*WB$U3Xi z$ta3LaXK6#>)ZF&&*%FGe4jtO*5mbhJzhV&et11z&&^B?xH$MZ007{+ZK!Jj01(PQ zJBFS4pH$0DefCd1HM@h*JNkcsi%oOXzj>qsEle$eQ7ApHL(XYdn5Y$Lk_3-J9p9d) zFeVfl3J47_g1XaoDXWsnBp9ZzZ74CI9RN-Nw{>+8A&#rBpZgc9WX2H3Ssv6doZP?t zS!g}lGvW1<9%?dj_G_x}3WUMN(8(x{a6_pd0yiUsf^67GGS50uSB*ORe5x6}qAf1z z@Q;2y4G{Lb?f21p)uTpChN&4q%^blZ2IsusUOhk)pe0<chGtjyTP-b6%vl?4F2xqG zOU>yxPD6oHKXWSj<y;3B&r^tK>v8&2pMdnegiQUtoXt1U0MmWAWu2&>3j$eb^qKNV z_(`JQZP&mXLT@U%-2rPy!7r|*Y1oAdlarltaUyq+yq^|d{B9_>t@Rd#@_KW9w_6P$ z^Dv8(Hi8pDJK{r0Iqq*va$cL=isZh0=1)wIoQ^vYPs$<T2#x2Kj^?$few0Pe4I~zZ zeAYbg0c0)2OtIx}d)C`Mw&~<64nQ!Uk8$^SW6e!?j1HfU4$&%i_`y~2R>(rBz$+DY z`y}1}`M%-da686<lVV-dk8h2*Tn8V7;-njKI(p4zUJy$ofY$z#INdRf(>`}zw_w>8 z!BcqxVTim*F)-}$segV$ON*!Zl~dhX@Rz^K2Xu<c1P8u4bp<yQO?OQj^dKZcE}xh_ z<z&gNJz{ZTTu3nGIcR;qG9;?^M0kG|PuThGH1+;j!xXDN6I_*@xL=@r$xRBuVh{MN zIUGEgxYJ(DFHKoLGF3_xPSW_^TT*1w(&gCNFdnv^AMnNFK6+ia>rh<1-vjImult%O z!-WXvkA_agVuhluW};J;#r>)?^uHS;G?a?j;(z?Y^FTwOA?tzLFvQDf&X8}9s7Wh< znEfd_vPyF_V`?>kR`w_h@+%59oKa;NPVGUo52QjisO-|$cYE(VNmm#+`#T5a;gh|Z z8A0^l3UwQMn0J3x<h`4-5?ApmemDp`8K)X6T0efPN*-~cf<tL>XWL7tY~Ox<iRkdJ zU|072zio5s?pAI0%Yx0uJh1f5i7VKWaFIaB;45=yji!1nH9<de2OLj_y{&41?nyPO zUrZT8xW#w*TQ5)($;JeSp2Pgrams&!r<Pe}#(LDg-blL{ESlmQ?a5Th4_;WRJR+4E zw6tQreDz+4bser4GB#?<roQ`hsw<hwcyHa9dkP0IO=6)WWkTxg{$NTm-b*c?j2_ul zyuRy=77P?tF`%S2aa=XEJa>Au=_hGvp@_%SZKA)ec-h-dfwIhS3jGBLL6e6Os;1LR zRDG&3TF`HV*n{&*H!oTSsLq!U5xV5!Yr6I_!*VhmwC3a2BOYfWH13AtVY|n5jv49e zcb0xCCZnt0i$>-S$k9J@-c!8wG#siu(Lg<MtkAtqhD8bV`jR^%b&>y_r1nfy+}!<h zAF+SdUhcuD`9zF%pRIHymB_I~)P%%~M=eQ#Ic#<Zr+NPzGTI`9;4khM^2h2PqMd?5 zGH>W9g-ucwp=&Hs1=Vs4i_q;dQL$8~Uq2BVA4o4uY!6}S`xH(Qec+{mJD~qgg@6W8 zipi@Z!ZR+Kr_)u&G);pG$tg$8#KPrsl&N3(m($NAU&9ogH9rVfW<4Mw>^7$&96g<9 zHQzekG9T5SS7DVm7EFY%CjChhfRyap4+d;+^0ng^B)~xKFG^7d2oOo|R8uY&S|X0@ znAGMb^rFQwGPTzsFQ8ZK4S@WO(8`6T+$Yt9{jGMd?jrTeb|_!Un`n9xDZu-fW+_aJ z4Uyy_$)`Ot!~doWUHW`(?F!iYvc5+g-(W9X<-tX*h%6(f;+A(OQ@w{WYSiq&pjKnN z)tSH~5g)03sKk)U+&GyP*?86fusX1ttpH1ng8ruC6UOddM~t>0wvZh}1cW%&7{tT$ zze(TwkA~V|_~nL{6YE#^RUC__Mx26zo*w(EfK2Q@R6xo`VkJKs^Eax`&*O*bw~*ap zyaqA_p(~(POY{H5+NIgewtB{|(%ML_wR8o);^XGTQ|{*J>74v>{_iyU;U*NTN}A%` z`8ltg(&furYlb!j%1ra!KPSiG<VRTwPDN9f5*7>mJ>f4c!bkAtjb_qmQ+aVB(QohO zRo@%)1krVtMPgkT6&3T*u`XO8pE&-!!u((3qVnraj|gN5aDxvqtrPs*MCZcO3i^Qt zI7$&BFr)50exhv11)82?u`ab0FgUSw;dpbnAtmz4k^&Nx`xMQ$5(JW}ry%)ry+DV> zS)TWjtXz7V6iK5$ghFuPiT>;;fAp)oy%%7grs4UwqU5+Ms96%`wU=YU5W-UGw(6iq z2GhB=Zw49;Yu<#7=soc@tZvYFIVNfkRPsCT&;76cYOONM<!9yYT8XS_j|<f)GAw6X z_w&Wq9xu5;px-$u*_Z^YS22HQpD*L|Z1fb)`d&qCQ^smb{5_5>wv!v*e#(X?l7eB- z&pWvVcaO;IKDg7C8bZ-+Hm`g>n_WC6%BL=CZlc``M{0T;%eYQ4t}V%m20okR=HET) z@)@WU_}tJOqiH7w2K%l<a?3NQ^6bZPnFJ<Mk`|jLP2*o$M^nx2160!F+h^quABnz; zAF6)v=cSvmebPJaPi4k%(nh|zGG@U(va!x`)nhbzOU0MkhuA%7v6ZH!EaE%H>pe0P z^FhhCX$ufUPCq4?C1A8ZSrVz=$~!VZ>;=kb8eaI;S1TKb|E9j*muthJe2||9pYYI$ zR@lkEo?K76^_v{llrL+?Swi1koJYJqG_-g!v?$ITb=q4#Rk--)f<yZAd%OCYe=RDW z4aV9=2rZm-rEPrLKA|1kuMv{%I=`DA(f6L;GQJ=_TAoYWBDl;}XZ0E+YfGjvp>ABD zh4Ibu7+f~5HEzy@7xo<qj_3c_D9C_vmh4{K98*=04-QLt1~2F@dBZe-l2GMsk#;A` zYHOcLf#^)Gn+{G3Q4YowOIK^&zQ|LTx89&c{IWvimdkFT8nJ{0X1}p;P(C>P^f$=} z+D3gYZ3W>%>m=U)p#UNOPPd&2cD&<J9<&QiV~vk5R%jVK^J1%HQ}`fxWs9c=2}L>; zxb{vXTzpCjcJAOEA_~=RX^_BM+_BYW*T{zzM(3TosvFOmf6Kp0IerP4`MuBgFdrkZ zf9X~m0O$toCckMn8klZDxWKr2%FHNk1VLQE)$!{Hz9{*a@TaZjC7kKsC1dIUx*6AQ zJFZc8p~!CewW(VvE@yaTPFt-6n+dZ@TM582m7=-#9JoDOH#zYPe{)-Lza89t+w#Zd zvQ3k$)Q)mPF)g)_+v$Gqgq~*RwGeBn{vhp!IPgkixW8WY)H`S{&~om!keO$Sum=oY zTatGW#*O^aVU<^!#et91z~$IYa;_C@J7+V)`<1b_lh`8FHOAgc=Az}lf)k%5xTMrv zr6uV%eKaU~wvi7pU)MeB7<DU@<PM)Ua&x<*j67UgrpKP|!tXx2R%YzH<LQn0XK>HK z2D;27Dik%)-q@hK-!I|N(cl`lAF^EIv0C-t$d1qtFnKIkcMW<4b%Lzf3Y+~~qB7`< zj);HTQS0Oex%zA170>?kRVA_m_*O?rZRpS3v{+O+cifN7Eb&>$Z==vGKh1V)C`qGu z_u8y<#N3Wp&$V^@T??GnE&RN^IyXM)r0h(gS3;b2pt0O!eNIt4{;3H~V5Ln7vs>8{ ziqqZL4Nwlvj4CtEv0>;Fw~D>LB_+-ecI)tiR%a!^GI3BawvNQGz4#b|_d<K40`zom zmZ%w0mYHcNzK(Ivg#;79zJA3Qs(emYQh|-Y&A>f&`e||2k;K}WnvU!Dx=0#ue(=U# zK&pYNNf5RQZOveUm+;dQ*FIA0&#`?@z*bBhUgr(n9_FpoHPB2pI8iMpW|sF*D{+75 z-k;nba~m^}=b7P$<BGu%3I<`>FAF1)S!oDKtNG-`%h{XQi6=SMH5GZ%8j?ugqt~!K zw<hNaHlewKU9pKh0n@^4X=DQ<4~UnDj4@h3>vA_m(*=EI<IgUo)z0l9R@mb|@QOas zWU>ssFVW0EZ;o=u#R5gBB$CUL+->U32;2PM2O(drij20XBy|hH+=bu!0*KIKBj%c+ z^{)B`3$NB2yp-IHf02C#Fw!(;S&rR%2P<?W3i)a{Hv71$$mqNwIwWJTc5XCVCY(ZM zZEUT%{m1IMAyv+ZxJdeiWsFSau%`*Ji4gu)?i`XAkA6AeCLD>q(!<`Q=u&+_V4eCe z?!d0m@n<F6bnzf#{rI&DDtbzb{#Q?q`iI`Fv^=Q#{GVsrKi@5H!=Yk{`KU+uXc?t@ zxGi_IMbsNpVL63R9MI#c?&2tT**S1&xk6UXV{?VrG2Vb8uwy$l2i~-P)jArRJvd+p zAMPX_jhyzm3a}Qc-9M){f2vD<`B3X9uKLW{DLodF&IsV$kXKT%@Qtp6|3s@S0+S=% zV+#X9n<D=<XzlauBx&tS1|?-doY!<IKSZPJ`vt2XRD)VP6|a+O3xDEZOZR$X3e5-S zuOL@^Te?HwRm63Ch16HfZ|^W=1@ax6$xAQ(4$2J*D69D!1&Ss_Wp=KanXxf%3)jB= zyl{(zRa6B4dz*qTVGFnQ#lf#G^~(Orm6*fvz@t#mixM85R=piy5ZZ)?<t2uZj~#Q1 z%87M&!_4Xmtg&aKmcnz`(+k~CS_9jg?1HcPF4&*jQGA1B5O}@9G995LTJuL|d}-c# zRi6~5UoNF~Ng3*RH>dhMu%QZ`ERBCD+uU~%h<WLJg$(5L-k}}ce*Ymz9%AWcG8~o) zrgMWKP5N71i-Vz&u9fBxjTT}~QT7=y$EdDt>>+E^Qd;Cz=IlGV(IwUrOz(+1Gkd7O z$HME|^+mAGBc4k(2jEj5$g30r-BUoK@Nn!*Td)5USoe+IZ-x9)#yd)sD}2Z?2{4@) zb|)xsK&pqOpB;+H#gbf^Pto29M<2Y>dU5pAF4p{+j=oBZ$2EXA*xI~AM@g20H7o_x z{2-Kc;SRpcxLXzU)a53ZoX%ndB^i8=>Sf&{i6CYkGSkvLj0<@C-!VKm#iX8dws__S zKp`T~rIAfaogJ!tV(~rs5)ctD#A};YXgPNI`<5=nWQjnIf<=1Pzn2y$C8yUkFKhwM z@%Ah?L`DM^@d<2evu->Oo=SVaiR<1GjYwe^G2)XY`l$Q%4H`|PpFA($N_8=6uOr0s zj+)C5x<cICx<i}#5D8LZ3LNFG7uU}%Q5<kbowYRV6Bs|^frDu{l2XM2Lj-Yh_!|?f z+a6@mRKb9j3p<Zh$+a4#UQQYhPF@-a9mWMpS)m;R6VEWV!i;mbS?{`eur*GS8_tX$ jEfLfZC2@~9k9g`Sv9u1yERTOL1mL!wsczLx=g0p8M%V6I literal 0 HcmV?d00001 diff --git a/static/glyphicons-halflings.png b/static/glyphicons-halflings.png new file mode 100644 index 0000000000000000000000000000000000000000..92d4445dfd0af414835467132cf50c7c38a303af GIT binary patch literal 4352 zcmc(jSvb@I*TDbCl4#mw&6;FnOR{7wTf|sqB70@Y*4Sf=t&%DGGDxy7<4<NH`!>in zwn`&QQOr<`27|~lU*GNfe)r$+;%v`3=Q$VW;ymZMrG+ssw-7e~0K7L%46Ffwh5XNs z<6`?KHS^P-{ZmgZZ@~?jOs2~JH%~nY@PG5j1zTI#0Amn(L8qe2oETm=+B^jogFL!D zS!ISRHW3ybWQ6o&?2=byQi)JhfBSH9PzL~<0B#!S!^50cUq25lRnLyYPq06zWw>~J z`$KJG?wJet%MCZ1y81U)c?UzG;{mBi?no2aAHvt8L__Xy66K$DAupSD_4^VSeG;vA zGhrY7dmCA}Zg<=d*dvUYvYMo40k!iu>o|-n)q^ld6Q(6yBtUWr1GY<4vK2?uoeS|r zT(a}}&NC3;#Lv8{0Y$f=#j|95fZYUrx?foCUQ)KvUf$-LSb+6D%%)z#|1KO+ZTgw~ zNbE_n|4p~xYoc$edOQF-XOS;%<r!#dmHF{5#RTzN2!T(FFMc;x+SmC=Km>evzdNi3 zk@(r9h#R5FpacG)j3VDRRz>g49u-o5A=@X`M=nQQ@W&MqFu3+}8)vIJ<N(sT_Zk8X zMLcU+@C0(GanqcI+g=S0kMDE|mIlGu&c=CozOm!OJr0PRi4D`Obo#+t^;Xncwa7ai zdh<9v@cF*U;YbI{iHB@gJAiGAx>yezf?(vDF#3iq72Yg1rU0$uCw``L1fzH6tU=MT zJ)FP#7~BMLoosB<>)Y`BnyxN?%PW`qwa_nrmk;P<^+|3lA$<ii8%uY~81lp=vs^qj zbHc@jPjA%v+=Qq|+H=tEesx$(-?7Mn9R7&2+ZkE|b0%rF{pOe&2PywxrLyZ}ob?{? zS!X14D0!!&R7j4z&a_ZX7E96o-d9#)-rDWl);JNdUKsSn^M1g(Sofin)_^D2A6fsk zK%N&KDHIEtjz^2e+RnzNElc?mvW&i)!L?OOITL^U!tz7HAYtpl+few+Se~$Nk0>cC z!KnRdI-*8rENgl-h*t3^hviocbR?_BCX&(%?-)#H*`RRAUES@w^(0ey@bvFIq^EE0 zYIYPpa4Xz>{9(cUIq~=IuByDHtJskc@OXkoyhOvqjT$BRxhihe#hq<$(TaV?g(bYx zzk*$b_y4xdrKd-u!#@W)7x%!%FE62JOZu)fTpnAUKW94KXQKo9lR9BoI`nN#BV<pu zN$Y&tINUw4JJ60wNhX=$oO%xnS0~8-36@e}lO69__j)7adZ<L2U#u5vwGeo2shUYF zH*Rf1efjD`jdvTV8a6X+&!xQkbfP<z!gz1jlz##Puuh>NL^WLc-2PBnDb`!FkQ6Yw zt8#VMCqN`vOx>8A-pqa3!sg7$vF4w|C29%3h5O_{d+D-|gED!U;S&A}5QU_Uz%?vp zmMBIPvj7qQQG74PJJYIU8KAgcJcJvNO0O6=%8w|@chXvpUX6O34cERMj)m?X)jwit zWYksusgx8zcrOv1Kd4Cm%yUoW#?wfM-ee=?*pXt7dU<wL(ECgNtn7KAcQSgjF$wec z&wNDxS$nw$r4-^(dj0lt)f7DU5?+TTQ7UFh7R=*xI5;Wr=aA7JB?^0SzgQ^V;4r`? zBrN-yp=!hwMFq0PE?Y!UWLSr9S4c>vyZrhI*Zx3!VQzm2&D<yRh#LVfjXeOPcj~wR z5UG;7Ix04MSLbA=`nZloXfY{`*@7=#K0}`VWppv~RO%H}$!V*DNHvZFBHUqfI?CD0 zbx!B4^9`#pqXl&iB{Pv^*lNn33}KeCeaE4o?M=ZBEL9o|=KG==a{vbsI4@1LO3@|! z=#F_^eo|k6WLCD`I?D^lB}ZeRa3j2$+MNG{fZN~d@a`$my6AxPBfp8Irx1gDj_8y_ zB{|_Ko-%@Zv$H~Px&z9e&#zqq`(8HmN?{uv#cDixDOJ%G_;k$j?o_(Za8|9R0~pd~ zhP6EvoFeWkI{=X$R-d0BaUhyb8w0in4s%stxoODXOl;El?W^#yR`?d86Ax#>k2i(z zv;J?=_W|Z`2Nb*9*m`XJ^1ixr>GY^eNXXM8UzHKbJ%`E&g=n<QM>C-&t%U{b2>k}4 zM^eC8z9@VJ)NO6~zgW94x7psn_*GsP&AXPV>|c7+3V*`GDl?NuNHOr8_5jSBY+FrJ zxxFy&omakmacj-wPLUexLeI~s2^i^7j<QS1^o69wqChX$OY6u{tW}exT*h=kf_UuP z+XaMs<6dAuy-kT^H%eXIYHYk4Q!FTjJ*&L%*Q})SYV#u;NgCV`gwN=QJ~!7t_q2+B zpbd_ZMR9D%dyk)}nec)ZXV~q^?S+kxZJj&X5@|w?zO<x_02M#Q3a*5JM8Y&n;d~#^ zX?>diy$lDh;U-ze^bf8Wq&_j48xx9sRj~I0?AI|l`&NRKa0xj_M7{QQP8x>W$llZ# z^2}mA)Bep^+iA@Qw-LK1wT3nbnW#j??18HOX9M~EwO_4MW54*U(nB|yBja(g7FnMC zblZNR)Y{`EcNWNZ9&#=!$@W#;-?`_@7{fb;%BTG<Be%)pb!CB`M;1FsO>aNt!jg%h zP{`+<{G!`T5|=OLq>Z*{Z2O&8zMn16ACVB$Qm``DYk?tjJdb2uC7aci<-`J?E%OU+ zGrN5UtA#%|w#4Z;NP?k$>n!<|SrjF%qnK<QD=|fvQ-`MgFRin=cJ~1?W$Nv-%7>36 z-X#tb9{hRfZswTsPVZBN8H~75sHKLYIz~6u+pKzy#crwlQTpM#$E~+Abk)TD#sz#v zXX8Go`ZaF>B8Zu%M9U<U?k5{O<y&QE7KlDa9?QUr-S}#I$LYUm81UoWaH<><;>RXE zbfFb@39Y9#&~E%DMKl*GIPjFwcNZ7nuMbVEpA0WbvBjM9QA!sp{YiDoe131&NawG0 z)w7{^`zTTBX*b%&r|n~U@dMgnxo!))g;D+Qg=`Xw5@VHk^{hiH?Dbc#u;gsXHzn0i z2)8o6*&Kl>6tpGG-xYv<M}QNBKQ@Z8AUtKe=QqbSl$Amw(w@PJ2Fl*B4kD#B1X|@h zND6v-C(>B-r`9coW<<#c<0|E=wQpY(XerrkkfVOt!t*N?wvbI|9F@&~JQ7q2jXe2H zCW^MvkWX8I-=%fo@BdI{A^py@pAB`s<yjfB3(la;jxJW|8b9;qtmahyAaiMpzZU^P zxD>hd&A{*amKE*X!a7A2Yu?Z%f;af$36@t#hgGI$UAqZQr>(vfUM3&C0L=d07kpTV z65hXXqa6SYLUvQ%beIm#w8HN~d3!4?$?iB2Owr|ut8l>>rMSqaZB}JGncrpN>H)eX z?`{XC$$(nou>9J>y&RJ_GCHrPS%%Jr+GeZ-p;^lV`1YLmyxKN-u#7+}dnx}N%zgXH z$CV1rQyi4eN)t(4&9Ix9{_jMeW*4;LYis@>9EQ2Es^gfy-VKyn0lc8i{7q3yuQV}F zD6Fom;2?qz@ukzYpge~g8?BAWbC}{;E82F=WrGc<q3x&8B^qmty_aky%YQ{CKTGq< zYP!kE(69SylMU^oAELgld(|`QSIDWIzU`!z4rh5Kn4EmCqu{yU{SIwx=mqDK8w<~1 zUPFy^`6*;La<HSR(O`c-+NrbAEnz=wxz=;F=D$%Gr5~UQ*wG%^^eW0ENv91u_qR-a z$S)u&@oi_Fi#yBZUxTms_h&AvlAOS|`l_14f97W-V>0;?er)DQ&9VG84bSn{>9B(k zwM%!e%*jQ~?@0DuS;yYC#^~O_E+}d7VN;GP%ockmCFlj4DNZ%yl_X-Hn$v_=+Er1z z)xF^ugN@xFweaki3bVXB3?uwjsn55R<b|OgeId~Hv@}>D1&YMi6B+jBAEU6|0Y1ne zLxbyOnkM9BHX2f}bHa<7WG>P_pz=aP(B)D(uo1i&yvId9DaA3GTsK?WdG%g5Q5z-% zUfT;wH`Xu@LDvM>F<4<`LiFUdk7UO)oS&1>Rnv!81;V#S1gZ^;byAIw5fmjY3m)nw z?+@SmlmBCWV>bFM8|-jGB{WLeI3o9DaWo<)11@8`kh*v=cN0DNB+st4sz6R#2I0qi z4c&8ZcAexDoiEyzoZJ((D9)8bG%^Z+MCs@_Q)++#Uvn&7#CI<7^ioFM{2qLTEAfMX z#1kD>oACS6EsTK8F}{R&pahvhyt|}$lX5-EzVP=!*jL*U(=7^7%UUF#`g>m(9)4uh zN+-O*&B&PgYQ520)x+!;$#)PXM`Kgq-o1CQLPsDGuSVi?k7|gIEtmv^WewHMkLAio zl1Us*ZM8T5*j_cED4OCIiNDZ{(dj&{3{g&T+~4Y*L((GimlI~v8Q&*2;zNurHxdEX zDgWY5T-u#~Rw6AH53<&eUOA_3sJa+<`S@61`0Z+&gPPC(dA9xY-3vCHs+QQ8y<*H| zq`~2~B6ACGIIhlq0<JP>$V=$vE_&HDcwxCpLD6$_1>ZT*h{SQByL1NMw0+fOj?Wz& zFvJdbQkbJBeJ=wX#hUle7%rUXR$4yPWhM|#t(`DrC+d#^K8*!sRn%{Eee5S%bqSan z?Gaxb6y6;Dw^4Ura3@7~UnV3ahsAZxfc!%uwqZbo@PGj7@>ji1sVn}8fiB(aiz~Jo zTDXK*@oVh~gVo^Iu~o8PQNMj6)RalL?o3^H@pnjZNLWoX&@@;gDJHvX&C-&SZCkAF z?Pux@B3eZQ037cWb&FZMuP+XLz1yG`s8)?SoCs!ygWlxG$PB`Eka2i37Fv)TK{|58 zJti;S=?xo)8?eTei(HD#<H{`dIBo}QZ*qye7Ch&8W=G`>f`Jq8j>vX~5NRzRU9sf_ z>oxtdr~$>ax+OJ;^X)vsSztp0JYJsoQlX{)JP`NN^%4mv6u3oW-hBTdM2W@5-Fze> z9n9nd!<vn@x)+DSqur{lShQR5c_q20z&z9X_VI@tF-sZITiJ8(=%yDq%20jBZq4o? zgCC2nZ#R@cyO{hJ?i_$meOX?m;pkq%(#414r`r1hpFn%A^?fTAk~P~=C0`Omj7x)= z_=sB}!Gp5B>;qg7R6d&M#&&}CPAvA|mF^4XPltG`XZl9!t)5o^flxcEGJRDAZjOjF zQ0Iea%DG$E3bP&!(93|2RCY3l5t3s3J*JOik0=hGeaJ@3@H8tD7<k9<<dKwp&eQ6Z z9|U0$hb)b5lItCim6MC_Nf&^qL{S0zjAEPdi{G~l$mUBpQVcZOtKq$za5*WnwuQO{ zxF$NXUlSh-TEr%CuFbjgKX@wV^CqEZM<ObXOWagY0q?8j*FR)BnR)!IQXA#2X-7RS zQDDqU9@ib_?%osL+z(HZl~m@gbUVL(W{K>CVRqHg&`+R3j0a8@kqB}PI}{$m!yRab zvul5lL(>3*TF>n~)*#hsmwUTtKRAA2Fnk0PENdI!9GrZLu@zyKzs+&m-IKFviqv>& kg1Lm#gqI~e;$iYPkmG5c&N-g{UI@TVLkokN>#mRg2V?7pi2wiq literal 0 HcmV?d00001 From 1192e305c7fa7ba0b6572cc8c450127d6458b0af Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Fri, 27 Jul 2012 04:37:29 -0400 Subject: [PATCH 132/331] update to newer version needed by bootstrap --- static/jquery.full.js | 4435 ++++++++++++++++++++++------------------- 1 file changed, 2429 insertions(+), 2006 deletions(-) diff --git a/static/jquery.full.js b/static/jquery.full.js index f3201aacb6..3774ff9861 100644 --- a/static/jquery.full.js +++ b/static/jquery.full.js @@ -1,5 +1,5 @@ /*! - * jQuery JavaScript Library v1.6.2 + * jQuery JavaScript Library v1.7.2 * http://jquery.com/ * * Copyright 2011, John Resig @@ -11,7 +11,7 @@ * Copyright 2011, The Dojo Foundation * Released under the MIT, BSD, and GPL Licenses. * - * Date: Thu Jun 30 14:16:56 2011 -0400 + * Date: Wed Mar 21 12:46:34 2012 -0700 */ (function( window, undefined ) { @@ -37,8 +37,8 @@ var jQuery = function( selector, context ) { rootjQuery, // A simple way to check for HTML strings or ID strings - // (both of which we optimize for) - quickExpr = /^(?:[^<]*(<[\w\W]+>)[^>]*$|#([\w\-]*)$)/, + // Prioritize #id over <tag> to avoid XSS via location.hash (#9521) + quickExpr = /^(?:[^#<]*(<[\w\W]+>)[^>]*$|#([\w\-]*)$)/, // Check if a string has a non-whitespace character in it rnotwhite = /\S/, @@ -47,9 +47,6 @@ var jQuery = function( selector, context ) { trimLeft = /^\s+/, trimRight = /\s+$/, - // Check for digits - rdigit = /\d/, - // Match a standalone tag rsingleTag = /^<(\w+)\s*\/?>(?:<\/\1>)?$/, @@ -66,11 +63,12 @@ var jQuery = function( selector, context ) { rmozilla = /(mozilla)(?:.*? rv:([\w.]+))?/, // Matches dashed string for camelizing - rdashAlpha = /-([a-z])/ig, + rdashAlpha = /-([a-z]|[0-9])/ig, + rmsPrefix = /^-ms-/, // Used by jQuery.camelCase as callback to replace() fcamelCase = function( all, letter ) { - return letter.toUpperCase(); + return ( letter + "" ).toUpperCase(); }, // Keep a UserAgent string for use with jQuery.browser @@ -139,7 +137,7 @@ jQuery.fn = jQuery.prototype = { // HANDLE: $(html) -> $(array) if ( match[1] ) { context = context instanceof jQuery ? context[0] : context; - doc = (context ? context.ownerDocument || context : document); + doc = ( context ? context.ownerDocument || context : document ); // If a single string is passed in and it's a single tag // just do a createElement and skip the rest @@ -156,7 +154,7 @@ jQuery.fn = jQuery.prototype = { } else { ret = jQuery.buildFragment( [ match[1] ], [ doc ] ); - selector = (ret.cacheable ? jQuery.clone(ret.fragment) : ret.fragment).childNodes; + selector = ( ret.cacheable ? jQuery.clone(ret.fragment) : ret.fragment ).childNodes; } return jQuery.merge( this, selector ); @@ -186,7 +184,7 @@ jQuery.fn = jQuery.prototype = { // HANDLE: $(expr, $(...)) } else if ( !context || context.jquery ) { - return (context || rootjQuery).find( selector ); + return ( context || rootjQuery ).find( selector ); // HANDLE: $(expr, context) // (which is just equivalent to: $(context).find(expr) @@ -200,7 +198,7 @@ jQuery.fn = jQuery.prototype = { return rootjQuery.ready( selector ); } - if (selector.selector !== undefined) { + if ( selector.selector !== undefined ) { this.selector = selector.selector; this.context = selector.context; } @@ -212,7 +210,7 @@ jQuery.fn = jQuery.prototype = { selector: "", // The current version of jQuery being used - jquery: "1.6.2", + jquery: "1.7.2", // The default length of a jQuery object is 0 length: 0, @@ -257,7 +255,7 @@ jQuery.fn = jQuery.prototype = { ret.context = this.context; if ( name === "find" ) { - ret.selector = this.selector + (this.selector ? " " : "") + selector; + ret.selector = this.selector + ( this.selector ? " " : "" ) + selector; } else if ( name ) { ret.selector = this.selector + "." + name + "(" + selector + ")"; } @@ -278,15 +276,16 @@ jQuery.fn = jQuery.prototype = { jQuery.bindReady(); // Add the callback - readyList.done( fn ); + readyList.add( fn ); return this; }, eq: function( i ) { + i = +i; return i === -1 ? this.slice( i ) : - this.slice( i, +i + 1 ); + this.slice( i, i + 1 ); }, first: function() { @@ -433,11 +432,11 @@ jQuery.extend({ } // If there are functions bound, to execute - readyList.resolveWith( document, [ jQuery ] ); + readyList.fireWith( document, [ jQuery ] ); // Trigger any bound ready events if ( jQuery.fn.trigger ) { - jQuery( document ).trigger( "ready" ).unbind( "ready" ); + jQuery( document ).trigger( "ready" ).off( "ready" ); } } }, @@ -447,7 +446,7 @@ jQuery.extend({ return; } - readyList = jQuery._Deferred(); + readyList = jQuery.Callbacks( "once memory" ); // Catch cases where $(document).ready() is called after the // browser event has already occurred. @@ -498,13 +497,12 @@ jQuery.extend({ return jQuery.type(obj) === "array"; }, - // A crude way of determining if an object is a window isWindow: function( obj ) { - return obj && typeof obj === "object" && "setInterval" in obj; + return obj != null && obj == obj.window; }, - isNaN: function( obj ) { - return obj == null || !rdigit.test( obj ) || isNaN( obj ); + isNumeric: function( obj ) { + return !isNaN( parseFloat(obj) ) && isFinite( obj ); }, type: function( obj ) { @@ -521,10 +519,15 @@ jQuery.extend({ return false; } - // Not own constructor property must be Object - if ( obj.constructor && - !hasOwn.call(obj, "constructor") && - !hasOwn.call(obj.constructor.prototype, "isPrototypeOf") ) { + try { + // Not own constructor property must be Object + if ( obj.constructor && + !hasOwn.call(obj, "constructor") && + !hasOwn.call(obj.constructor.prototype, "isPrototypeOf") ) { + return false; + } + } catch ( e ) { + // IE8,9 Will throw exceptions on certain host objects #9897 return false; } @@ -545,7 +548,7 @@ jQuery.extend({ }, error: function( msg ) { - throw msg; + throw new Error( msg ); }, parseJSON: function( data ) { @@ -567,31 +570,33 @@ jQuery.extend({ .replace( rvalidtokens, "]" ) .replace( rvalidbraces, "")) ) { - return (new Function( "return " + data ))(); + return ( new Function( "return " + data ) )(); } jQuery.error( "Invalid JSON: " + data ); }, // Cross-browser xml parsing - // (xml & tmp used internally) - parseXML: function( data , xml , tmp ) { - - if ( window.DOMParser ) { // Standard - tmp = new DOMParser(); - xml = tmp.parseFromString( data , "text/xml" ); - } else { // IE - xml = new ActiveXObject( "Microsoft.XMLDOM" ); - xml.async = "false"; - xml.loadXML( data ); + parseXML: function( data ) { + if ( typeof data !== "string" || !data ) { + return null; } - - tmp = xml.documentElement; - - if ( ! tmp || ! tmp.nodeName || tmp.nodeName === "parsererror" ) { + var xml, tmp; + try { + if ( window.DOMParser ) { // Standard + tmp = new DOMParser(); + xml = tmp.parseFromString( data , "text/xml" ); + } else { // IE + xml = new ActiveXObject( "Microsoft.XMLDOM" ); + xml.async = "false"; + xml.loadXML( data ); + } + } catch( e ) { + xml = undefined; + } + if ( !xml || !xml.documentElement || xml.getElementsByTagName( "parsererror" ).length ) { jQuery.error( "Invalid XML: " + data ); } - return xml; }, @@ -611,10 +616,10 @@ jQuery.extend({ } }, - // Converts a dashed string to camelCased string; - // Used by both the css and data modules + // Convert dashed to camelCase; used by the css and data modules + // Microsoft forgot to hump their vendor prefix (#9572) camelCase: function( string ) { - return string.replace( rdashAlpha, fcamelCase ); + return string.replace( rmsPrefix, "ms-" ).replace( rdashAlpha, fcamelCase ); }, nodeName: function( elem, name ) { @@ -683,8 +688,6 @@ jQuery.extend({ if ( array != null ) { // The window, strings (and functions) also have 'length' - // The extra typeof function check is to prevent crashes - // in Safari 2 (See: #3039) // Tweaked logic slightly to handle Blackberry 4.7 RegExp issues #6930 var type = jQuery.type( array ); @@ -698,15 +701,22 @@ jQuery.extend({ return ret; }, - inArray: function( elem, array ) { + inArray: function( elem, array, i ) { + var len; - if ( indexOf ) { - return indexOf.call( array, elem ); - } + if ( array ) { + if ( indexOf ) { + return indexOf.call( array, elem, i ); + } - for ( var i = 0, length = array.length; i < length; i++ ) { - if ( array[ i ] === elem ) { - return i; + len = array.length; + i = i ? i < 0 ? Math.max( 0, len + i ) : i : 0; + + for ( ; i < len; i++ ) { + // Skip accessing in sparse arrays + if ( i in array && array[ i ] === elem ) { + return i; + } } } @@ -814,35 +824,59 @@ jQuery.extend({ // Mutifunctional method to get and set values to a collection // The value/s can optionally be executed if it's a function - access: function( elems, key, value, exec, fn, pass ) { - var length = elems.length; + access: function( elems, fn, key, value, chainable, emptyGet, pass ) { + var exec, + bulk = key == null, + i = 0, + length = elems.length; - // Setting many attributes - if ( typeof key === "object" ) { - for ( var k in key ) { - jQuery.access( elems, k, key[k], exec, fn, value ); + // Sets many values + if ( key && typeof key === "object" ) { + for ( i in key ) { + jQuery.access( elems, fn, i, key[i], 1, emptyGet, value ); } - return elems; - } + chainable = 1; - // Setting one attribute - if ( value !== undefined ) { + // Sets one value + } else if ( value !== undefined ) { // Optionally, function values get executed if exec is true - exec = !pass && exec && jQuery.isFunction(value); + exec = pass === undefined && jQuery.isFunction( value ); - for ( var i = 0; i < length; i++ ) { - fn( elems[i], key, exec ? value.call( elems[i], i, fn( elems[i], key ) ) : value, pass ); + if ( bulk ) { + // Bulk operations only iterate when executing function values + if ( exec ) { + exec = fn; + fn = function( elem, key, value ) { + return exec.call( jQuery( elem ), value ); + }; + + // Otherwise they run against the entire set + } else { + fn.call( elems, value ); + fn = null; + } } - return elems; + if ( fn ) { + for (; i < length; i++ ) { + fn( elems[i], key, exec ? value.call( elems[i], i, fn( elems[i], key ) ) : value, pass ); + } + } + + chainable = 1; } - // Getting an attribute - return length ? fn( elems[0], key ) : undefined; + return chainable ? + elems : + + // Gets + bulk ? + fn.call( elems ) : + length ? fn( elems[0], key ) : emptyGet; }, now: function() { - return (new Date()).getTime(); + return ( new Date() ).getTime(); }, // Use of jQuery.browser is frowned upon. @@ -949,188 +983,363 @@ return jQuery; })(); -var // Promise methods - promiseMethods = "done fail isResolved isRejected promise then always pipe".split( " " ), - // Static reference to slice +// String to Object flags format cache +var flagsCache = {}; + +// Convert String-formatted flags into Object-formatted ones and store in cache +function createFlags( flags ) { + var object = flagsCache[ flags ] = {}, + i, length; + flags = flags.split( /\s+/ ); + for ( i = 0, length = flags.length; i < length; i++ ) { + object[ flags[i] ] = true; + } + return object; +} + +/* + * Create a callback list using the following parameters: + * + * flags: an optional list of space-separated flags that will change how + * the callback list behaves + * + * By default a callback list will act like an event callback list and can be + * "fired" multiple times. + * + * Possible flags: + * + * once: will ensure the callback list can only be fired once (like a Deferred) + * + * memory: will keep track of previous values and will call any callback added + * after the list has been fired right away with the latest "memorized" + * values (like a Deferred) + * + * unique: will ensure a callback can only be added once (no duplicate in the list) + * + * stopOnFalse: interrupt callings when a callback returns false + * + */ +jQuery.Callbacks = function( flags ) { + + // Convert flags from String-formatted to Object-formatted + // (we check in cache first) + flags = flags ? ( flagsCache[ flags ] || createFlags( flags ) ) : {}; + + var // Actual callback list + list = [], + // Stack of fire calls for repeatable lists + stack = [], + // Last fire value (for non-forgettable lists) + memory, + // Flag to know if list was already fired + fired, + // Flag to know if list is currently firing + firing, + // First callback to fire (used internally by add and fireWith) + firingStart, + // End of the loop when firing + firingLength, + // Index of currently firing callback (modified by remove if needed) + firingIndex, + // Add one or several callbacks to the list + add = function( args ) { + var i, + length, + elem, + type, + actual; + for ( i = 0, length = args.length; i < length; i++ ) { + elem = args[ i ]; + type = jQuery.type( elem ); + if ( type === "array" ) { + // Inspect recursively + add( elem ); + } else if ( type === "function" ) { + // Add if not in unique mode and callback is not in + if ( !flags.unique || !self.has( elem ) ) { + list.push( elem ); + } + } + } + }, + // Fire callbacks + fire = function( context, args ) { + args = args || []; + memory = !flags.memory || [ context, args ]; + fired = true; + firing = true; + firingIndex = firingStart || 0; + firingStart = 0; + firingLength = list.length; + for ( ; list && firingIndex < firingLength; firingIndex++ ) { + if ( list[ firingIndex ].apply( context, args ) === false && flags.stopOnFalse ) { + memory = true; // Mark as halted + break; + } + } + firing = false; + if ( list ) { + if ( !flags.once ) { + if ( stack && stack.length ) { + memory = stack.shift(); + self.fireWith( memory[ 0 ], memory[ 1 ] ); + } + } else if ( memory === true ) { + self.disable(); + } else { + list = []; + } + } + }, + // Actual Callbacks object + self = { + // Add a callback or a collection of callbacks to the list + add: function() { + if ( list ) { + var length = list.length; + add( arguments ); + // Do we need to add the callbacks to the + // current firing batch? + if ( firing ) { + firingLength = list.length; + // With memory, if we're not firing then + // we should call right away, unless previous + // firing was halted (stopOnFalse) + } else if ( memory && memory !== true ) { + firingStart = length; + fire( memory[ 0 ], memory[ 1 ] ); + } + } + return this; + }, + // Remove a callback from the list + remove: function() { + if ( list ) { + var args = arguments, + argIndex = 0, + argLength = args.length; + for ( ; argIndex < argLength ; argIndex++ ) { + for ( var i = 0; i < list.length; i++ ) { + if ( args[ argIndex ] === list[ i ] ) { + // Handle firingIndex and firingLength + if ( firing ) { + if ( i <= firingLength ) { + firingLength--; + if ( i <= firingIndex ) { + firingIndex--; + } + } + } + // Remove the element + list.splice( i--, 1 ); + // If we have some unicity property then + // we only need to do this once + if ( flags.unique ) { + break; + } + } + } + } + } + return this; + }, + // Control if a given callback is in the list + has: function( fn ) { + if ( list ) { + var i = 0, + length = list.length; + for ( ; i < length; i++ ) { + if ( fn === list[ i ] ) { + return true; + } + } + } + return false; + }, + // Remove all callbacks from the list + empty: function() { + list = []; + return this; + }, + // Have the list do nothing anymore + disable: function() { + list = stack = memory = undefined; + return this; + }, + // Is it disabled? + disabled: function() { + return !list; + }, + // Lock the list in its current state + lock: function() { + stack = undefined; + if ( !memory || memory === true ) { + self.disable(); + } + return this; + }, + // Is it locked? + locked: function() { + return !stack; + }, + // Call all callbacks with the given context and arguments + fireWith: function( context, args ) { + if ( stack ) { + if ( firing ) { + if ( !flags.once ) { + stack.push( [ context, args ] ); + } + } else if ( !( flags.once && memory ) ) { + fire( context, args ); + } + } + return this; + }, + // Call all the callbacks with the given arguments + fire: function() { + self.fireWith( this, arguments ); + return this; + }, + // To know if the callbacks have already been called at least once + fired: function() { + return !!fired; + } + }; + + return self; +}; + + + + +var // Static reference to slice sliceDeferred = [].slice; jQuery.extend({ - // Create a simple deferred (one callbacks list) - _Deferred: function() { - var // callbacks list - callbacks = [], - // stored [ context , args ] - fired, - // to avoid firing when already doing so - firing, - // flag to know if the deferred has been cancelled - cancelled, - // the deferred itself - deferred = { - // done( f1, f2, ...) - done: function() { - if ( !cancelled ) { - var args = arguments, - i, - length, - elem, - type, - _fired; - if ( fired ) { - _fired = fired; - fired = 0; - } - for ( i = 0, length = args.length; i < length; i++ ) { - elem = args[ i ]; - type = jQuery.type( elem ); - if ( type === "array" ) { - deferred.done.apply( deferred, elem ); - } else if ( type === "function" ) { - callbacks.push( elem ); - } - } - if ( _fired ) { - deferred.resolveWith( _fired[ 0 ], _fired[ 1 ] ); - } - } - return this; - }, - - // resolve with given context and args - resolveWith: function( context, args ) { - if ( !cancelled && !fired && !firing ) { - // make sure args are available (#8421) - args = args || []; - firing = 1; - try { - while( callbacks[ 0 ] ) { - callbacks.shift().apply( context, args ); - } - } - finally { - fired = [ context, args ]; - firing = 0; - } - } - return this; - }, - - // resolve with this as context and given arguments - resolve: function() { - deferred.resolveWith( this, arguments ); - return this; - }, - - // Has this deferred been resolved? - isResolved: function() { - return !!( firing || fired ); - }, - - // Cancel - cancel: function() { - cancelled = 1; - callbacks = []; - return this; - } - }; - - return deferred; - }, - - // Full fledged deferred (two callbacks list) Deferred: function( func ) { - var deferred = jQuery._Deferred(), - failDeferred = jQuery._Deferred(), - promise; - // Add errorDeferred methods, then and promise - jQuery.extend( deferred, { - then: function( doneCallbacks, failCallbacks ) { - deferred.done( doneCallbacks ).fail( failCallbacks ); - return this; + var doneList = jQuery.Callbacks( "once memory" ), + failList = jQuery.Callbacks( "once memory" ), + progressList = jQuery.Callbacks( "memory" ), + state = "pending", + lists = { + resolve: doneList, + reject: failList, + notify: progressList }, - always: function() { - return deferred.done.apply( deferred, arguments ).fail.apply( this, arguments ); - }, - fail: failDeferred.done, - rejectWith: failDeferred.resolveWith, - reject: failDeferred.resolve, - isRejected: failDeferred.isResolved, - pipe: function( fnDone, fnFail ) { - return jQuery.Deferred(function( newDefer ) { - jQuery.each( { - done: [ fnDone, "resolve" ], - fail: [ fnFail, "reject" ] - }, function( handler, data ) { - var fn = data[ 0 ], - action = data[ 1 ], - returned; - if ( jQuery.isFunction( fn ) ) { - deferred[ handler ](function() { - returned = fn.apply( this, arguments ); - if ( returned && jQuery.isFunction( returned.promise ) ) { - returned.promise().then( newDefer.resolve, newDefer.reject ); - } else { - newDefer[ action ]( returned ); - } - }); - } else { - deferred[ handler ]( newDefer[ action ] ); + promise = { + done: doneList.add, + fail: failList.add, + progress: progressList.add, + + state: function() { + return state; + }, + + // Deprecated + isResolved: doneList.fired, + isRejected: failList.fired, + + then: function( doneCallbacks, failCallbacks, progressCallbacks ) { + deferred.done( doneCallbacks ).fail( failCallbacks ).progress( progressCallbacks ); + return this; + }, + always: function() { + deferred.done.apply( deferred, arguments ).fail.apply( deferred, arguments ); + return this; + }, + pipe: function( fnDone, fnFail, fnProgress ) { + return jQuery.Deferred(function( newDefer ) { + jQuery.each( { + done: [ fnDone, "resolve" ], + fail: [ fnFail, "reject" ], + progress: [ fnProgress, "notify" ] + }, function( handler, data ) { + var fn = data[ 0 ], + action = data[ 1 ], + returned; + if ( jQuery.isFunction( fn ) ) { + deferred[ handler ](function() { + returned = fn.apply( this, arguments ); + if ( returned && jQuery.isFunction( returned.promise ) ) { + returned.promise().then( newDefer.resolve, newDefer.reject, newDefer.notify ); + } else { + newDefer[ action + "With" ]( this === deferred ? newDefer : this, [ returned ] ); + } + }); + } else { + deferred[ handler ]( newDefer[ action ] ); + } + }); + }).promise(); + }, + // Get a promise for this deferred + // If obj is provided, the promise aspect is added to the object + promise: function( obj ) { + if ( obj == null ) { + obj = promise; + } else { + for ( var key in promise ) { + obj[ key ] = promise[ key ]; } - }); - }).promise(); - }, - // Get a promise for this deferred - // If obj is provided, the promise aspect is added to the object - promise: function( obj ) { - if ( obj == null ) { - if ( promise ) { - return promise; } - promise = obj = {}; + return obj; } - var i = promiseMethods.length; - while( i-- ) { - obj[ promiseMethods[i] ] = deferred[ promiseMethods[i] ]; - } - return obj; - } - }); - // Make sure only one callback list will be used - deferred.done( failDeferred.cancel ).fail( deferred.cancel ); - // Unexpose cancel - delete deferred.cancel; + }, + deferred = promise.promise({}), + key; + + for ( key in lists ) { + deferred[ key ] = lists[ key ].fire; + deferred[ key + "With" ] = lists[ key ].fireWith; + } + + // Handle state + deferred.done( function() { + state = "resolved"; + }, failList.disable, progressList.lock ).fail( function() { + state = "rejected"; + }, doneList.disable, progressList.lock ); + // Call given func if any if ( func ) { func.call( deferred, deferred ); } + + // All done! return deferred; }, // Deferred helper when: function( firstParam ) { - var args = arguments, + var args = sliceDeferred.call( arguments, 0 ), i = 0, length = args.length, + pValues = new Array( length ), count = length, + pCount = length, deferred = length <= 1 && firstParam && jQuery.isFunction( firstParam.promise ) ? firstParam : - jQuery.Deferred(); + jQuery.Deferred(), + promise = deferred.promise(); function resolveFunc( i ) { return function( value ) { args[ i ] = arguments.length > 1 ? sliceDeferred.call( arguments, 0 ) : value; if ( !( --count ) ) { - // Strange bug in FF4: - // Values changed onto the arguments object sometimes end up as undefined values - // outside the $.when method. Cloning the object into a fresh array solves the issue - deferred.resolveWith( deferred, sliceDeferred.call( args, 0 ) ); + deferred.resolveWith( deferred, args ); } }; } + function progressFunc( i ) { + return function( value ) { + pValues[ i ] = arguments.length > 1 ? sliceDeferred.call( arguments, 0 ) : value; + deferred.notifyWith( promise, pValues ); + }; + } if ( length > 1 ) { - for( ; i < length; i++ ) { - if ( args[ i ] && jQuery.isFunction( args[ i ].promise ) ) { - args[ i ].promise().then( resolveFunc(i), deferred.reject ); + for ( ; i < length; i++ ) { + if ( args[ i ] && args[ i ].promise && jQuery.isFunction( args[ i ].promise ) ) { + args[ i ].promise().then( resolveFunc(i), deferred.reject, progressFunc(i) ); } else { --count; } @@ -1141,33 +1350,29 @@ jQuery.extend({ } else if ( deferred !== firstParam ) { deferred.resolveWith( deferred, length ? [ firstParam ] : [] ); } - return deferred.promise(); + return promise; } }); + jQuery.support = (function() { - var div = document.createElement( "div" ), - documentElement = document.documentElement, + var support, all, a, select, opt, input, - marginDiv, - support, fragment, - body, - testElementParent, - testElement, - testElementStyle, tds, events, eventName, i, - isSupported; + isSupported, + div = document.createElement( "div" ), + documentElement = document.documentElement; // Preliminary tests div.setAttribute("className", "t"); @@ -1192,11 +1397,11 @@ jQuery.support = (function() { // Make sure that tbody elements aren't automatically inserted // IE will insert them into empty tables - tbody: !div.getElementsByTagName( "tbody" ).length, + tbody: !div.getElementsByTagName("tbody").length, // Make sure that link elements get serialized correctly by innerHTML // This requires a wrapper element in IE - htmlSerialize: !!div.getElementsByTagName( "link" ).length, + htmlSerialize: !!div.getElementsByTagName("link").length, // Get the style information from getAttribute // (IE uses .cssText instead) @@ -1204,12 +1409,12 @@ jQuery.support = (function() { // Make sure that URLs aren't manipulated // (IE normalizes it by default) - hrefNormalized: ( a.getAttribute( "href" ) === "/a" ), + hrefNormalized: ( a.getAttribute("href") === "/a" ), // Make sure that element opacity exists // (IE uses filter instead) // Use a regex to work around a WebKit issue. See #5145 - opacity: /^0.55$/.test( a.style.opacity ), + opacity: /^0.55/.test( a.style.opacity ), // Verify style float existence // (IE uses styleFloat instead of cssFloat) @@ -1227,6 +1432,13 @@ jQuery.support = (function() { // Test setAttribute on camelCase class. If it works, we need attrFixes when doing get/setAttribute (ie6/7) getSetAttribute: div.className !== "t", + // Tests for enctype support on a form(#6743) + enctype: !!document.createElement("form").enctype, + + // Makes sure cloning an html5 element does not cause problems + // Where outerHTML is undefined, this still works + html5Clone: document.createElement("nav").cloneNode( true ).outerHTML !== "<:nav></:nav>", + // Will be defined later submitBubbles: true, changeBubbles: true, @@ -1235,9 +1447,13 @@ jQuery.support = (function() { noCloneEvent: true, inlineBlockNeedsLayout: false, shrinkWrapBlocks: false, - reliableMarginRight: true + reliableMarginRight: true, + pixelMargin: true }; + // jQuery.boxModel DEPRECATED in 1.3, use jQuery.support.boxModel instead + jQuery.boxModel = support.boxModel = (document.compatMode === "CSS1Compat"); + // Make sure checked status is properly cloned input.checked = true; support.noCloneChecked = input.cloneNode( true ).checked; @@ -1264,7 +1480,7 @@ jQuery.support = (function() { div.cloneNode( true ).fireEvent( "onclick" ); } - // Check if a radio maintains it's value + // Check if a radio maintains its value // after being appended to the DOM input = document.createElement("input"); input.value = "t"; @@ -1272,115 +1488,36 @@ jQuery.support = (function() { support.radioValue = input.value === "t"; input.setAttribute("checked", "checked"); + + // #11217 - WebKit loses check when the name is after the checked attribute + input.setAttribute( "name", "t" ); + div.appendChild( input ); fragment = document.createDocumentFragment(); - fragment.appendChild( div.firstChild ); + fragment.appendChild( div.lastChild ); // WebKit doesn't clone checked state correctly in fragments support.checkClone = fragment.cloneNode( true ).cloneNode( true ).lastChild.checked; - div.innerHTML = ""; - - // Figure out if the W3C box model works as expected - div.style.width = div.style.paddingLeft = "1px"; - - body = document.getElementsByTagName( "body" )[ 0 ]; - // We use our own, invisible, body unless the body is already present - // in which case we use a div (#9239) - testElement = document.createElement( body ? "div" : "body" ); - testElementStyle = { - visibility: "hidden", - width: 0, - height: 0, - border: 0, - margin: 0 - }; - if ( body ) { - jQuery.extend( testElementStyle, { - position: "absolute", - left: -1000, - top: -1000 - }); - } - for ( i in testElementStyle ) { - testElement.style[ i ] = testElementStyle[ i ]; - } - testElement.appendChild( div ); - testElementParent = body || documentElement; - testElementParent.insertBefore( testElement, testElementParent.firstChild ); - // Check if a disconnected checkbox will retain its checked // value of true after appended to the DOM (IE6/7) support.appendChecked = input.checked; - support.boxModel = div.offsetWidth === 2; - - if ( "zoom" in div.style ) { - // Check if natively block-level elements act like inline-block - // elements when setting their display to 'inline' and giving - // them layout - // (IE < 8 does this) - div.style.display = "inline"; - div.style.zoom = 1; - support.inlineBlockNeedsLayout = ( div.offsetWidth === 2 ); - - // Check if elements with layout shrink-wrap their children - // (IE 6 does this) - div.style.display = ""; - div.innerHTML = "<div style='width:4px;'></div>"; - support.shrinkWrapBlocks = ( div.offsetWidth !== 2 ); - } - - div.innerHTML = "<table><tr><td style='padding:0;border:0;display:none'></td><td>t</td></tr></table>"; - tds = div.getElementsByTagName( "td" ); - - // Check if table cells still have offsetWidth/Height when they are set - // to display:none and there are still other visible table cells in a - // table row; if so, offsetWidth/Height are not reliable for use when - // determining if an element has been hidden directly using - // display:none (it is still safe to use offsets if a parent element is - // hidden; don safety goggles and see bug #4512 for more information). - // (only IE 8 fails this test) - isSupported = ( tds[ 0 ].offsetHeight === 0 ); - - tds[ 0 ].style.display = ""; - tds[ 1 ].style.display = "none"; - - // Check if empty table cells still have offsetWidth/Height - // (IE < 8 fail this test) - support.reliableHiddenOffsets = isSupported && ( tds[ 0 ].offsetHeight === 0 ); - div.innerHTML = ""; - - // Check if div with explicit width and no margin-right incorrectly - // gets computed margin-right based on width of container. For more - // info see bug #3333 - // Fails in WebKit before Feb 2011 nightlies - // WebKit Bug 13343 - getComputedStyle returns wrong value for margin-right - if ( document.defaultView && document.defaultView.getComputedStyle ) { - marginDiv = document.createElement( "div" ); - marginDiv.style.width = "0"; - marginDiv.style.marginRight = "0"; - div.appendChild( marginDiv ); - support.reliableMarginRight = - ( parseInt( ( document.defaultView.getComputedStyle( marginDiv, null ) || { marginRight: 0 } ).marginRight, 10 ) || 0 ) === 0; - } - - // Remove the body element we added - testElement.innerHTML = ""; - testElementParent.removeChild( testElement ); + fragment.removeChild( input ); + fragment.appendChild( div ); // Technique from Juriy Zaytsev - // http://thinkweb2.com/projects/prototype/detecting-event-support-without-browser-sniffing/ + // http://perfectionkills.com/detecting-event-support-without-browser-sniffing/ // We only care about the case where non-standard event systems // are used, namely in IE. Short-circuiting here helps us to // avoid an eval call (in setAttribute) which can cause CSP // to go haywire. See: https://developer.mozilla.org/en/Security/CSP if ( div.attachEvent ) { - for( i in { + for ( i in { submit: 1, change: 1, focusin: 1 - } ) { + }) { eventName = "on" + i; isSupported = ( eventName in div ); if ( !isSupported ) { @@ -1391,20 +1528,143 @@ jQuery.support = (function() { } } - // Null connected elements to avoid leaks in IE - testElement = fragment = select = opt = body = marginDiv = div = input = null; + fragment.removeChild( div ); + + // Null elements to avoid leaks in IE + fragment = select = opt = div = input = null; + + // Run tests that need a body at doc ready + jQuery(function() { + var container, outer, inner, table, td, offsetSupport, + marginDiv, conMarginTop, style, html, positionTopLeftWidthHeight, + paddingMarginBorderVisibility, paddingMarginBorder, + body = document.getElementsByTagName("body")[0]; + + if ( !body ) { + // Return for frameset docs that don't have a body + return; + } + + conMarginTop = 1; + paddingMarginBorder = "padding:0;margin:0;border:"; + positionTopLeftWidthHeight = "position:absolute;top:0;left:0;width:1px;height:1px;"; + paddingMarginBorderVisibility = paddingMarginBorder + "0;visibility:hidden;"; + style = "style='" + positionTopLeftWidthHeight + paddingMarginBorder + "5px solid #000;"; + html = "<div " + style + "display:block;'><div style='" + paddingMarginBorder + "0;display:block;overflow:hidden;'></div></div>" + + "<table " + style + "' cellpadding='0' cellspacing='0'>" + + "<tr><td></td></tr></table>"; + + container = document.createElement("div"); + container.style.cssText = paddingMarginBorderVisibility + "width:0;height:0;position:static;top:0;margin-top:" + conMarginTop + "px"; + body.insertBefore( container, body.firstChild ); + + // Construct the test element + div = document.createElement("div"); + container.appendChild( div ); + + // Check if table cells still have offsetWidth/Height when they are set + // to display:none and there are still other visible table cells in a + // table row; if so, offsetWidth/Height are not reliable for use when + // determining if an element has been hidden directly using + // display:none (it is still safe to use offsets if a parent element is + // hidden; don safety goggles and see bug #4512 for more information). + // (only IE 8 fails this test) + div.innerHTML = "<table><tr><td style='" + paddingMarginBorder + "0;display:none'></td><td>t</td></tr></table>"; + tds = div.getElementsByTagName( "td" ); + isSupported = ( tds[ 0 ].offsetHeight === 0 ); + + tds[ 0 ].style.display = ""; + tds[ 1 ].style.display = "none"; + + // Check if empty table cells still have offsetWidth/Height + // (IE <= 8 fail this test) + support.reliableHiddenOffsets = isSupported && ( tds[ 0 ].offsetHeight === 0 ); + + // Check if div with explicit width and no margin-right incorrectly + // gets computed margin-right based on width of container. For more + // info see bug #3333 + // Fails in WebKit before Feb 2011 nightlies + // WebKit Bug 13343 - getComputedStyle returns wrong value for margin-right + if ( window.getComputedStyle ) { + div.innerHTML = ""; + marginDiv = document.createElement( "div" ); + marginDiv.style.width = "0"; + marginDiv.style.marginRight = "0"; + div.style.width = "2px"; + div.appendChild( marginDiv ); + support.reliableMarginRight = + ( parseInt( ( window.getComputedStyle( marginDiv, null ) || { marginRight: 0 } ).marginRight, 10 ) || 0 ) === 0; + } + + if ( typeof div.style.zoom !== "undefined" ) { + // Check if natively block-level elements act like inline-block + // elements when setting their display to 'inline' and giving + // them layout + // (IE < 8 does this) + div.innerHTML = ""; + div.style.width = div.style.padding = "1px"; + div.style.border = 0; + div.style.overflow = "hidden"; + div.style.display = "inline"; + div.style.zoom = 1; + support.inlineBlockNeedsLayout = ( div.offsetWidth === 3 ); + + // Check if elements with layout shrink-wrap their children + // (IE 6 does this) + div.style.display = "block"; + div.style.overflow = "visible"; + div.innerHTML = "<div style='width:5px;'></div>"; + support.shrinkWrapBlocks = ( div.offsetWidth !== 3 ); + } + + div.style.cssText = positionTopLeftWidthHeight + paddingMarginBorderVisibility; + div.innerHTML = html; + + outer = div.firstChild; + inner = outer.firstChild; + td = outer.nextSibling.firstChild.firstChild; + + offsetSupport = { + doesNotAddBorder: ( inner.offsetTop !== 5 ), + doesAddBorderForTableAndCells: ( td.offsetTop === 5 ) + }; + + inner.style.position = "fixed"; + inner.style.top = "20px"; + + // safari subtracts parent border width here which is 5px + offsetSupport.fixedPosition = ( inner.offsetTop === 20 || inner.offsetTop === 15 ); + inner.style.position = inner.style.top = ""; + + outer.style.overflow = "hidden"; + outer.style.position = "relative"; + + offsetSupport.subtractsBorderForOverflowNotVisible = ( inner.offsetTop === -5 ); + offsetSupport.doesNotIncludeMarginInBodyOffset = ( body.offsetTop !== conMarginTop ); + + if ( window.getComputedStyle ) { + div.style.marginTop = "1%"; + support.pixelMargin = ( window.getComputedStyle( div, null ) || { marginTop: 0 } ).marginTop !== "1%"; + } + + if ( typeof container.style.zoom !== "undefined" ) { + container.style.zoom = 1; + } + + body.removeChild( container ); + marginDiv = div = container = null; + + jQuery.extend( support, offsetSupport ); + }); return support; })(); -// Keep track of boxModel -jQuery.boxModel = jQuery.support.boxModel; - var rbrace = /^(?:\{.*\}|\[.*\])$/, - rmultiDash = /([a-z])([A-Z])/g; + rmultiDash = /([A-Z])/g; jQuery.extend({ cache: {}, @@ -1427,7 +1687,6 @@ jQuery.extend({ hasData: function( elem ) { elem = elem.nodeType ? jQuery.cache[ elem[jQuery.expando] ] : elem[ jQuery.expando ]; - return !!elem && !isEmptyDataObject( elem ); }, @@ -1436,7 +1695,9 @@ jQuery.extend({ return; } - var internalKey = jQuery.expando, getByName = typeof name === "string", thisCache, + var privateCache, thisCache, ret, + internalKey = jQuery.expando, + getByName = typeof name === "string", // We have to handle DOM nodes and JS objects differently because IE6-7 // can't GC object references properly across the DOM-JS boundary @@ -1448,11 +1709,12 @@ jQuery.extend({ // Only defining an ID for JS objects if its cache already exists allows // the code to shortcut on the same path as a DOM node with no cache - id = isNode ? elem[ jQuery.expando ] : elem[ jQuery.expando ] && jQuery.expando; + id = isNode ? elem[ internalKey ] : elem[ internalKey ] && internalKey, + isEvents = name === "events"; // Avoid doing any more work than we need to when trying to get data on an // object that has no data at all - if ( (!id || (pvt && id && !cache[ id ][ internalKey ])) && getByName && data === undefined ) { + if ( (!id || !cache[id] || (!isEvents && !pvt && !cache[id].data)) && getByName && data === undefined ) { return; } @@ -1460,18 +1722,17 @@ jQuery.extend({ // Only DOM nodes need a new unique ID for each element since their data // ends up in the global cache if ( isNode ) { - elem[ jQuery.expando ] = id = ++jQuery.uuid; + elem[ internalKey ] = id = ++jQuery.uuid; } else { - id = jQuery.expando; + id = internalKey; } } if ( !cache[ id ] ) { cache[ id ] = {}; - // TODO: This is a hack for 1.5 ONLY. Avoids exposing jQuery - // metadata on plain JS objects when the object is serialized using - // JSON.stringify + // Avoids exposing jQuery metadata on plain JS objects when the object + // is serialized using JSON.stringify if ( !isNode ) { cache[ id ].toJSON = jQuery.noop; } @@ -1481,40 +1742,53 @@ jQuery.extend({ // shallow copied over onto the existing cache if ( typeof name === "object" || typeof name === "function" ) { if ( pvt ) { - cache[ id ][ internalKey ] = jQuery.extend(cache[ id ][ internalKey ], name); + cache[ id ] = jQuery.extend( cache[ id ], name ); } else { - cache[ id ] = jQuery.extend(cache[ id ], name); + cache[ id ].data = jQuery.extend( cache[ id ].data, name ); } } - thisCache = cache[ id ]; + privateCache = thisCache = cache[ id ]; - // Internal jQuery data is stored in a separate object inside the object's data + // jQuery data() is stored in a separate object inside the object's internal data // cache in order to avoid key collisions between internal data and user-defined - // data - if ( pvt ) { - if ( !thisCache[ internalKey ] ) { - thisCache[ internalKey ] = {}; + // data. + if ( !pvt ) { + if ( !thisCache.data ) { + thisCache.data = {}; } - thisCache = thisCache[ internalKey ]; + thisCache = thisCache.data; } if ( data !== undefined ) { thisCache[ jQuery.camelCase( name ) ] = data; } - // TODO: This is a hack for 1.5 ONLY. It will be removed in 1.6. Users should - // not attempt to inspect the internal events object using jQuery.data, as this - // internal data object is undocumented and subject to change. - if ( name === "events" && !thisCache[name] ) { - return thisCache[ internalKey ] && thisCache[ internalKey ].events; + // Users should not attempt to inspect the internal events object using jQuery.data, + // it is undocumented and subject to change. But does anyone listen? No. + if ( isEvents && !thisCache[ name ] ) { + return privateCache.events; } - return getByName ? - // Check for both converted-to-camel and non-converted data property names - thisCache[ jQuery.camelCase( name ) ] || thisCache[ name ] : - thisCache; + // Check for both converted-to-camel and non-converted data property names + // If a data property was specified + if ( getByName ) { + + // First Try to find as-is property data + ret = thisCache[ name ]; + + // Test for null|undefined property data + if ( ret == null ) { + + // Try to find the camelCased property + ret = thisCache[ jQuery.camelCase( name ) ]; + } + } else { + ret = thisCache; + } + + return ret; }, removeData: function( elem, name, pvt /* Internal Use Only */ ) { @@ -1522,13 +1796,18 @@ jQuery.extend({ return; } - var internalKey = jQuery.expando, isNode = elem.nodeType, + var thisCache, i, l, + + // Reference to internal data cache key + internalKey = jQuery.expando, + + isNode = elem.nodeType, // See jQuery.data for more information cache = isNode ? jQuery.cache : elem, // See jQuery.data for more information - id = isNode ? elem[ jQuery.expando ] : jQuery.expando; + id = isNode ? elem[ internalKey ] : internalKey; // If there is already no cache entry for this object, there is no // purpose in continuing @@ -1537,22 +1816,44 @@ jQuery.extend({ } if ( name ) { - var thisCache = pvt ? cache[ id ][ internalKey ] : cache[ id ]; + + thisCache = pvt ? cache[ id ] : cache[ id ].data; if ( thisCache ) { - delete thisCache[ name ]; + + // Support array or space separated string names for data keys + if ( !jQuery.isArray( name ) ) { + + // try the string as a key before any manipulation + if ( name in thisCache ) { + name = [ name ]; + } else { + + // split the camel cased version by spaces unless a key with the spaces exists + name = jQuery.camelCase( name ); + if ( name in thisCache ) { + name = [ name ]; + } else { + name = name.split( " " ); + } + } + } + + for ( i = 0, l = name.length; i < l; i++ ) { + delete thisCache[ name[i] ]; + } // If there is no data left in the cache, we want to continue // and let the cache object itself get destroyed - if ( !isEmptyDataObject(thisCache) ) { + if ( !( pvt ? isEmptyDataObject : jQuery.isEmptyObject )( thisCache ) ) { return; } } } // See jQuery.data for more information - if ( pvt ) { - delete cache[ id ][ internalKey ]; + if ( !pvt ) { + delete cache[ id ].data; // Don't destroy the parent cache unless the internal data object // had been the only thing left in it @@ -1561,43 +1862,28 @@ jQuery.extend({ } } - var internalCache = cache[ id ][ internalKey ]; - // Browsers that fail expando deletion also refuse to delete expandos on // the window, but it will allow it on all other JS objects; other browsers // don't care - if ( jQuery.support.deleteExpando || cache != window ) { + // Ensure that `cache` is not a window object #10080 + if ( jQuery.support.deleteExpando || !cache.setInterval ) { delete cache[ id ]; } else { cache[ id ] = null; } - // We destroyed the entire user cache at once because it's faster than - // iterating through each key, but we need to continue to persist internal - // data if it existed - if ( internalCache ) { - cache[ id ] = {}; - // TODO: This is a hack for 1.5 ONLY. Avoids exposing jQuery - // metadata on plain JS objects when the object is serialized using - // JSON.stringify - if ( !isNode ) { - cache[ id ].toJSON = jQuery.noop; - } - - cache[ id ][ internalKey ] = internalCache; - - // Otherwise, we need to eliminate the expando on the node to avoid + // We destroyed the cache and need to eliminate the expando on the node to avoid // false lookups in the cache for entries that no longer exist - } else if ( isNode ) { + if ( isNode ) { // IE does not allow us to delete expando properties from nodes, // nor does it have a removeAttribute function on Document nodes; // we must handle all of these cases if ( jQuery.support.deleteExpando ) { - delete elem[ jQuery.expando ]; + delete elem[ internalKey ]; } else if ( elem.removeAttribute ) { - elem.removeAttribute( jQuery.expando ); + elem.removeAttribute( internalKey ); } else { - elem[ jQuery.expando ] = null; + elem[ internalKey ] = null; } } }, @@ -1623,60 +1909,70 @@ jQuery.extend({ jQuery.fn.extend({ data: function( key, value ) { - var data = null; + var parts, part, attr, name, l, + elem = this[0], + i = 0, + data = null; - if ( typeof key === "undefined" ) { + // Gets all values + if ( key === undefined ) { if ( this.length ) { - data = jQuery.data( this[0] ); + data = jQuery.data( elem ); - if ( this[0].nodeType === 1 ) { - var attr = this[0].attributes, name; - for ( var i = 0, l = attr.length; i < l; i++ ) { + if ( elem.nodeType === 1 && !jQuery._data( elem, "parsedAttrs" ) ) { + attr = elem.attributes; + for ( l = attr.length; i < l; i++ ) { name = attr[i].name; if ( name.indexOf( "data-" ) === 0 ) { name = jQuery.camelCase( name.substring(5) ); - dataAttr( this[0], name, data[ name ] ); + dataAttr( elem, name, data[ name ] ); } } + jQuery._data( elem, "parsedAttrs", true ); } } return data; + } - } else if ( typeof key === "object" ) { + // Sets multiple values + if ( typeof key === "object" ) { return this.each(function() { jQuery.data( this, key ); }); } - var parts = key.split("."); + parts = key.split( ".", 2 ); parts[1] = parts[1] ? "." + parts[1] : ""; + part = parts[1] + "!"; - if ( value === undefined ) { - data = this.triggerHandler("getData" + parts[1] + "!", [parts[0]]); + return jQuery.access( this, function( value ) { - // Try to fetch any internally stored data first - if ( data === undefined && this.length ) { - data = jQuery.data( this[0], key ); - data = dataAttr( this[0], key, data ); + if ( value === undefined ) { + data = this.triggerHandler( "getData" + part, [ parts[0] ] ); + + // Try to fetch any internally stored data first + if ( data === undefined && elem ) { + data = jQuery.data( elem, key ); + data = dataAttr( elem, key, data ); + } + + return data === undefined && parts[1] ? + this.data( parts[0] ) : + data; } - return data === undefined && parts[1] ? - this.data( parts[0] ) : - data; + parts[1] = value; + this.each(function() { + var self = jQuery( this ); - } else { - return this.each(function() { - var $this = jQuery( this ), - args = [ parts[0], value ]; - - $this.triggerHandler( "setData" + parts[1] + "!", args ); + self.triggerHandler( "setData" + part, parts ); jQuery.data( this, key, value ); - $this.triggerHandler( "changeData" + parts[1] + "!", args ); + self.triggerHandler( "changeData" + part, parts ); }); - } + }, null, value, arguments.length > 1, null, false ); }, removeData: function( key ) { @@ -1690,7 +1986,8 @@ function dataAttr( elem, key, data ) { // If nothing was found internally, try to fetch any // data from the HTML5 data-* attribute if ( data === undefined && elem.nodeType === 1 ) { - var name = "data-" + key.replace( rmultiDash, "$1-$2" ).toLowerCase(); + + var name = "data-" + key.replace( rmultiDash, "-$1" ).toLowerCase(); data = elem.getAttribute( name ); @@ -1699,7 +1996,7 @@ function dataAttr( elem, key, data ) { data = data === "true" ? true : data === "false" ? false : data === "null" ? null : - !jQuery.isNaN( data ) ? parseFloat( data ) : + jQuery.isNumeric( data ) ? +data : rbrace.test( data ) ? jQuery.parseJSON( data ) : data; } catch( e ) {} @@ -1715,11 +2012,14 @@ function dataAttr( elem, key, data ) { return data; } -// TODO: This is a hack for 1.5 ONLY to allow objects with a single toJSON -// property to be considered empty objects; this property always exists in -// order to make sure JSON.stringify does not expose internal metadata +// checks a cache object for emptiness function isEmptyDataObject( obj ) { for ( var name in obj ) { + + // if the public data object is empty, the private is still empty + if ( name === "data" && jQuery.isEmptyObject( obj[name] ) ) { + continue; + } if ( name !== "toJSON" ) { return false; } @@ -1735,17 +2035,17 @@ function handleQueueMarkDefer( elem, type, src ) { var deferDataKey = type + "defer", queueDataKey = type + "queue", markDataKey = type + "mark", - defer = jQuery.data( elem, deferDataKey, undefined, true ); + defer = jQuery._data( elem, deferDataKey ); if ( defer && - ( src === "queue" || !jQuery.data( elem, queueDataKey, undefined, true ) ) && - ( src === "mark" || !jQuery.data( elem, markDataKey, undefined, true ) ) ) { + ( src === "queue" || !jQuery._data(elem, queueDataKey) ) && + ( src === "mark" || !jQuery._data(elem, markDataKey) ) ) { // Give room for hard-coded callbacks to fire first // and eventually mark/queue something else on the element setTimeout( function() { - if ( !jQuery.data( elem, queueDataKey, undefined, true ) && - !jQuery.data( elem, markDataKey, undefined, true ) ) { + if ( !jQuery._data( elem, queueDataKey ) && + !jQuery._data( elem, markDataKey ) ) { jQuery.removeData( elem, deferDataKey, true ); - defer.resolve(); + defer.fire(); } }, 0 ); } @@ -1755,8 +2055,8 @@ jQuery.extend({ _mark: function( elem, type ) { if ( elem ) { - type = (type || "fx") + "mark"; - jQuery.data( elem, type, (jQuery.data(elem,type,undefined,true) || 0) + 1, true ); + type = ( type || "fx" ) + "mark"; + jQuery._data( elem, type, (jQuery._data( elem, type ) || 0) + 1 ); } }, @@ -1769,9 +2069,9 @@ jQuery.extend({ if ( elem ) { type = type || "fx"; var key = type + "mark", - count = force ? 0 : ( (jQuery.data( elem, key, undefined, true) || 1 ) - 1 ); + count = force ? 0 : ( (jQuery._data( elem, key ) || 1) - 1 ); if ( count ) { - jQuery.data( elem, key, count, true ); + jQuery._data( elem, key, count ); } else { jQuery.removeData( elem, key, true ); handleQueueMarkDefer( elem, type, "mark" ); @@ -1780,13 +2080,15 @@ jQuery.extend({ }, queue: function( elem, type, data ) { + var q; if ( elem ) { - type = (type || "fx") + "queue"; - var q = jQuery.data( elem, type, undefined, true ); + type = ( type || "fx" ) + "queue"; + q = jQuery._data( elem, type ); + // Speed up dequeue by getting out quickly if this is just a lookup if ( data ) { if ( !q || jQuery.isArray(data) ) { - q = jQuery.data( elem, type, jQuery.makeArray(data), true ); + q = jQuery._data( elem, type, jQuery.makeArray(data) ); } else { q.push( data ); } @@ -1800,7 +2102,7 @@ jQuery.extend({ var queue = jQuery.queue( elem, type ), fn = queue.shift(), - defer; + hooks = {}; // If the fx queue is dequeued, always remove the progress sentinel if ( fn === "inprogress" ) { @@ -1811,16 +2113,17 @@ jQuery.extend({ // Add a progress sentinel to prevent the fx queue from being // automatically dequeued if ( type === "fx" ) { - queue.unshift("inprogress"); + queue.unshift( "inprogress" ); } - fn.call(elem, function() { - jQuery.dequeue(elem, type); - }); + jQuery._data( elem, type + ".run", hooks ); + fn.call( elem, function() { + jQuery.dequeue( elem, type ); + }, hooks ); } if ( !queue.length ) { - jQuery.removeData( elem, type + "queue", true ); + jQuery.removeData( elem, type + "queue " + type + ".run", true ); handleQueueMarkDefer( elem, type, "queue" ); } } @@ -1828,21 +2131,27 @@ jQuery.extend({ jQuery.fn.extend({ queue: function( type, data ) { + var setter = 2; + if ( typeof type !== "string" ) { data = type; type = "fx"; + setter--; } - if ( data === undefined ) { + if ( arguments.length < setter ) { return jQuery.queue( this[0], type ); } - return this.each(function() { - var queue = jQuery.queue( this, type, data ); - if ( type === "fx" && queue[0] !== "inprogress" ) { - jQuery.dequeue( this, type ); - } - }); + return data === undefined ? + this : + this.each(function() { + var queue = jQuery.queue( this, type, data ); + + if ( type === "fx" && queue[0] !== "inprogress" ) { + jQuery.dequeue( this, type ); + } + }); }, dequeue: function( type ) { return this.each(function() { @@ -1852,14 +2161,14 @@ jQuery.fn.extend({ // Based off of the plugin by Clint Helfers, with permission. // http://blindsignals.com/index.php/2009/07/jquery-delay/ delay: function( time, type ) { - time = jQuery.fx ? jQuery.fx.speeds[time] || time : time; + time = jQuery.fx ? jQuery.fx.speeds[ time ] || time : time; type = type || "fx"; - return this.queue( type, function() { - var elem = this; - setTimeout(function() { - jQuery.dequeue( elem, type ); - }, time ); + return this.queue( type, function( next, hooks ) { + var timeout = setTimeout( next, time ); + hooks.stop = function() { + clearTimeout( timeout ); + }; }); }, clearQueue: function( type ) { @@ -1890,13 +2199,13 @@ jQuery.fn.extend({ if (( tmp = jQuery.data( elements[ i ], deferDataKey, undefined, true ) || ( jQuery.data( elements[ i ], queueDataKey, undefined, true ) || jQuery.data( elements[ i ], markDataKey, undefined, true ) ) && - jQuery.data( elements[ i ], deferDataKey, jQuery._Deferred(), true ) )) { + jQuery.data( elements[ i ], deferDataKey, jQuery.Callbacks( "once memory" ), true ) )) { count++; - tmp.done( resolve ); + tmp.add( resolve ); } } resolve(); - return defer.promise(); + return defer.promise( object ); } }); @@ -1910,12 +2219,12 @@ var rclass = /[\n\t\r]/g, rfocusable = /^(?:button|input|object|select|textarea)$/i, rclickable = /^a(?:rea)?$/i, rboolean = /^(?:autofocus|autoplay|async|checked|controls|defer|disabled|hidden|loop|multiple|open|readonly|required|scoped|selected)$/i, - rinvalidChar = /\:|^on/, - formHook, boolHook; + getSetAttribute = jQuery.support.getSetAttribute, + nodeHook, boolHook, fixSpecified; jQuery.fn.extend({ attr: function( name, value ) { - return jQuery.access( this, name, value, true, jQuery.attr ); + return jQuery.access( this, jQuery.attr, name, value, arguments.length > 1 ); }, removeAttr: function( name ) { @@ -1923,11 +2232,11 @@ jQuery.fn.extend({ jQuery.removeAttr( this, name ); }); }, - + prop: function( name, value ) { - return jQuery.access( this, name, value, true, jQuery.prop ); + return jQuery.access( this, jQuery.prop, name, value, arguments.length > 1 ); }, - + removeProp: function( name ) { name = jQuery.propFix[ name ] || name; return this.each(function() { @@ -1986,7 +2295,7 @@ jQuery.fn.extend({ } if ( (value && typeof value === "string") || value === undefined ) { - classNames = (value || "").split( rspace ); + classNames = ( value || "" ).split( rspace ); for ( i = 0, l = this.length; i < l; i++ ) { elem = this[ i ]; @@ -2047,9 +2356,11 @@ jQuery.fn.extend({ }, hasClass: function( selector ) { - var className = " " + selector + " "; - for ( var i = 0, l = this.length; i < l; i++ ) { - if ( (" " + this[i].className + " ").replace(rclass, " ").indexOf( className ) > -1 ) { + var className = " " + selector + " ", + i = 0, + l = this.length; + for ( ; i < l; i++ ) { + if ( this[i].nodeType === 1 && (" " + this[i].className + " ").replace(rclass, " ").indexOf( className ) > -1 ) { return true; } } @@ -2058,12 +2369,12 @@ jQuery.fn.extend({ }, val: function( value ) { - var hooks, ret, + var hooks, ret, isFunction, elem = this[0]; - + if ( !arguments.length ) { if ( elem ) { - hooks = jQuery.valHooks[ elem.nodeName.toLowerCase() ] || jQuery.valHooks[ elem.type ]; + hooks = jQuery.valHooks[ elem.type ] || jQuery.valHooks[ elem.nodeName.toLowerCase() ]; if ( hooks && "get" in hooks && (ret = hooks.get( elem, "value" )) !== undefined ) { return ret; @@ -2071,17 +2382,17 @@ jQuery.fn.extend({ ret = elem.value; - return typeof ret === "string" ? + return typeof ret === "string" ? // handle most common string cases - ret.replace(rreturn, "") : + ret.replace(rreturn, "") : // handle cases where value is null/undef or number ret == null ? "" : ret; } - return undefined; + return; } - var isFunction = jQuery.isFunction( value ); + isFunction = jQuery.isFunction( value ); return this.each(function( i ) { var self = jQuery(this), val; @@ -2107,7 +2418,7 @@ jQuery.fn.extend({ }); } - hooks = jQuery.valHooks[ this.nodeName.toLowerCase() ] || jQuery.valHooks[ this.type ]; + hooks = jQuery.valHooks[ this.type ] || jQuery.valHooks[ this.nodeName.toLowerCase() ]; // If set returns undefined, fall back to normal setting if ( !hooks || !("set" in hooks) || hooks.set( this, val, "value" ) === undefined ) { @@ -2129,7 +2440,7 @@ jQuery.extend({ }, select: { get: function( elem ) { - var value, + var value, i, max, option, index = elem.selectedIndex, values = [], options = elem.options, @@ -2141,8 +2452,10 @@ jQuery.extend({ } // Loop through all the selected options - for ( var i = one ? index : 0, max = one ? index + 1 : options.length; i < max; i++ ) { - var option = options[ i ]; + i = one ? index : 0; + max = one ? index + 1 : options.length; + for ( ; i < max; i++ ) { + option = options[ i ]; // Don't return options that are disabled or in a disabled optgroup if ( option.selected && (jQuery.support.optDisabled ? !option.disabled : option.getAttribute("disabled") === null) && @@ -2194,18 +2507,14 @@ jQuery.extend({ height: true, offset: true }, - - attrFix: { - // Always normalize to ensure hook usage - tabindex: "tabIndex" - }, - + attr: function( elem, name, value, pass ) { - var nType = elem.nodeType; - + var ret, hooks, notxml, + nType = elem.nodeType; + // don't get/set attributes on text, comment and attribute nodes if ( !elem || nType === 3 || nType === 8 || nType === 2 ) { - return undefined; + return; } if ( pass && name in jQuery.attrFn ) { @@ -2213,39 +2522,24 @@ jQuery.extend({ } // Fallback to prop when attributes are not supported - if ( !("getAttribute" in elem) ) { + if ( typeof elem.getAttribute === "undefined" ) { return jQuery.prop( elem, name, value ); } - var ret, hooks, - notxml = nType !== 1 || !jQuery.isXMLDoc( elem ); + notxml = nType !== 1 || !jQuery.isXMLDoc( elem ); - // Normalize the name if needed + // All attributes are lowercase + // Grab necessary hook if one is defined if ( notxml ) { - name = jQuery.attrFix[ name ] || name; - - hooks = jQuery.attrHooks[ name ]; - - if ( !hooks ) { - // Use boolHook for boolean attributes - if ( rboolean.test( name ) ) { - - hooks = boolHook; - - // Use formHook for forms and if the name contains certain characters - } else if ( formHook && name !== "className" && - (jQuery.nodeName( elem, "form" ) || rinvalidChar.test( name )) ) { - - hooks = formHook; - } - } + name = name.toLowerCase(); + hooks = jQuery.attrHooks[ name ] || ( rboolean.test( name ) ? boolHook : nodeHook ); } if ( value !== undefined ) { if ( value === null ) { jQuery.removeAttr( elem, name ); - return undefined; + return; } else if ( hooks && "set" in hooks && notxml && (ret = hooks.set( elem, value, name )) !== undefined ) { return ret; @@ -2269,22 +2563,33 @@ jQuery.extend({ } }, - removeAttr: function( elem, name ) { - var propName; - if ( elem.nodeType === 1 ) { - name = jQuery.attrFix[ name ] || name; - - if ( jQuery.support.getSetAttribute ) { - // Use removeAttribute in browsers that support it - elem.removeAttribute( name ); - } else { - jQuery.attr( elem, name, "" ); - elem.removeAttributeNode( elem.getAttributeNode( name ) ); - } + removeAttr: function( elem, value ) { + var propName, attrNames, name, l, isBool, + i = 0; - // Set corresponding property to false for boolean attributes - if ( rboolean.test( name ) && (propName = jQuery.propFix[ name ] || name) in elem ) { - elem[ propName ] = false; + if ( value && elem.nodeType === 1 ) { + attrNames = value.toLowerCase().split( rspace ); + l = attrNames.length; + + for ( ; i < l; i++ ) { + name = attrNames[ i ]; + + if ( name ) { + propName = jQuery.propFix[ name ] || name; + isBool = rboolean.test( name ); + + // See #9699 for explanation of this approach (setting first, then removal) + // Do not do this for boolean attributes (see #10870) + if ( !isBool ) { + jQuery.attr( elem, name, "" ); + } + elem.removeAttribute( getSetAttribute ? name : propName ); + + // Set corresponding property to false for boolean attributes + if ( isBool && propName in elem ) { + elem[ propName ] = false; + } + } } } }, @@ -2308,33 +2613,20 @@ jQuery.extend({ } } }, - tabIndex: { - get: function( elem ) { - // elem.tabIndex doesn't always return the correct value when it hasn't been explicitly set - // http://fluidproject.org/blog/2008/01/09/getting-setting-and-removing-tabindex-values-with-javascript/ - var attributeNode = elem.getAttributeNode("tabIndex"); - - return attributeNode && attributeNode.specified ? - parseInt( attributeNode.value, 10 ) : - rfocusable.test( elem.nodeName ) || rclickable.test( elem.nodeName ) && elem.href ? - 0 : - undefined; - } - }, // Use the value property for back compat - // Use the formHook for button elements in IE6/7 (#1954) + // Use the nodeHook for button elements in IE6/7 (#1954) value: { get: function( elem, name ) { - if ( formHook && jQuery.nodeName( elem, "button" ) ) { - return formHook.get( elem, name ); + if ( nodeHook && jQuery.nodeName( elem, "button" ) ) { + return nodeHook.get( elem, name ); } return name in elem ? elem.value : null; }, set: function( elem, value, name ) { - if ( formHook && jQuery.nodeName( elem, "button" ) ) { - return formHook.set( elem, value, name ); + if ( nodeHook && jQuery.nodeName( elem, "button" ) ) { + return nodeHook.set( elem, value, name ); } // Does not return so that setAttribute is also used elem.value = value; @@ -2356,17 +2648,17 @@ jQuery.extend({ frameborder: "frameBorder", contenteditable: "contentEditable" }, - + prop: function( elem, name, value ) { - var nType = elem.nodeType; + var ret, hooks, notxml, + nType = elem.nodeType; // don't get/set properties on text, comment and attribute nodes if ( !elem || nType === 3 || nType === 8 || nType === 2 ) { - return undefined; + return; } - var ret, hooks, - notxml = nType !== 1 || !jQuery.isXMLDoc( elem ); + notxml = nType !== 1 || !jQuery.isXMLDoc( elem ); if ( notxml ) { // Fix name and attach hooks @@ -2379,11 +2671,11 @@ jQuery.extend({ return ret; } else { - return (elem[ name ] = value); + return ( elem[ name ] = value ); } } else { - if ( hooks && "get" in hooks && (ret = hooks.get( elem, name )) !== undefined ) { + if ( hooks && "get" in hooks && (ret = hooks.get( elem, name )) !== null ) { return ret; } else { @@ -2391,15 +2683,35 @@ jQuery.extend({ } } }, - - propHooks: {} + + propHooks: { + tabIndex: { + get: function( elem ) { + // elem.tabIndex doesn't always return the correct value when it hasn't been explicitly set + // http://fluidproject.org/blog/2008/01/09/getting-setting-and-removing-tabindex-values-with-javascript/ + var attributeNode = elem.getAttributeNode("tabindex"); + + return attributeNode && attributeNode.specified ? + parseInt( attributeNode.value, 10 ) : + rfocusable.test( elem.nodeName ) || rclickable.test( elem.nodeName ) && elem.href ? + 0 : + undefined; + } + } + } }); +// Add the tabIndex propHook to attrHooks for back-compat (different case is intentional) +jQuery.attrHooks.tabindex = jQuery.propHooks.tabIndex; + // Hook for boolean attributes boolHook = { get: function( elem, name ) { // Align boolean attributes with corresponding properties - return jQuery.prop( elem, name ) ? + // Fall back to attribute presence where some booleans are not supported + var attrNode, + property = jQuery.prop( elem, name ); + return property === true || typeof property !== "boolean" && ( attrNode = elem.getAttributeNode(name) ) && attrNode.nodeValue !== false ? name.toLowerCase() : undefined; }, @@ -2424,32 +2736,38 @@ boolHook = { }; // IE6/7 do not support getting/setting some attributes with get/setAttribute -if ( !jQuery.support.getSetAttribute ) { +if ( !getSetAttribute ) { - // propFix is more comprehensive and contains all fixes - jQuery.attrFix = jQuery.propFix; - - // Use this for any attribute on a form in IE6/7 - formHook = jQuery.attrHooks.name = jQuery.attrHooks.title = jQuery.valHooks.button = { + fixSpecified = { + name: true, + id: true, + coords: true + }; + + // Use this for any attribute in IE6/7 + // This fixes almost every IE6/7 issue + nodeHook = jQuery.valHooks.button = { get: function( elem, name ) { var ret; ret = elem.getAttributeNode( name ); - // Return undefined if nodeValue is empty string - return ret && ret.nodeValue !== "" ? + return ret && ( fixSpecified[ name ] ? ret.nodeValue !== "" : ret.specified ) ? ret.nodeValue : undefined; }, set: function( elem, value, name ) { - // Check form objects in IE (multiple bugs related) - // Only use nodeValue if the attribute node exists on the form + // Set the existing or create a new attribute node var ret = elem.getAttributeNode( name ); - if ( ret ) { - ret.nodeValue = value; - return value; + if ( !ret ) { + ret = document.createAttribute( name ); + elem.setAttributeNode( ret ); } + return ( ret.nodeValue = value + "" ); } }; + // Apply the nodeHook to tabindex + jQuery.attrHooks.tabindex.set = nodeHook.set; + // Set width and height to auto instead of 0 on empty string( Bug #8150 ) // This is for removals jQuery.each([ "width", "height" ], function( i, name ) { @@ -2462,6 +2780,18 @@ if ( !jQuery.support.getSetAttribute ) { } }); }); + + // Set contenteditable to false on removals(#10429) + // Setting to empty string throws an error as an invalid value + jQuery.attrHooks.contenteditable = { + get: nodeHook.get, + set: function( elem, value, name ) { + if ( value === "" ) { + value = "false"; + } + nodeHook.set( elem, value, name ); + } + }; } @@ -2485,7 +2815,7 @@ if ( !jQuery.support.style ) { return elem.style.cssText.toLowerCase() || undefined; }, set: function( elem, value ) { - return (elem.style.cssText = "" + value); + return ( elem.style.cssText = "" + value ); } }; } @@ -2505,10 +2835,16 @@ if ( !jQuery.support.optSelected ) { parent.parentNode.selectedIndex; } } + return null; } }); } +// IE6/7 call enctype encoding +if ( !jQuery.support.enctype ) { + jQuery.propFix.enctype = "encoding"; +} + // Radios and checkboxes getter/setter if ( !jQuery.support.checkOn ) { jQuery.each([ "radio", "checkbox" ], function() { @@ -2524,7 +2860,7 @@ jQuery.each([ "radio", "checkbox" ], function() { jQuery.valHooks[ this ] = jQuery.extend( jQuery.valHooks[ this ], { set: function( elem, value ) { if ( jQuery.isArray( value ) ) { - return (elem.checked = jQuery.inArray( jQuery(elem).val(), value ) >= 0); + return ( elem.checked = jQuery.inArray( jQuery(elem).val(), value ) >= 0 ); } } }); @@ -2533,116 +2869,119 @@ jQuery.each([ "radio", "checkbox" ], function() { -var rnamespaces = /\.(.*)$/, - rformElems = /^(?:textarea|input|select)$/i, - rperiod = /\./g, - rspaces = / /g, - rescape = /[^\w\s.|`]/g, - fcleanup = function( nm ) { - return nm.replace(rescape, "\\$&"); +var rformElems = /^(?:textarea|input|select)$/i, + rtypenamespace = /^([^\.]*)?(?:\.(.+))?$/, + rhoverHack = /(?:^|\s)hover(\.\S+)?\b/, + rkeyEvent = /^key/, + rmouseEvent = /^(?:mouse|contextmenu)|click/, + rfocusMorph = /^(?:focusinfocus|focusoutblur)$/, + rquickIs = /^(\w*)(?:#([\w\-]+))?(?:\.([\w\-]+))?$/, + quickParse = function( selector ) { + var quick = rquickIs.exec( selector ); + if ( quick ) { + // 0 1 2 3 + // [ _, tag, id, class ] + quick[1] = ( quick[1] || "" ).toLowerCase(); + quick[3] = quick[3] && new RegExp( "(?:^|\\s)" + quick[3] + "(?:\\s|$)" ); + } + return quick; + }, + quickIs = function( elem, m ) { + var attrs = elem.attributes || {}; + return ( + (!m[1] || elem.nodeName.toLowerCase() === m[1]) && + (!m[2] || (attrs.id || {}).value === m[2]) && + (!m[3] || m[3].test( (attrs[ "class" ] || {}).value )) + ); + }, + hoverHack = function( events ) { + return jQuery.event.special.hover ? events : events.replace( rhoverHack, "mouseenter$1 mouseleave$1" ); }; /* - * A number of helper functions used for managing events. - * Many of the ideas behind this code originated from - * Dean Edwards' addEvent library. + * Helper functions for managing events -- not part of the public interface. + * Props to Dean Edwards' addEvent library for many of the ideas. */ jQuery.event = { - // Bind an event to an element - // Original by Dean Edwards - add: function( elem, types, handler, data ) { - if ( elem.nodeType === 3 || elem.nodeType === 8 ) { + add: function( elem, types, handler, data, selector ) { + + var elemData, eventHandle, events, + t, tns, type, namespaces, handleObj, + handleObjIn, quick, handlers, special; + + // Don't attach events to noData or text/comment nodes (allow plain objects tho) + if ( elem.nodeType === 3 || elem.nodeType === 8 || !types || !handler || !(elemData = jQuery._data( elem )) ) { return; } - if ( handler === false ) { - handler = returnFalse; - } else if ( !handler ) { - // Fixes bug #7229. Fix recommended by jdalton - return; - } - - var handleObjIn, handleObj; - + // Caller can pass in an object of custom data in lieu of the handler if ( handler.handler ) { handleObjIn = handler; handler = handleObjIn.handler; + selector = handleObjIn.selector; } - // Make sure that the function being executed has a unique ID + // Make sure that the handler has a unique ID, used to find/remove it later if ( !handler.guid ) { handler.guid = jQuery.guid++; } - // Init the element's event structure - var elemData = jQuery._data( elem ); - - // If no elemData is found then we must be trying to bind to one of the - // banned noData elements - if ( !elemData ) { - return; - } - - var events = elemData.events, - eventHandle = elemData.handle; - + // Init the element's event structure and main handler, if this is the first + events = elemData.events; if ( !events ) { elemData.events = events = {}; } - + eventHandle = elemData.handle; if ( !eventHandle ) { elemData.handle = eventHandle = function( e ) { // Discard the second event of a jQuery.event.trigger() and // when an event is called after a page has unloaded return typeof jQuery !== "undefined" && (!e || jQuery.event.triggered !== e.type) ? - jQuery.event.handle.apply( eventHandle.elem, arguments ) : + jQuery.event.dispatch.apply( eventHandle.elem, arguments ) : undefined; }; + // Add elem as a property of the handle fn to prevent a memory leak with IE non-native events + eventHandle.elem = elem; } - // Add elem as a property of the handle function - // This is to prevent a memory leak with non-native events in IE. - eventHandle.elem = elem; - // Handle multiple events separated by a space // jQuery(...).bind("mouseover mouseout", fn); - types = types.split(" "); + types = jQuery.trim( hoverHack(types) ).split( " " ); + for ( t = 0; t < types.length; t++ ) { - var type, i = 0, namespaces; + tns = rtypenamespace.exec( types[t] ) || []; + type = tns[1]; + namespaces = ( tns[2] || "" ).split( "." ).sort(); - while ( (type = types[ i++ ]) ) { - handleObj = handleObjIn ? - jQuery.extend({}, handleObjIn) : - { handler: handler, data: data }; + // If event changes its type, use the special event handlers for the changed type + special = jQuery.event.special[ type ] || {}; - // Namespaced event handlers - if ( type.indexOf(".") > -1 ) { - namespaces = type.split("."); - type = namespaces.shift(); - handleObj.namespace = namespaces.slice(0).sort().join("."); + // If selector defined, determine special event api type, otherwise given type + type = ( selector ? special.delegateType : special.bindType ) || type; - } else { - namespaces = []; - handleObj.namespace = ""; - } + // Update special based on newly reset type + special = jQuery.event.special[ type ] || {}; - handleObj.type = type; - if ( !handleObj.guid ) { - handleObj.guid = handler.guid; - } + // handleObj is passed to all event handlers + handleObj = jQuery.extend({ + type: type, + origType: tns[1], + data: data, + handler: handler, + guid: handler.guid, + selector: selector, + quick: selector && quickParse( selector ), + namespace: namespaces.join(".") + }, handleObjIn ); - // Get the current list of functions bound to this event - var handlers = events[ type ], - special = jQuery.event.special[ type ] || {}; - - // Init the event handler queue + // Init the event handler queue if we're the first + handlers = events[ type ]; if ( !handlers ) { handlers = events[ type ] = []; + handlers.delegateCount = 0; - // Check for a special event handler - // Only use addEventListener/attachEvent if the special - // events handler returns false + // Only use addEventListener/attachEvent if the special events handler returns false if ( !special.setup || special.setup.call( elem, data, namespaces, eventHandle ) === false ) { // Bind the global event handler to the element if ( elem.addEventListener ) { @@ -2662,10 +3001,14 @@ jQuery.event = { } } - // Add the function to the element's handler list - handlers.push( handleObj ); + // Add to the element's handler list, delegates in front + if ( selector ) { + handlers.splice( handlers.delegateCount++, 0, handleObj ); + } else { + handlers.push( handleObj ); + } - // Keep track of which events have been used, for event optimization + // Keep track of which events have ever been used, for event optimization jQuery.event.global[ type ] = true; } @@ -2676,129 +3019,80 @@ jQuery.event = { global: {}, // Detach an event or set of events from an element - remove: function( elem, types, handler, pos ) { - // don't do events on text and comment nodes - if ( elem.nodeType === 3 || elem.nodeType === 8 ) { + remove: function( elem, types, handler, selector, mappedTypes ) { + + var elemData = jQuery.hasData( elem ) && jQuery._data( elem ), + t, tns, type, origType, namespaces, origCount, + j, events, special, handle, eventType, handleObj; + + if ( !elemData || !(events = elemData.events) ) { return; } - if ( handler === false ) { - handler = returnFalse; - } + // Once for each type.namespace in types; type may be omitted + types = jQuery.trim( hoverHack( types || "" ) ).split(" "); + for ( t = 0; t < types.length; t++ ) { + tns = rtypenamespace.exec( types[t] ) || []; + type = origType = tns[1]; + namespaces = tns[2]; - var ret, type, fn, j, i = 0, all, namespaces, namespace, special, eventType, handleObj, origType, - elemData = jQuery.hasData( elem ) && jQuery._data( elem ), - events = elemData && elemData.events; - - if ( !elemData || !events ) { - return; - } - - // types is actually an event object here - if ( types && types.type ) { - handler = types.handler; - types = types.type; - } - - // Unbind all events for the element - if ( !types || typeof types === "string" && types.charAt(0) === "." ) { - types = types || ""; - - for ( type in events ) { - jQuery.event.remove( elem, type + types ); - } - - return; - } - - // Handle multiple events separated by a space - // jQuery(...).unbind("mouseover mouseout", fn); - types = types.split(" "); - - while ( (type = types[ i++ ]) ) { - origType = type; - handleObj = null; - all = type.indexOf(".") < 0; - namespaces = []; - - if ( !all ) { - // Namespaced event handlers - namespaces = type.split("."); - type = namespaces.shift(); - - namespace = new RegExp("(^|\\.)" + - jQuery.map( namespaces.slice(0).sort(), fcleanup ).join("\\.(?:.*\\.)?") + "(\\.|$)"); - } - - eventType = events[ type ]; - - if ( !eventType ) { - continue; - } - - if ( !handler ) { - for ( j = 0; j < eventType.length; j++ ) { - handleObj = eventType[ j ]; - - if ( all || namespace.test( handleObj.namespace ) ) { - jQuery.event.remove( elem, origType, handleObj.handler, j ); - eventType.splice( j--, 1 ); - } + // Unbind all events (on this namespace, if provided) for the element + if ( !type ) { + for ( type in events ) { + jQuery.event.remove( elem, type + types[ t ], handler, selector, true ); } - continue; } special = jQuery.event.special[ type ] || {}; + type = ( selector? special.delegateType : special.bindType ) || type; + eventType = events[ type ] || []; + origCount = eventType.length; + namespaces = namespaces ? new RegExp("(^|\\.)" + namespaces.split(".").sort().join("\\.(?:.*\\.)?") + "(\\.|$)") : null; - for ( j = pos || 0; j < eventType.length; j++ ) { + // Remove matching events + for ( j = 0; j < eventType.length; j++ ) { handleObj = eventType[ j ]; - if ( handler.guid === handleObj.guid ) { - // remove the given handler for the given type - if ( all || namespace.test( handleObj.namespace ) ) { - if ( pos == null ) { - eventType.splice( j--, 1 ); - } + if ( ( mappedTypes || origType === handleObj.origType ) && + ( !handler || handler.guid === handleObj.guid ) && + ( !namespaces || namespaces.test( handleObj.namespace ) ) && + ( !selector || selector === handleObj.selector || selector === "**" && handleObj.selector ) ) { + eventType.splice( j--, 1 ); - if ( special.remove ) { - special.remove.call( elem, handleObj ); - } + if ( handleObj.selector ) { + eventType.delegateCount--; } - - if ( pos != null ) { - break; + if ( special.remove ) { + special.remove.call( elem, handleObj ); } } } - // remove generic event handler if no more handlers exist - if ( eventType.length === 0 || pos != null && eventType.length === 1 ) { + // Remove generic event handler if we removed something and no more handlers exist + // (avoids potential for endless recursion during removal of special event handlers) + if ( eventType.length === 0 && origCount !== eventType.length ) { if ( !special.teardown || special.teardown.call( elem, namespaces ) === false ) { jQuery.removeEvent( elem, type, elemData.handle ); } - ret = null; delete events[ type ]; } } // Remove the expando if it's no longer used if ( jQuery.isEmptyObject( events ) ) { - var handle = elemData.handle; + handle = elemData.handle; if ( handle ) { handle.elem = null; } - delete elemData.events; - delete elemData.handle; - - if ( jQuery.isEmptyObject( elemData ) ) { - jQuery.removeData( elem, undefined, true ); - } + // removeData also checks for emptiness and clears the expando if empty + // so use it instead of delete + jQuery.removeData( elem, [ "events", "handle" ], true ); } }, - + // Events that are safe to short-circuit if no handlers are attached. // Native DOM events should not be added, they may have inline handlers. customEvent: { @@ -2808,18 +3102,28 @@ jQuery.event = { }, trigger: function( event, data, elem, onlyHandlers ) { + // Don't do events on text and comment nodes + if ( elem && (elem.nodeType === 3 || elem.nodeType === 8) ) { + return; + } + // Event object or event type var type = event.type || event, namespaces = [], - exclusive; + cache, exclusive, i, cur, old, ontype, special, handle, eventPath, bubbleType; - if ( type.indexOf("!") >= 0 ) { + // focus/blur morphs to focusin/out; ensure we're not firing them right now + if ( rfocusMorph.test( type + jQuery.event.triggered ) ) { + return; + } + + if ( type.indexOf( "!" ) >= 0 ) { // Exclusive events trigger only for the exact event (no namespaces) type = type.slice(0, -1); exclusive = true; } - if ( type.indexOf(".") >= 0 ) { + if ( type.indexOf( "." ) >= 0 ) { // Namespaced trigger; create a regexp to match event type in handle() namespaces = type.split("."); type = namespaces.shift(); @@ -2841,230 +3145,314 @@ jQuery.event = { new jQuery.Event( type ); event.type = type; + event.isTrigger = true; event.exclusive = exclusive; - event.namespace = namespaces.join("."); - event.namespace_re = new RegExp("(^|\\.)" + namespaces.join("\\.(?:.*\\.)?") + "(\\.|$)"); - - // triggerHandler() and global events don't bubble or run the default action - if ( onlyHandlers || !elem ) { - event.preventDefault(); - event.stopPropagation(); - } + event.namespace = namespaces.join( "." ); + event.namespace_re = event.namespace? new RegExp("(^|\\.)" + namespaces.join("\\.(?:.*\\.)?") + "(\\.|$)") : null; + ontype = type.indexOf( ":" ) < 0 ? "on" + type : ""; // Handle a global trigger if ( !elem ) { - // TODO: Stop taunting the data cache; remove global events and always attach to document - jQuery.each( jQuery.cache, function() { - // internalKey variable is just used to make it easier to find - // and potentially change this stuff later; currently it just - // points to jQuery.expando - var internalKey = jQuery.expando, - internalCache = this[ internalKey ]; - if ( internalCache && internalCache.events && internalCache.events[ type ] ) { - jQuery.event.trigger( event, data, internalCache.handle.elem ); - } - }); - return; - } - // Don't do events on text and comment nodes - if ( elem.nodeType === 3 || elem.nodeType === 8 ) { + // TODO: Stop taunting the data cache; remove global events and always attach to document + cache = jQuery.cache; + for ( i in cache ) { + if ( cache[ i ].events && cache[ i ].events[ type ] ) { + jQuery.event.trigger( event, data, cache[ i ].handle.elem, true ); + } + } return; } // Clean up the event in case it is being reused event.result = undefined; - event.target = elem; + if ( !event.target ) { + event.target = elem; + } // Clone any incoming data and prepend the event, creating the handler arg list data = data != null ? jQuery.makeArray( data ) : []; data.unshift( event ); - var cur = elem, - // IE doesn't like method names with a colon (#3533, #8272) - ontype = type.indexOf(":") < 0 ? "on" + type : ""; + // Allow special events to draw outside the lines + special = jQuery.event.special[ type ] || {}; + if ( special.trigger && special.trigger.apply( elem, data ) === false ) { + return; + } - // Fire event on the current element, then bubble up the DOM tree - do { - var handle = jQuery._data( cur, "handle" ); + // Determine event propagation path in advance, per W3C events spec (#9951) + // Bubble up to document, then to window; watch for a global ownerDocument var (#9724) + eventPath = [[ elem, special.bindType || type ]]; + if ( !onlyHandlers && !special.noBubble && !jQuery.isWindow( elem ) ) { - event.currentTarget = cur; + bubbleType = special.delegateType || type; + cur = rfocusMorph.test( bubbleType + type ) ? elem : elem.parentNode; + old = null; + for ( ; cur; cur = cur.parentNode ) { + eventPath.push([ cur, bubbleType ]); + old = cur; + } + + // Only add window if we got to document (e.g., not plain obj or detached DOM) + if ( old && old === elem.ownerDocument ) { + eventPath.push([ old.defaultView || old.parentWindow || window, bubbleType ]); + } + } + + // Fire handlers on the event path + for ( i = 0; i < eventPath.length && !event.isPropagationStopped(); i++ ) { + + cur = eventPath[i][0]; + event.type = eventPath[i][1]; + + handle = ( jQuery._data( cur, "events" ) || {} )[ event.type ] && jQuery._data( cur, "handle" ); if ( handle ) { handle.apply( cur, data ); } - - // Trigger an inline bound script - if ( ontype && jQuery.acceptData( cur ) && cur[ ontype ] && cur[ ontype ].apply( cur, data ) === false ) { - event.result = false; + // Note that this is a bare JS function and not a jQuery handler + handle = ontype && cur[ ontype ]; + if ( handle && jQuery.acceptData( cur ) && handle.apply( cur, data ) === false ) { event.preventDefault(); } - - // Bubble up to document, then to window - cur = cur.parentNode || cur.ownerDocument || cur === event.target.ownerDocument && window; - } while ( cur && !event.isPropagationStopped() ); + } + event.type = type; // If nobody prevented the default action, do it now - if ( !event.isDefaultPrevented() ) { - var old, - special = jQuery.event.special[ type ] || {}; + if ( !onlyHandlers && !event.isDefaultPrevented() ) { - if ( (!special._default || special._default.call( elem.ownerDocument, event ) === false) && + if ( (!special._default || special._default.apply( elem.ownerDocument, data ) === false) && !(type === "click" && jQuery.nodeName( elem, "a" )) && jQuery.acceptData( elem ) ) { // Call a native DOM method on the target with the same name name as the event. - // Can't use an .isFunction)() check here because IE6/7 fails that test. - // IE<9 dies on focus to hidden element (#1486), may want to revisit a try/catch. - try { - if ( ontype && elem[ type ] ) { - // Don't re-trigger an onFOO event when we call its FOO() method - old = elem[ ontype ]; + // Can't use an .isFunction() check here because IE6/7 fails that test. + // Don't do default actions on window, that's where global variables be (#6170) + // IE<9 dies on focus/blur to hidden element (#1486) + if ( ontype && elem[ type ] && ((type !== "focus" && type !== "blur") || event.target.offsetWidth !== 0) && !jQuery.isWindow( elem ) ) { - if ( old ) { - elem[ ontype ] = null; - } + // Don't re-trigger an onFOO event when we call its FOO() method + old = elem[ ontype ]; - jQuery.event.triggered = type; - elem[ type ](); + if ( old ) { + elem[ ontype ] = null; } - } catch ( ieError ) {} - if ( old ) { - elem[ ontype ] = old; + // Prevent re-triggering of the same event, since we already bubbled it above + jQuery.event.triggered = type; + elem[ type ](); + jQuery.event.triggered = undefined; + + if ( old ) { + elem[ ontype ] = old; + } } - - jQuery.event.triggered = undefined; } } - + return event.result; }, - handle: function( event ) { + dispatch: function( event ) { + + // Make a writable jQuery.Event from the native event object event = jQuery.event.fix( event || window.event ); - // Snapshot the handlers list since a called handler may add/remove events. - var handlers = ((jQuery._data( this, "events" ) || {})[ event.type ] || []).slice(0), + + var handlers = ( (jQuery._data( this, "events" ) || {} )[ event.type ] || []), + delegateCount = handlers.delegateCount, + args = [].slice.call( arguments, 0 ), run_all = !event.exclusive && !event.namespace, - args = Array.prototype.slice.call( arguments, 0 ); + special = jQuery.event.special[ event.type ] || {}, + handlerQueue = [], + i, j, cur, jqcur, ret, selMatch, matched, matches, handleObj, sel, related; - // Use the fix-ed Event rather than the (read-only) native event + // Use the fix-ed jQuery.Event rather than the (read-only) native event args[0] = event; - event.currentTarget = this; + event.delegateTarget = this; - for ( var j = 0, l = handlers.length; j < l; j++ ) { - var handleObj = handlers[ j ]; + // Call the preDispatch hook for the mapped type, and let it bail if desired + if ( special.preDispatch && special.preDispatch.call( this, event ) === false ) { + return; + } - // Triggered event must 1) be non-exclusive and have no namespace, or - // 2) have namespace(s) a subset or equal to those in the bound event. - if ( run_all || event.namespace_re.test( handleObj.namespace ) ) { - // Pass in a reference to the handler function itself - // So that we can later remove it - event.handler = handleObj.handler; - event.data = handleObj.data; - event.handleObj = handleObj; + // Determine handlers that should run if there are delegated events + // Avoid non-left-click bubbling in Firefox (#3861) + if ( delegateCount && !(event.button && event.type === "click") ) { - var ret = handleObj.handler.apply( this, args ); + // Pregenerate a single jQuery object for reuse with .is() + jqcur = jQuery(this); + jqcur.context = this.ownerDocument || this; - if ( ret !== undefined ) { - event.result = ret; - if ( ret === false ) { - event.preventDefault(); - event.stopPropagation(); + for ( cur = event.target; cur != this; cur = cur.parentNode || this ) { + + // Don't process events on disabled elements (#6911, #8165) + if ( cur.disabled !== true ) { + selMatch = {}; + matches = []; + jqcur[0] = cur; + for ( i = 0; i < delegateCount; i++ ) { + handleObj = handlers[ i ]; + sel = handleObj.selector; + + if ( selMatch[ sel ] === undefined ) { + selMatch[ sel ] = ( + handleObj.quick ? quickIs( cur, handleObj.quick ) : jqcur.is( sel ) + ); + } + if ( selMatch[ sel ] ) { + matches.push( handleObj ); + } + } + if ( matches.length ) { + handlerQueue.push({ elem: cur, matches: matches }); } - } - - if ( event.isImmediatePropagationStopped() ) { - break; } } } + + // Add the remaining (directly-bound) handlers + if ( handlers.length > delegateCount ) { + handlerQueue.push({ elem: this, matches: handlers.slice( delegateCount ) }); + } + + // Run delegates first; they may want to stop propagation beneath us + for ( i = 0; i < handlerQueue.length && !event.isPropagationStopped(); i++ ) { + matched = handlerQueue[ i ]; + event.currentTarget = matched.elem; + + for ( j = 0; j < matched.matches.length && !event.isImmediatePropagationStopped(); j++ ) { + handleObj = matched.matches[ j ]; + + // Triggered event must either 1) be non-exclusive and have no namespace, or + // 2) have namespace(s) a subset or equal to those in the bound event (both can have no namespace). + if ( run_all || (!event.namespace && !handleObj.namespace) || event.namespace_re && event.namespace_re.test( handleObj.namespace ) ) { + + event.data = handleObj.data; + event.handleObj = handleObj; + + ret = ( (jQuery.event.special[ handleObj.origType ] || {}).handle || handleObj.handler ) + .apply( matched.elem, args ); + + if ( ret !== undefined ) { + event.result = ret; + if ( ret === false ) { + event.preventDefault(); + event.stopPropagation(); + } + } + } + } + } + + // Call the postDispatch hook for the mapped type + if ( special.postDispatch ) { + special.postDispatch.call( this, event ); + } + return event.result; }, - props: "altKey attrChange attrName bubbles button cancelable charCode clientX clientY ctrlKey currentTarget data detail eventPhase fromElement handler keyCode layerX layerY metaKey newValue offsetX offsetY pageX pageY prevValue relatedNode relatedTarget screenX screenY shiftKey srcElement target toElement view wheelDelta which".split(" "), + // Includes some event props shared by KeyEvent and MouseEvent + // *** attrChange attrName relatedNode srcElement are not normalized, non-W3C, deprecated, will be removed in 1.8 *** + props: "attrChange attrName relatedNode srcElement altKey bubbles cancelable ctrlKey currentTarget eventPhase metaKey relatedTarget shiftKey target timeStamp view which".split(" "), + + fixHooks: {}, + + keyHooks: { + props: "char charCode key keyCode".split(" "), + filter: function( event, original ) { + + // Add which for key events + if ( event.which == null ) { + event.which = original.charCode != null ? original.charCode : original.keyCode; + } + + return event; + } + }, + + mouseHooks: { + props: "button buttons clientX clientY fromElement offsetX offsetY pageX pageY screenX screenY toElement".split(" "), + filter: function( event, original ) { + var eventDoc, doc, body, + button = original.button, + fromElement = original.fromElement; + + // Calculate pageX/Y if missing and clientX/Y available + if ( event.pageX == null && original.clientX != null ) { + eventDoc = event.target.ownerDocument || document; + doc = eventDoc.documentElement; + body = eventDoc.body; + + event.pageX = original.clientX + ( doc && doc.scrollLeft || body && body.scrollLeft || 0 ) - ( doc && doc.clientLeft || body && body.clientLeft || 0 ); + event.pageY = original.clientY + ( doc && doc.scrollTop || body && body.scrollTop || 0 ) - ( doc && doc.clientTop || body && body.clientTop || 0 ); + } + + // Add relatedTarget, if necessary + if ( !event.relatedTarget && fromElement ) { + event.relatedTarget = fromElement === event.target ? original.toElement : fromElement; + } + + // Add which for click: 1 === left; 2 === middle; 3 === right + // Note: button is not normalized, so don't use it + if ( !event.which && button !== undefined ) { + event.which = ( button & 1 ? 1 : ( button & 2 ? 3 : ( button & 4 ? 2 : 0 ) ) ); + } + + return event; + } + }, fix: function( event ) { if ( event[ jQuery.expando ] ) { return event; } - // store a copy of the original event object - // and "clone" to set read-only properties - var originalEvent = event; + // Create a writable copy of the event object and normalize some properties + var i, prop, + originalEvent = event, + fixHook = jQuery.event.fixHooks[ event.type ] || {}, + copy = fixHook.props ? this.props.concat( fixHook.props ) : this.props; + event = jQuery.Event( originalEvent ); - for ( var i = this.props.length, prop; i; ) { - prop = this.props[ --i ]; + for ( i = copy.length; i; ) { + prop = copy[ --i ]; event[ prop ] = originalEvent[ prop ]; } - // Fix target property, if necessary + // Fix target property, if necessary (#1925, IE 6/7/8 & Safari2) if ( !event.target ) { - // Fixes #1925 where srcElement might not be defined either - event.target = event.srcElement || document; + event.target = originalEvent.srcElement || document; } - // check if target is a textnode (safari) + // Target should not be a text node (#504, Safari) if ( event.target.nodeType === 3 ) { event.target = event.target.parentNode; } - // Add relatedTarget, if necessary - if ( !event.relatedTarget && event.fromElement ) { - event.relatedTarget = event.fromElement === event.target ? event.toElement : event.fromElement; - } - - // Calculate pageX/Y if missing and clientX/Y available - if ( event.pageX == null && event.clientX != null ) { - var eventDocument = event.target.ownerDocument || document, - doc = eventDocument.documentElement, - body = eventDocument.body; - - event.pageX = event.clientX + (doc && doc.scrollLeft || body && body.scrollLeft || 0) - (doc && doc.clientLeft || body && body.clientLeft || 0); - event.pageY = event.clientY + (doc && doc.scrollTop || body && body.scrollTop || 0) - (doc && doc.clientTop || body && body.clientTop || 0); - } - - // Add which for key events - if ( event.which == null && (event.charCode != null || event.keyCode != null) ) { - event.which = event.charCode != null ? event.charCode : event.keyCode; - } - - // Add metaKey to non-Mac browsers (use ctrl for PC's and Meta for Macs) - if ( !event.metaKey && event.ctrlKey ) { + // For mouse/key events; add metaKey if it's not there (#3368, IE6/7/8) + if ( event.metaKey === undefined ) { event.metaKey = event.ctrlKey; } - // Add which for click: 1 === left; 2 === middle; 3 === right - // Note: button is not normalized, so don't use it - if ( !event.which && event.button !== undefined ) { - event.which = (event.button & 1 ? 1 : ( event.button & 2 ? 3 : ( event.button & 4 ? 2 : 0 ) )); - } - - return event; + return fixHook.filter? fixHook.filter( event, originalEvent ) : event; }, - // Deprecated, use jQuery.guid instead - guid: 1E8, - - // Deprecated, use jQuery.proxy instead - proxy: jQuery.proxy, - special: { ready: { // Make sure the ready event is setup - setup: jQuery.bindReady, - teardown: jQuery.noop + setup: jQuery.bindReady }, - live: { - add: function( handleObj ) { - jQuery.event.add( this, - liveConvert( handleObj.origType, handleObj.selector ), - jQuery.extend({}, handleObj, {handler: liveHandler, guid: handleObj.handler.guid}) ); - }, + load: { + // Prevent triggered image.load events from bubbling to window.load + noBubble: true + }, - remove: function( handleObj ) { - jQuery.event.remove( this, liveConvert( handleObj.origType, handleObj.selector ), handleObj ); - } + focus: { + delegateType: "focusin" + }, + blur: { + delegateType: "focusout" }, beforeunload: { @@ -3081,9 +3469,35 @@ jQuery.event = { } } } + }, + + simulate: function( type, elem, event, bubble ) { + // Piggyback on a donor event to simulate a different one. + // Fake originalEvent to avoid donor's stopPropagation, but if the + // simulated event prevents default then we do the same on the donor. + var e = jQuery.extend( + new jQuery.Event(), + event, + { type: type, + isSimulated: true, + originalEvent: {} + } + ); + if ( bubble ) { + jQuery.event.trigger( e, null, elem ); + } else { + jQuery.event.dispatch.call( elem, e ); + } + if ( e.isDefaultPrevented() ) { + event.preventDefault(); + } } }; +// Some plugins are using, but it's undocumented/deprecated and will be removed. +// The 1.7 special event interface should provide all the hooks needed now. +jQuery.event.handle = jQuery.event.dispatch; + jQuery.removeEvent = document.removeEventListener ? function( elem, type, handle ) { if ( elem.removeEventListener ) { @@ -3098,7 +3512,7 @@ jQuery.removeEvent = document.removeEventListener ? jQuery.Event = function( src, props ) { // Allow instantiation without the 'new' keyword - if ( !this.preventDefault ) { + if ( !(this instanceof jQuery.Event) ) { return new jQuery.Event( src, props ); } @@ -3109,8 +3523,8 @@ jQuery.Event = function( src, props ) { // Events bubbling up the document may have been marked as prevented // by a handler lower down the tree; reflect the correct value. - this.isDefaultPrevented = (src.defaultPrevented || src.returnValue === false || - src.getPreventDefault && src.getPreventDefault()) ? returnTrue : returnFalse; + this.isDefaultPrevented = ( src.defaultPrevented || src.returnValue === false || + src.getPreventDefault && src.getPreventDefault() ) ? returnTrue : returnFalse; // Event type } else { @@ -3122,9 +3536,8 @@ jQuery.Event = function( src, props ) { jQuery.extend( this, props ); } - // timeStamp is buggy for some events on Firefox(#3843) - // So we won't rely on the native value - this.timeStamp = jQuery.now(); + // Create a timestamp if incoming event doesn't have one + this.timeStamp = src && src.timeStamp || jQuery.now(); // Mark it as fixed this[ jQuery.expando ] = true; @@ -3180,214 +3593,137 @@ jQuery.Event.prototype = { isImmediatePropagationStopped: returnFalse }; -// Checks if an event happened on an element within another element -// Used in jQuery.event.special.mouseenter and mouseleave handlers -var withinElement = function( event ) { - - // Check if mouse(over|out) are still within the same parent element - var related = event.relatedTarget, - inside = false, - eventType = event.type; - - event.type = event.data; - - if ( related !== this ) { - - if ( related ) { - inside = jQuery.contains( this, related ); - } - - if ( !inside ) { - - jQuery.event.handle.apply( this, arguments ); - - event.type = eventType; - } - } -}, - -// In case of event delegation, we only need to rename the event.type, -// liveHandler will take care of the rest. -delegate = function( event ) { - event.type = event.data; - jQuery.event.handle.apply( this, arguments ); -}; - -// Create mouseenter and mouseleave events +// Create mouseenter/leave events using mouseover/out and event-time checks jQuery.each({ mouseenter: "mouseover", mouseleave: "mouseout" }, function( orig, fix ) { jQuery.event.special[ orig ] = { - setup: function( data ) { - jQuery.event.add( this, fix, data && data.selector ? delegate : withinElement, orig ); - }, - teardown: function( data ) { - jQuery.event.remove( this, fix, data && data.selector ? delegate : withinElement ); + delegateType: fix, + bindType: fix, + + handle: function( event ) { + var target = this, + related = event.relatedTarget, + handleObj = event.handleObj, + selector = handleObj.selector, + ret; + + // For mousenter/leave call the handler if related is outside the target. + // NB: No relatedTarget if the mouse left/entered the browser window + if ( !related || (related !== target && !jQuery.contains( target, related )) ) { + event.type = handleObj.origType; + ret = handleObj.handler.apply( this, arguments ); + event.type = fix; + } + return ret; } }; }); -// submit delegation +// IE submit delegation if ( !jQuery.support.submitBubbles ) { jQuery.event.special.submit = { - setup: function( data, namespaces ) { - if ( !jQuery.nodeName( this, "form" ) ) { - jQuery.event.add(this, "click.specialSubmit", function( e ) { - var elem = e.target, - type = elem.type; - - if ( (type === "submit" || type === "image") && jQuery( elem ).closest("form").length ) { - trigger( "submit", this, arguments ); - } - }); - - jQuery.event.add(this, "keypress.specialSubmit", function( e ) { - var elem = e.target, - type = elem.type; - - if ( (type === "text" || type === "password") && jQuery( elem ).closest("form").length && e.keyCode === 13 ) { - trigger( "submit", this, arguments ); - } - }); - - } else { + setup: function() { + // Only need this for delegated form submit events + if ( jQuery.nodeName( this, "form" ) ) { return false; } + + // Lazy-add a submit handler when a descendant form may potentially be submitted + jQuery.event.add( this, "click._submit keypress._submit", function( e ) { + // Node name check avoids a VML-related crash in IE (#9807) + var elem = e.target, + form = jQuery.nodeName( elem, "input" ) || jQuery.nodeName( elem, "button" ) ? elem.form : undefined; + if ( form && !form._submit_attached ) { + jQuery.event.add( form, "submit._submit", function( event ) { + event._submit_bubble = true; + }); + form._submit_attached = true; + } + }); + // return undefined since we don't need an event listener + }, + + postDispatch: function( event ) { + // If form was submitted by the user, bubble the event up the tree + if ( event._submit_bubble ) { + delete event._submit_bubble; + if ( this.parentNode && !event.isTrigger ) { + jQuery.event.simulate( "submit", this.parentNode, event, true ); + } + } }, - teardown: function( namespaces ) { - jQuery.event.remove( this, ".specialSubmit" ); + teardown: function() { + // Only need this for delegated form submit events + if ( jQuery.nodeName( this, "form" ) ) { + return false; + } + + // Remove delegated handlers; cleanData eventually reaps submit handlers attached above + jQuery.event.remove( this, "._submit" ); } }; - } -// change delegation, happens here so we have bind. +// IE change delegation and checkbox/radio fix if ( !jQuery.support.changeBubbles ) { - var changeFilters, - - getVal = function( elem ) { - var type = elem.type, val = elem.value; - - if ( type === "radio" || type === "checkbox" ) { - val = elem.checked; - - } else if ( type === "select-multiple" ) { - val = elem.selectedIndex > -1 ? - jQuery.map( elem.options, function( elem ) { - return elem.selected; - }).join("-") : - ""; - - } else if ( jQuery.nodeName( elem, "select" ) ) { - val = elem.selectedIndex; - } - - return val; - }, - - testChange = function testChange( e ) { - var elem = e.target, data, val; - - if ( !rformElems.test( elem.nodeName ) || elem.readOnly ) { - return; - } - - data = jQuery._data( elem, "_change_data" ); - val = getVal(elem); - - // the current data will be also retrieved by beforeactivate - if ( e.type !== "focusout" || elem.type !== "radio" ) { - jQuery._data( elem, "_change_data", val ); - } - - if ( data === undefined || val === data ) { - return; - } - - if ( data != null || val ) { - e.type = "change"; - e.liveFired = undefined; - jQuery.event.trigger( e, arguments[1], elem ); - } - }; - jQuery.event.special.change = { - filters: { - focusout: testChange, - beforedeactivate: testChange, + setup: function() { - click: function( e ) { - var elem = e.target, type = jQuery.nodeName( elem, "input" ) ? elem.type : ""; - - if ( type === "radio" || type === "checkbox" || jQuery.nodeName( elem, "select" ) ) { - testChange.call( this, e ); + if ( rformElems.test( this.nodeName ) ) { + // IE doesn't fire change on a check/radio until blur; trigger it on click + // after a propertychange. Eat the blur-change in special.change.handle. + // This still fires onchange a second time for check/radio after blur. + if ( this.type === "checkbox" || this.type === "radio" ) { + jQuery.event.add( this, "propertychange._change", function( event ) { + if ( event.originalEvent.propertyName === "checked" ) { + this._just_changed = true; + } + }); + jQuery.event.add( this, "click._change", function( event ) { + if ( this._just_changed && !event.isTrigger ) { + this._just_changed = false; + jQuery.event.simulate( "change", this, event, true ); + } + }); } - }, - - // Change has to be called before submit - // Keydown will be called before keypress, which is used in submit-event delegation - keydown: function( e ) { - var elem = e.target, type = jQuery.nodeName( elem, "input" ) ? elem.type : ""; - - if ( (e.keyCode === 13 && !jQuery.nodeName( elem, "textarea" ) ) || - (e.keyCode === 32 && (type === "checkbox" || type === "radio")) || - type === "select-multiple" ) { - testChange.call( this, e ); - } - }, - - // Beforeactivate happens also before the previous element is blurred - // with this event you can't trigger a change event, but you can store - // information - beforeactivate: function( e ) { - var elem = e.target; - jQuery._data( elem, "_change_data", getVal(elem) ); - } - }, - - setup: function( data, namespaces ) { - if ( this.type === "file" ) { return false; } + // Delegated event; lazy-add a change handler on descendant inputs + jQuery.event.add( this, "beforeactivate._change", function( e ) { + var elem = e.target; - for ( var type in changeFilters ) { - jQuery.event.add( this, type + ".specialChange", changeFilters[type] ); - } - - return rformElems.test( this.nodeName ); + if ( rformElems.test( elem.nodeName ) && !elem._change_attached ) { + jQuery.event.add( elem, "change._change", function( event ) { + if ( this.parentNode && !event.isSimulated && !event.isTrigger ) { + jQuery.event.simulate( "change", this.parentNode, event, true ); + } + }); + elem._change_attached = true; + } + }); }, - teardown: function( namespaces ) { - jQuery.event.remove( this, ".specialChange" ); + handle: function( event ) { + var elem = event.target; + + // Swallow native change events from checkbox/radio, we already triggered them above + if ( this !== elem || event.isSimulated || event.isTrigger || (elem.type !== "radio" && elem.type !== "checkbox") ) { + return event.handleObj.handler.apply( this, arguments ); + } + }, + + teardown: function() { + jQuery.event.remove( this, "._change" ); return rformElems.test( this.nodeName ); } }; - - changeFilters = jQuery.event.special.change.filters; - - // Handle when the input is .focus()'d - changeFilters.focus = changeFilters.beforeactivate; -} - -function trigger( type, elem, args ) { - // Piggyback on a donor event to simulate a different one. - // Fake originalEvent to avoid donor's stopPropagation, but if the - // simulated event prevents default then we do the same on the donor. - // Don't pass args or remember liveFired; they apply to the donor event. - var event = jQuery.extend( {}, args[ 0 ] ); - event.type = type; - event.originalEvent = {}; - event.liveFired = undefined; - jQuery.event.handle.call( elem, event ); - if ( event.isDefaultPrevented() ) { - args[ 0 ].preventDefault(); - } } // Create "bubbling" focus and blur events @@ -3395,7 +3731,10 @@ if ( !jQuery.support.focusinBubbles ) { jQuery.each({ focus: "focusin", blur: "focusout" }, function( orig, fix ) { // Attach a single capturing handler while someone wants focusin/focusout - var attaches = 0; + var attaches = 0, + handler = function( event ) { + jQuery.event.simulate( fix, event.target, jQuery.event.fix( event ), true ); + }; jQuery.event.special[ fix ] = { setup: function() { @@ -3409,89 +3748,120 @@ if ( !jQuery.support.focusinBubbles ) { } } }; - - function handler( donor ) { - // Donor event is always a native one; fix it and switch its type. - // Let focusin/out handler cancel the donor focus/blur event. - var e = jQuery.event.fix( donor ); - e.type = fix; - e.originalEvent = {}; - jQuery.event.trigger( e, null, e.target ); - if ( e.isDefaultPrevented() ) { - donor.preventDefault(); - } - } }); } -jQuery.each(["bind", "one"], function( i, name ) { - jQuery.fn[ name ] = function( type, data, fn ) { - var handler; +jQuery.fn.extend({ - // Handle object literals - if ( typeof type === "object" ) { - for ( var key in type ) { - this[ name ](key, data, type[key], fn); + on: function( types, selector, data, fn, /*INTERNAL*/ one ) { + var origFn, type; + + // Types can be a map of types/handlers + if ( typeof types === "object" ) { + // ( types-Object, selector, data ) + if ( typeof selector !== "string" ) { // && selector != null + // ( types-Object, data ) + data = data || selector; + selector = undefined; + } + for ( type in types ) { + this.on( type, selector, data, types[ type ], one ); } return this; } - if ( arguments.length === 2 || data === false ) { - fn = data; - data = undefined; + if ( data == null && fn == null ) { + // ( types, fn ) + fn = selector; + data = selector = undefined; + } else if ( fn == null ) { + if ( typeof selector === "string" ) { + // ( types, selector, fn ) + fn = data; + data = undefined; + } else { + // ( types, data, fn ) + fn = data; + data = selector; + selector = undefined; + } + } + if ( fn === false ) { + fn = returnFalse; + } else if ( !fn ) { + return this; } - if ( name === "one" ) { - handler = function( event ) { - jQuery( this ).unbind( event, handler ); - return fn.apply( this, arguments ); + if ( one === 1 ) { + origFn = fn; + fn = function( event ) { + // Can use an empty set, since event contains the info + jQuery().off( event ); + return origFn.apply( this, arguments ); }; - handler.guid = fn.guid || jQuery.guid++; - } else { - handler = fn; + // Use same guid so caller can remove using origFn + fn.guid = origFn.guid || ( origFn.guid = jQuery.guid++ ); } - - if ( type === "unload" && name !== "one" ) { - this.one( type, data, fn ); - - } else { - for ( var i = 0, l = this.length; i < l; i++ ) { - jQuery.event.add( this[i], type, handler, data ); + return this.each( function() { + jQuery.event.add( this, types, fn, data, selector ); + }); + }, + one: function( types, selector, data, fn ) { + return this.on( types, selector, data, fn, 1 ); + }, + off: function( types, selector, fn ) { + if ( types && types.preventDefault && types.handleObj ) { + // ( event ) dispatched jQuery.Event + var handleObj = types.handleObj; + jQuery( types.delegateTarget ).off( + handleObj.namespace ? handleObj.origType + "." + handleObj.namespace : handleObj.origType, + handleObj.selector, + handleObj.handler + ); + return this; + } + if ( typeof types === "object" ) { + // ( types-object [, selector] ) + for ( var type in types ) { + this.off( type, selector, types[ type ] ); } + return this; } + if ( selector === false || typeof selector === "function" ) { + // ( types [, fn] ) + fn = selector; + selector = undefined; + } + if ( fn === false ) { + fn = returnFalse; + } + return this.each(function() { + jQuery.event.remove( this, types, fn, selector ); + }); + }, + bind: function( types, data, fn ) { + return this.on( types, null, data, fn ); + }, + unbind: function( types, fn ) { + return this.off( types, null, fn ); + }, + + live: function( types, data, fn ) { + jQuery( this.context ).on( types, this.selector, data, fn ); return this; - }; -}); - -jQuery.fn.extend({ - unbind: function( type, fn ) { - // Handle object literals - if ( typeof type === "object" && !type.preventDefault ) { - for ( var key in type ) { - this.unbind(key, type[key]); - } - - } else { - for ( var i = 0, l = this.length; i < l; i++ ) { - jQuery.event.remove( this[i], type, fn ); - } - } - + }, + die: function( types, fn ) { + jQuery( this.context ).off( types, this.selector || "**", fn ); return this; }, delegate: function( selector, types, data, fn ) { - return this.live( types, data, fn, selector ); + return this.on( types, selector, data, fn ); }, - undelegate: function( selector, types, fn ) { - if ( arguments.length === 0 ) { - return this.unbind( "live" ); - - } else { - return this.die( types, null, fn, selector ); - } + // ( namespace ) or ( selector, types [, fn] ) + return arguments.length == 1? this.off( selector, "**" ) : this.off( types, selector, fn ); }, trigger: function( type, data ) { @@ -3499,7 +3869,6 @@ jQuery.fn.extend({ jQuery.event.trigger( type, data, this ); }); }, - triggerHandler: function( type, data ) { if ( this[0] ) { return jQuery.event.trigger( type, data, this[0], true ); @@ -3513,8 +3882,8 @@ jQuery.fn.extend({ i = 0, toggler = function( event ) { // Figure out which function to execute - var lastToggle = ( jQuery.data( this, "lastToggle" + fn.guid ) || 0 ) % i; - jQuery.data( this, "lastToggle" + fn.guid, lastToggle + 1 ); + var lastToggle = ( jQuery._data( this, "lastToggle" + fn.guid ) || 0 ) % i; + jQuery._data( this, "lastToggle" + fn.guid, lastToggle + 1 ); // Make sure that clicks stop event.preventDefault(); @@ -3537,178 +3906,9 @@ jQuery.fn.extend({ } }); -var liveMap = { - focus: "focusin", - blur: "focusout", - mouseenter: "mouseover", - mouseleave: "mouseout" -}; - -jQuery.each(["live", "die"], function( i, name ) { - jQuery.fn[ name ] = function( types, data, fn, origSelector /* Internal Use Only */ ) { - var type, i = 0, match, namespaces, preType, - selector = origSelector || this.selector, - context = origSelector ? this : jQuery( this.context ); - - if ( typeof types === "object" && !types.preventDefault ) { - for ( var key in types ) { - context[ name ]( key, data, types[key], selector ); - } - - return this; - } - - if ( name === "die" && !types && - origSelector && origSelector.charAt(0) === "." ) { - - context.unbind( origSelector ); - - return this; - } - - if ( data === false || jQuery.isFunction( data ) ) { - fn = data || returnFalse; - data = undefined; - } - - types = (types || "").split(" "); - - while ( (type = types[ i++ ]) != null ) { - match = rnamespaces.exec( type ); - namespaces = ""; - - if ( match ) { - namespaces = match[0]; - type = type.replace( rnamespaces, "" ); - } - - if ( type === "hover" ) { - types.push( "mouseenter" + namespaces, "mouseleave" + namespaces ); - continue; - } - - preType = type; - - if ( liveMap[ type ] ) { - types.push( liveMap[ type ] + namespaces ); - type = type + namespaces; - - } else { - type = (liveMap[ type ] || type) + namespaces; - } - - if ( name === "live" ) { - // bind live handler - for ( var j = 0, l = context.length; j < l; j++ ) { - jQuery.event.add( context[j], "live." + liveConvert( type, selector ), - { data: data, selector: selector, handler: fn, origType: type, origHandler: fn, preType: preType } ); - } - - } else { - // unbind live handler - context.unbind( "live." + liveConvert( type, selector ), fn ); - } - } - - return this; - }; -}); - -function liveHandler( event ) { - var stop, maxLevel, related, match, handleObj, elem, j, i, l, data, close, namespace, ret, - elems = [], - selectors = [], - events = jQuery._data( this, "events" ); - - // Make sure we avoid non-left-click bubbling in Firefox (#3861) and disabled elements in IE (#6911) - if ( event.liveFired === this || !events || !events.live || event.target.disabled || event.button && event.type === "click" ) { - return; - } - - if ( event.namespace ) { - namespace = new RegExp("(^|\\.)" + event.namespace.split(".").join("\\.(?:.*\\.)?") + "(\\.|$)"); - } - - event.liveFired = this; - - var live = events.live.slice(0); - - for ( j = 0; j < live.length; j++ ) { - handleObj = live[j]; - - if ( handleObj.origType.replace( rnamespaces, "" ) === event.type ) { - selectors.push( handleObj.selector ); - - } else { - live.splice( j--, 1 ); - } - } - - match = jQuery( event.target ).closest( selectors, event.currentTarget ); - - for ( i = 0, l = match.length; i < l; i++ ) { - close = match[i]; - - for ( j = 0; j < live.length; j++ ) { - handleObj = live[j]; - - if ( close.selector === handleObj.selector && (!namespace || namespace.test( handleObj.namespace )) && !close.elem.disabled ) { - elem = close.elem; - related = null; - - // Those two events require additional checking - if ( handleObj.preType === "mouseenter" || handleObj.preType === "mouseleave" ) { - event.type = handleObj.preType; - related = jQuery( event.relatedTarget ).closest( handleObj.selector )[0]; - - // Make sure not to accidentally match a child element with the same selector - if ( related && jQuery.contains( elem, related ) ) { - related = elem; - } - } - - if ( !related || related !== elem ) { - elems.push({ elem: elem, handleObj: handleObj, level: close.level }); - } - } - } - } - - for ( i = 0, l = elems.length; i < l; i++ ) { - match = elems[i]; - - if ( maxLevel && match.level > maxLevel ) { - break; - } - - event.currentTarget = match.elem; - event.data = match.handleObj.data; - event.handleObj = match.handleObj; - - ret = match.handleObj.origHandler.apply( match.elem, arguments ); - - if ( ret === false || event.isPropagationStopped() ) { - maxLevel = match.level; - - if ( ret === false ) { - stop = false; - } - if ( event.isImmediatePropagationStopped() ) { - break; - } - } - } - - return stop; -} - -function liveConvert( type, selector ) { - return (type && type !== "*" ? type + "." : "") + selector.replace(rperiod, "`").replace(rspaces, "&"); -} - jQuery.each( ("blur focus focusin focusout load resize scroll unload click dblclick " + "mousedown mouseup mousemove mouseover mouseout mouseenter mouseleave " + - "change select submit keydown keypress keyup error").split(" "), function( i, name ) { + "change select submit keydown keypress keyup error contextmenu").split(" "), function( i, name ) { // Handle event binding jQuery.fn[ name ] = function( data, fn ) { @@ -3718,13 +3918,21 @@ jQuery.each( ("blur focus focusin focusout load resize scroll unload click dblcl } return arguments.length > 0 ? - this.bind( name, data, fn ) : + this.on( name, null, data, fn ) : this.trigger( name ); }; if ( jQuery.attrFn ) { jQuery.attrFn[ name ] = true; } + + if ( rkeyEvent.test( name ) ) { + jQuery.event.fixHooks[ name ] = jQuery.event.keyHooks; + } + + if ( rmouseEvent.test( name ) ) { + jQuery.event.fixHooks[ name ] = jQuery.event.mouseHooks; + } }); @@ -3738,11 +3946,13 @@ jQuery.each( ("blur focus focusin focusout load resize scroll unload click dblcl (function(){ var chunker = /((?:\((?:\([^()]+\)|[^()]+)+\)|\[(?:\[[^\[\]]*\]|['"][^'"]*['"]|[^\[\]'"]+)+\]|\\.|[^ >+~,(\[\\]+)+|[>+~])(\s*,\s*)?((?:.|\r|\n)*)/g, + expando = "sizcache" + (Math.random() + '').replace('.', ''), done = 0, toString = Object.prototype.toString, hasDuplicate = false, baseHasDuplicate = true, rBackslash = /\\/g, + rReturn = /\r\n/g, rNonWord = /\W/; // Here we check if the JavaScript engine is using some sort of @@ -3763,7 +3973,7 @@ var Sizzle = function( selector, context, results, seed ) { if ( context.nodeType !== 1 && context.nodeType !== 9 ) { return []; } - + if ( !selector || typeof selector !== "string" ) { return results; } @@ -3773,7 +3983,7 @@ var Sizzle = function( selector, context, results, seed ) { contextXML = Sizzle.isXML( context ), parts = [], soFar = selector; - + // Reset the position of the chunker regexp (start from head) do { chunker.exec( "" ); @@ -3781,9 +3991,9 @@ var Sizzle = function( selector, context, results, seed ) { if ( m ) { soFar = m[3]; - + parts.push( m[1] ); - + if ( m[2] ) { extra = m[3]; break; @@ -3794,7 +4004,7 @@ var Sizzle = function( selector, context, results, seed ) { if ( parts.length > 1 && origPOS.exec( selector ) ) { if ( parts.length === 2 && Expr.relative[ parts[0] ] ) { - set = posProcess( parts[0] + parts[1], context ); + set = posProcess( parts[0] + parts[1], context, seed ); } else { set = Expr.relative[ parts[0] ] ? @@ -3807,8 +4017,8 @@ var Sizzle = function( selector, context, results, seed ) { if ( Expr.relative[ selector ] ) { selector += parts.shift(); } - - set = posProcess( selector, set ); + + set = posProcess( selector, set, seed ); } } @@ -3927,18 +4137,17 @@ Sizzle.matchesSelector = function( node, expr ) { }; Sizzle.find = function( expr, context, isXML ) { - var set; + var set, i, len, match, type, left; if ( !expr ) { return []; } - for ( var i = 0, l = Expr.order.length; i < l; i++ ) { - var match, - type = Expr.order[i]; - + for ( i = 0, len = Expr.order.length; i < len; i++ ) { + type = Expr.order[i]; + if ( (match = Expr.leftMatch[ type ].exec( expr )) ) { - var left = match[1]; + left = match[1]; match.splice( 1, 1 ); if ( left.substr( left.length - 1 ) !== "\\" ) { @@ -3964,17 +4173,18 @@ Sizzle.find = function( expr, context, isXML ) { Sizzle.filter = function( expr, set, inplace, not ) { var match, anyFound, + type, found, item, filter, left, + i, pass, old = expr, result = [], curLoop = set, isXMLFilter = set && set[0] && Sizzle.isXML( set[0] ); while ( expr && set.length ) { - for ( var type in Expr.filter ) { + for ( type in Expr.filter ) { if ( (match = Expr.leftMatch[ type ].exec( expr )) != null && match[2] ) { - var found, item, - filter = Expr.filter[ type ], - left = match[1]; + filter = Expr.filter[ type ]; + left = match[1]; anyFound = false; @@ -4000,10 +4210,10 @@ Sizzle.filter = function( expr, set, inplace, not ) { } if ( match ) { - for ( var i = 0; (item = curLoop[i]) != null; i++ ) { + for ( i = 0; (item = curLoop[i]) != null; i++ ) { if ( item ) { found = filter( item, match, i, curLoop ); - var pass = not ^ !!found; + pass = not ^ found; if ( inplace && found != null ) { if ( pass ) { @@ -4054,7 +4264,46 @@ Sizzle.filter = function( expr, set, inplace, not ) { }; Sizzle.error = function( msg ) { - throw "Syntax error, unrecognized expression: " + msg; + throw new Error( "Syntax error, unrecognized expression: " + msg ); +}; + +/** + * Utility function for retreiving the text value of an array of DOM nodes + * @param {Array|Element} elem + */ +var getText = Sizzle.getText = function( elem ) { + var i, node, + nodeType = elem.nodeType, + ret = ""; + + if ( nodeType ) { + if ( nodeType === 1 || nodeType === 9 || nodeType === 11 ) { + // Use textContent || innerText for elements + if ( typeof elem.textContent === 'string' ) { + return elem.textContent; + } else if ( typeof elem.innerText === 'string' ) { + // Replace IE's carriage returns + return elem.innerText.replace( rReturn, '' ); + } else { + // Traverse it's children + for ( elem = elem.firstChild; elem; elem = elem.nextSibling) { + ret += getText( elem ); + } + } + } else if ( nodeType === 3 || nodeType === 4 ) { + return elem.nodeValue; + } + } else { + + // If no nodeType, this is expected to be an array + for ( i = 0; (node = elem[i]); i++ ) { + // Do not traverse comment nodes + if ( node.nodeType !== 8 ) { + ret += getText( node ); + } + } + } + return ret; }; var Expr = Sizzle.selectors = { @@ -4268,7 +4517,7 @@ var Expr = Sizzle.selectors = { ATTR: function( match, curLoop, inplace, result, not, isXML ) { var name = match[1] = match[1].replace( rBackslash, "" ); - + if ( !isXML && Expr.attrMap[name] ) { match[1] = Expr.attrMap[name]; } @@ -4302,7 +4551,7 @@ var Expr = Sizzle.selectors = { } else if ( Expr.match.POS.test( match[0] ) || Expr.match.CHILD.test( match[0] ) ) { return true; } - + return match; }, @@ -4312,7 +4561,7 @@ var Expr = Sizzle.selectors = { return match; } }, - + filters: { enabled: function( elem ) { return elem.disabled === false && elem.type !== "hidden"; @@ -4325,14 +4574,14 @@ var Expr = Sizzle.selectors = { checked: function( elem ) { return elem.checked === true; }, - + selected: function( elem ) { // Accessing this property makes selected-by-default // options in Safari work properly if ( elem.parentNode ) { elem.parentNode.selectedIndex; } - + return elem.selected === true; }, @@ -4354,7 +4603,7 @@ var Expr = Sizzle.selectors = { text: function( elem ) { var attr = elem.getAttribute( "type" ), type = elem.type; - // IE6 and 7 will map elem.type to 'text' for new HTML5 types (search, etc) + // IE6 and 7 will map elem.type to 'text' for new HTML5 types (search, etc) // use getAttribute instead to test this case return elem.nodeName.toLowerCase() === "input" && "text" === type && ( attr === type || attr === null ); }, @@ -4444,7 +4693,7 @@ var Expr = Sizzle.selectors = { return filter( elem, i, match, array ); } else if ( name === "contains" ) { - return (elem.textContent || elem.innerText || Sizzle.getText([ elem ]) || "").indexOf(match[3]) >= 0; + return (elem.textContent || elem.innerText || getText([ elem ]) || "").indexOf(match[3]) >= 0; } else if ( name === "not" ) { var not = match[3]; @@ -4463,57 +4712,61 @@ var Expr = Sizzle.selectors = { }, CHILD: function( elem, match ) { - var type = match[1], + var first, last, + doneName, parent, cache, + count, diff, + type = match[1], node = elem; switch ( type ) { case "only": case "first": - while ( (node = node.previousSibling) ) { - if ( node.nodeType === 1 ) { - return false; + while ( (node = node.previousSibling) ) { + if ( node.nodeType === 1 ) { + return false; } } - if ( type === "first" ) { - return true; + if ( type === "first" ) { + return true; } node = elem; + /* falls through */ case "last": - while ( (node = node.nextSibling) ) { - if ( node.nodeType === 1 ) { - return false; + while ( (node = node.nextSibling) ) { + if ( node.nodeType === 1 ) { + return false; } } return true; case "nth": - var first = match[2], - last = match[3]; + first = match[2]; + last = match[3]; if ( first === 1 && last === 0 ) { return true; } - - var doneName = match[0], - parent = elem.parentNode; - - if ( parent && (parent.sizcache !== doneName || !elem.nodeIndex) ) { - var count = 0; - + + doneName = match[0]; + parent = elem.parentNode; + + if ( parent && (parent[ expando ] !== doneName || !elem.nodeIndex) ) { + count = 0; + for ( node = parent.firstChild; node; node = node.nextSibling ) { if ( node.nodeType === 1 ) { node.nodeIndex = ++count; } - } + } - parent.sizcache = doneName; + parent[ expando ] = doneName; } - - var diff = elem.nodeIndex - last; + + diff = elem.nodeIndex - last; if ( first === 0 ) { return diff === 0; @@ -4529,9 +4782,9 @@ var Expr = Sizzle.selectors = { }, TAG: function( elem, match ) { - return (match === "*" && elem.nodeType === 1) || elem.nodeName.toLowerCase() === match; + return (match === "*" && elem.nodeType === 1) || !!elem.nodeName && elem.nodeName.toLowerCase() === match; }, - + CLASS: function( elem, match ) { return (" " + (elem.className || elem.getAttribute("class")) + " ") .indexOf( match ) > -1; @@ -4539,7 +4792,9 @@ var Expr = Sizzle.selectors = { ATTR: function( elem, match ) { var name = match[1], - result = Expr.attrHandle[ name ] ? + result = Sizzle.attr ? + Sizzle.attr( elem, name ) : + Expr.attrHandle[ name ] ? Expr.attrHandle[ name ]( elem ) : elem[ name ] != null ? elem[ name ] : @@ -4550,6 +4805,8 @@ var Expr = Sizzle.selectors = { return result == null ? type === "!=" : + !type && Sizzle.attr ? + result != null : type === "=" ? value === check : type === "*=" ? @@ -4589,6 +4846,9 @@ for ( var type in Expr.match ) { Expr.match[ type ] = new RegExp( Expr.match[ type ].source + (/(?![^\[]*\])(?![^\(]*\))/.source) ); Expr.leftMatch[ type ] = new RegExp( /(^(?:.|\r|\n)*?)/.source + Expr.match[ type ].source.replace(/\\(\d+)/g, fescape) ); } +// Expose origPOS +// "global" as in regardless of relation to brackets/parens +Expr.match.globalPOS = origPOS; var makeArray = function( array, results ) { array = Array.prototype.slice.call( array, 0 ); @@ -4597,7 +4857,7 @@ var makeArray = function( array, results ) { results.push.apply( results, array ); return results; } - + return array; }; @@ -4730,26 +4990,6 @@ if ( document.documentElement.compareDocumentPosition ) { }; } -// Utility function for retreiving the text value of an array of DOM nodes -Sizzle.getText = function( elems ) { - var ret = "", elem; - - for ( var i = 0; elems[i]; i++ ) { - elem = elems[i]; - - // Get the text from text nodes and CDATA nodes - if ( elem.nodeType === 3 || elem.nodeType === 4 ) { - ret += elem.nodeValue; - - // Traverse everything else, except comment nodes - } else if ( elem.nodeType !== 8 ) { - ret += Sizzle.getText( elem.childNodes ); - } - } - - return ret; -}; - // Check to see if the browser returns elements by name when // querying by getElementById (and provide a workaround) (function(){ @@ -4849,7 +5089,7 @@ if ( document.querySelectorAll ) { if ( div.querySelectorAll && div.querySelectorAll(".TEST").length === 0 ) { return; } - + Sizzle = function( query, context, extra, seed ) { context = context || document; @@ -4858,24 +5098,24 @@ if ( document.querySelectorAll ) { if ( !seed && !Sizzle.isXML(context) ) { // See if we find a selector to speed up var match = /^(\w+$)|^\.([\w\-]+$)|^#([\w\-]+$)/.exec( query ); - + if ( match && (context.nodeType === 1 || context.nodeType === 9) ) { // Speed-up: Sizzle("TAG") if ( match[1] ) { return makeArray( context.getElementsByTagName( query ), extra ); - + // Speed-up: Sizzle(".CLASS") } else if ( match[2] && Expr.find.CLASS && context.getElementsByClassName ) { return makeArray( context.getElementsByClassName( match[2] ), extra ); } } - + if ( context.nodeType === 9 ) { // Speed-up: Sizzle("body") // The body element only exists once, optimize finding it if ( query === "body" && context.body ) { return makeArray( [ context.body ], extra ); - + // Speed-up: Sizzle("#ID") } else if ( match && match[3] ) { var elem = context.getElementById( match[3] ); @@ -4888,12 +5128,12 @@ if ( document.querySelectorAll ) { if ( elem.id === match[3] ) { return makeArray( [ elem ], extra ); } - + } else { return makeArray( [], extra ); } } - + try { return makeArray( context.querySelectorAll(query), extra ); } catch(qsaError) {} @@ -4931,7 +5171,7 @@ if ( document.querySelectorAll ) { } } } - + return oldSizzle(query, context, extra, seed); }; @@ -4958,7 +5198,7 @@ if ( document.querySelectorAll ) { // This should fail with an exception // Gecko does not error, returns false instead matches.call( document.documentElement, "[test!='']:sizzle" ); - + } catch( pseudoError ) { pseudoWorks = true; } @@ -4968,7 +5208,7 @@ if ( document.querySelectorAll ) { expr = expr.replace(/\=\s*([^'"\]]*)\s*\]/g, "='$1']"); if ( !Sizzle.isXML( node ) ) { - try { + try { if ( pseudoWorks || !Expr.match.PSEUDO.test( expr ) && !/!=/.test( expr ) ) { var ret = matches.call( node, expr ); @@ -5005,7 +5245,7 @@ if ( document.querySelectorAll ) { if ( div.getElementsByClassName("e").length === 1 ) { return; } - + Expr.order.splice(1, 0, "CLASS"); Expr.find.CLASS = function( match, context, isXML ) { if ( typeof context.getElementsByClassName !== "undefined" && !isXML ) { @@ -5027,13 +5267,13 @@ function dirNodeCheck( dir, cur, doneName, checkSet, nodeCheck, isXML ) { elem = elem[dir]; while ( elem ) { - if ( elem.sizcache === doneName ) { + if ( elem[ expando ] === doneName ) { match = checkSet[elem.sizset]; break; } if ( elem.nodeType === 1 && !isXML ){ - elem.sizcache = doneName; + elem[ expando ] = doneName; elem.sizset = i; } @@ -5056,18 +5296,18 @@ function dirCheck( dir, cur, doneName, checkSet, nodeCheck, isXML ) { if ( elem ) { var match = false; - + elem = elem[dir]; while ( elem ) { - if ( elem.sizcache === doneName ) { + if ( elem[ expando ] === doneName ) { match = checkSet[elem.sizset]; break; } if ( elem.nodeType === 1 ) { if ( !isXML ) { - elem.sizcache = doneName; + elem[ expando ] = doneName; elem.sizset = i; } @@ -5109,13 +5349,13 @@ if ( document.documentElement.contains ) { Sizzle.isXML = function( elem ) { // documentElement is verified for cases where it doesn't yet exist - // (such as loading iframes in IE - #4833) + // (such as loading iframes in IE - #4833) var documentElement = (elem ? elem.ownerDocument || elem : 0).documentElement; return documentElement ? documentElement.nodeName !== "HTML" : false; }; -var posProcess = function( selector, context ) { +var posProcess = function( selector, context, seed ) { var match, tmpSet = [], later = "", @@ -5131,13 +5371,16 @@ var posProcess = function( selector, context ) { selector = Expr.relative[selector] ? selector + "*" : selector; for ( var i = 0, l = root.length; i < l; i++ ) { - Sizzle( selector, root[i], tmpSet ); + Sizzle( selector, root[i], tmpSet, seed ); } return Sizzle.filter( later, tmpSet ); }; // EXPOSE +// Override sizzle attribute retrieval +Sizzle.attr = jQuery.attr; +Sizzle.selectors.attrMap = {}; jQuery.find = Sizzle; jQuery.expr = Sizzle.selectors; jQuery.expr[":"] = jQuery.expr.filters; @@ -5156,7 +5399,7 @@ var runtil = /Until$/, rmultiselector = /,/, isSimple = /^.[^:#\[\.,]*$/, slice = Array.prototype.slice, - POS = jQuery.expr.match.POS, + POS = jQuery.expr.match.globalPOS, // methods guaranteed to produce a unique set when starting from a unique set guaranteedUnique = { children: true, @@ -5223,43 +5466,33 @@ jQuery.fn.extend({ }, is: function( selector ) { - return !!selector && ( typeof selector === "string" ? - jQuery.filter( selector, this ).length > 0 : - this.filter( selector ).length > 0 ); + return !!selector && ( + typeof selector === "string" ? + // If this is a positional selector, check membership in the returned set + // so $("p:first").is("p:last") won't return true for a doc with two "p". + POS.test( selector ) ? + jQuery( selector, this.context ).index( this[0] ) >= 0 : + jQuery.filter( selector, this ).length > 0 : + this.filter( selector ).length > 0 ); }, closest: function( selectors, context ) { var ret = [], i, l, cur = this[0]; - - // Array + + // Array (deprecated as of jQuery 1.7) if ( jQuery.isArray( selectors ) ) { - var match, selector, - matches = {}, - level = 1; + var level = 1; - if ( cur && selectors.length ) { - for ( i = 0, l = selectors.length; i < l; i++ ) { - selector = selectors[i]; + while ( cur && cur.ownerDocument && cur !== context ) { + for ( i = 0; i < selectors.length; i++ ) { - if ( !matches[ selector ] ) { - matches[ selector ] = POS.test( selector ) ? - jQuery( selector, context || this.context ) : - selector; + if ( jQuery( cur ).is( selectors[ i ] ) ) { + ret.push({ selector: selectors[ i ], elem: cur, level: level }); } } - while ( cur && cur.ownerDocument && cur !== context ) { - for ( selector in matches ) { - match = matches[ selector ]; - - if ( match.jquery ? match.index( cur ) > -1 : jQuery( cur ).is( match ) ) { - ret.push({ selector: selector, elem: cur, level: level }); - } - } - - cur = cur.parentNode; - level++; - } + cur = cur.parentNode; + level++; } return ret; @@ -5295,12 +5528,17 @@ jQuery.fn.extend({ // Determine the position of an element within // the matched set of elements index: function( elem ) { - if ( !elem || typeof elem === "string" ) { - return jQuery.inArray( this[0], - // If it receives a string, the selector is used - // If it receives nothing, the siblings are used - elem ? jQuery( elem ) : this.parent().children() ); + + // No argument, return index in parent + if ( !elem ) { + return ( this[0] && this[0].parentNode ) ? this.prevAll().length : -1; } + + // index in selector + if ( typeof elem === "string" ) { + return jQuery.inArray( this[0], jQuery( elem ) ); + } + // Locate the position of the desired element return jQuery.inArray( // If it receives a jQuery object, the first element is used @@ -5359,7 +5597,7 @@ jQuery.each({ return jQuery.dir( elem, "previousSibling", until ); }, siblings: function( elem ) { - return jQuery.sibling( elem.parentNode.firstChild, elem ); + return jQuery.sibling( ( elem.parentNode || {} ).firstChild, elem ); }, children: function( elem ) { return jQuery.sibling( elem.firstChild ); @@ -5371,12 +5609,7 @@ jQuery.each({ } }, function( name, fn ) { jQuery.fn[ name ] = function( until, selector ) { - var ret = jQuery.map( this, fn, until ), - // The variable 'args' was introduced in - // https://github.com/jquery/jquery/commit/52a0238 - // to work around a bug in Chrome 10 (Dev) and should be removed when the bug is fixed. - // http://code.google.com/p/v8/issues/detail?id=1050 - args = slice.call(arguments); + var ret = jQuery.map( this, fn, until ); if ( !runtil.test( name ) ) { selector = until; @@ -5392,7 +5625,7 @@ jQuery.each({ ret = ret.reverse(); } - return this.pushStack( ret, name, args.join(",") ); + return this.pushStack( ret, name, slice.call( arguments ).join(",") ); }; }); @@ -5461,7 +5694,7 @@ function winnow( elements, qualifier, keep ) { } else if ( qualifier.nodeType ) { return jQuery.grep(elements, function( elem, i ) { - return (elem === qualifier) === keep; + return ( elem === qualifier ) === keep; }); } else if ( typeof qualifier === "string" ) { @@ -5477,20 +5710,38 @@ function winnow( elements, qualifier, keep ) { } return jQuery.grep(elements, function( elem, i ) { - return (jQuery.inArray( elem, qualifier ) >= 0) === keep; + return ( jQuery.inArray( elem, qualifier ) >= 0 ) === keep; }); } -var rinlinejQuery = / jQuery\d+="(?:\d+|null)"/g, +function createSafeFragment( document ) { + var list = nodeNames.split( "|" ), + safeFrag = document.createDocumentFragment(); + + if ( safeFrag.createElement ) { + while ( list.length ) { + safeFrag.createElement( + list.pop() + ); + } + } + return safeFrag; +} + +var nodeNames = "abbr|article|aside|audio|bdi|canvas|data|datalist|details|figcaption|figure|footer|" + + "header|hgroup|mark|meter|nav|output|progress|section|summary|time|video", + rinlinejQuery = / jQuery\d+="(?:\d+|null)"/g, rleadingWhitespace = /^\s+/, rxhtmlTag = /<(?!area|br|col|embed|hr|img|input|link|meta|param)(([\w:]+)[^>]*)\/>/ig, rtagName = /<([\w:]+)/, rtbody = /<tbody/i, rhtml = /<|&#?\w+;/, + rnoInnerhtml = /<(?:script|style)/i, rnocache = /<(?:script|object|embed|option|style)/i, + rnoshimcache = new RegExp("<(?:" + nodeNames + ")[\\s/>]", "i"), // checked="checked" or checked rchecked = /checked\s*(?:[^=]|=\s*.checked.)/i, rscriptType = /\/(java|ecma)script/i, @@ -5504,7 +5755,8 @@ var rinlinejQuery = / jQuery\d+="(?:\d+|null)"/g, col: [ 2, "<table><tbody></tbody><colgroup>", "</colgroup></table>" ], area: [ 1, "<map>", "</map>" ], _default: [ 0, "", "" ] - }; + }, + safeFragment = createSafeFragment( document ); wrapMap.optgroup = wrapMap.option; wrapMap.tbody = wrapMap.tfoot = wrapMap.colgroup = wrapMap.caption = wrapMap.thead; @@ -5516,20 +5768,12 @@ if ( !jQuery.support.htmlSerialize ) { } jQuery.fn.extend({ - text: function( text ) { - if ( jQuery.isFunction(text) ) { - return this.each(function(i) { - var self = jQuery( this ); - - self.text( text.call(this, i, self.text()) ); - }); - } - - if ( typeof text !== "object" && text !== undefined ) { - return this.empty().append( (this[0] && this[0].ownerDocument || document).createTextNode( text ) ); - } - - return jQuery.text( this ); + text: function( value ) { + return jQuery.access( this, function( value ) { + return value === undefined ? + jQuery.text( this ) : + this.empty().append( ( this[0] && this[0].ownerDocument || document ).createTextNode( value ) ); + }, null, value, arguments.length ); }, wrapAll: function( html ) { @@ -5582,8 +5826,10 @@ jQuery.fn.extend({ }, wrap: function( html ) { - return this.each(function() { - jQuery( this ).wrapAll( html ); + var isFunction = jQuery.isFunction( html ); + + return this.each(function(i) { + jQuery( this ).wrapAll( isFunction ? html.call(this, i) : html ); }); }, @@ -5617,7 +5863,7 @@ jQuery.fn.extend({ this.parentNode.insertBefore( elem, this ); }); } else if ( arguments.length ) { - var set = jQuery(arguments[0]); + var set = jQuery.clean( arguments ); set.push.apply( set, this.toArray() ); return this.pushStack( set, "before", arguments ); } @@ -5630,7 +5876,7 @@ jQuery.fn.extend({ }); } else if ( arguments.length ) { var set = this.pushStack( this, "after", arguments ); - set.push.apply( set, jQuery(arguments[0]).toArray() ); + set.push.apply( set, jQuery.clean(arguments) ); return set; } }, @@ -5679,44 +5925,44 @@ jQuery.fn.extend({ }, html: function( value ) { - if ( value === undefined ) { - return this[0] && this[0].nodeType === 1 ? - this[0].innerHTML.replace(rinlinejQuery, "") : - null; + return jQuery.access( this, function( value ) { + var elem = this[0] || {}, + i = 0, + l = this.length; - // See if we can take a shortcut and just use innerHTML - } else if ( typeof value === "string" && !rnocache.test( value ) && - (jQuery.support.leadingWhitespace || !rleadingWhitespace.test( value )) && - !wrapMap[ (rtagName.exec( value ) || ["", ""])[1].toLowerCase() ] ) { - - value = value.replace(rxhtmlTag, "<$1></$2>"); - - try { - for ( var i = 0, l = this.length; i < l; i++ ) { - // Remove element nodes and prevent memory leaks - if ( this[i].nodeType === 1 ) { - jQuery.cleanData( this[i].getElementsByTagName("*") ); - this[i].innerHTML = value; - } - } - - // If using innerHTML throws an exception, use the fallback method - } catch(e) { - this.empty().append( value ); + if ( value === undefined ) { + return elem.nodeType === 1 ? + elem.innerHTML.replace( rinlinejQuery, "" ) : + null; } - } else if ( jQuery.isFunction( value ) ) { - this.each(function(i){ - var self = jQuery( this ); - self.html( value.call(this, i, self.html()) ); - }); + if ( typeof value === "string" && !rnoInnerhtml.test( value ) && + ( jQuery.support.leadingWhitespace || !rleadingWhitespace.test( value ) ) && + !wrapMap[ ( rtagName.exec( value ) || ["", ""] )[1].toLowerCase() ] ) { - } else { - this.empty().append( value ); - } + value = value.replace( rxhtmlTag, "<$1></$2>" ); - return this; + try { + for (; i < l; i++ ) { + // Remove element nodes and prevent memory leaks + elem = this[i] || {}; + if ( elem.nodeType === 1 ) { + jQuery.cleanData( elem.getElementsByTagName( "*" ) ); + elem.innerHTML = value; + } + } + + elem = 0; + + // If using innerHTML throws an exception, use the fallback method + } catch(e) {} + } + + if ( elem ) { + this.empty().append( value ); + } + }, null, value, arguments.length ); }, replaceWith: function( value ) { @@ -5811,7 +6057,7 @@ jQuery.fn.extend({ // in certain situations (Bug #8070). // Fragments from the fragment cache must always be cloned and never used // in place. - results.cacheable || (l > 1 && i < lastIndex) ? + results.cacheable || ( l > 1 && i < lastIndex ) ? jQuery.clone( fragment, true, true ) : fragment ); @@ -5819,7 +6065,23 @@ jQuery.fn.extend({ } if ( scripts.length ) { - jQuery.each( scripts, evalScript ); + jQuery.each( scripts, function( i, elem ) { + if ( elem.src ) { + jQuery.ajax({ + type: "GET", + global: false, + url: elem.src, + async: false, + dataType: "script" + }); + } else { + jQuery.globalEval( ( elem.text || elem.textContent || elem.innerHTML || "" ).replace( rcleanScript, "/*$0*/" ) ); + } + + if ( elem.parentNode ) { + elem.parentNode.removeChild( elem ); + } + }); } } @@ -5840,27 +6102,26 @@ function cloneCopyEvent( src, dest ) { return; } - var internalKey = jQuery.expando, - oldData = jQuery.data( src ), - curData = jQuery.data( dest, oldData ); + var type, i, l, + oldData = jQuery._data( src ), + curData = jQuery._data( dest, oldData ), + events = oldData.events; - // Switch to use the internal data object, if it exists, for the next - // stage of data copying - if ( (oldData = oldData[ internalKey ]) ) { - var events = oldData.events; - curData = curData[ internalKey ] = jQuery.extend({}, oldData); + if ( events ) { + delete curData.handle; + curData.events = {}; - if ( events ) { - delete curData.handle; - curData.events = {}; - - for ( var type in events ) { - for ( var i = 0, l = events[ type ].length; i < l; i++ ) { - jQuery.event.add( dest, type + ( events[ type ][ i ].namespace ? "." : "" ) + events[ type ][ i ].namespace, events[ type ][ i ], events[ type ][ i ].data ); - } + for ( type in events ) { + for ( i = 0, l = events[ type ].length; i < l; i++ ) { + jQuery.event.add( dest, type, events[ type ][ i ] ); } } } + + // make the cloned public data object a copy from the original + if ( curData.data ) { + curData.data = jQuery.extend( {}, curData.data ); + } } function cloneFixAttributes( src, dest ) { @@ -5914,24 +6175,34 @@ function cloneFixAttributes( src, dest ) { // cloning other types of input fields } else if ( nodeName === "input" || nodeName === "textarea" ) { dest.defaultValue = src.defaultValue; + + // IE blanks contents when cloning scripts + } else if ( nodeName === "script" && dest.text !== src.text ) { + dest.text = src.text; } // Event data gets referenced instead of copied if the expando // gets copied too dest.removeAttribute( jQuery.expando ); + + // Clear flags for bubbling special change/submit events, they must + // be reattached when the newly cloned events are first activated + dest.removeAttribute( "_submit_attached" ); + dest.removeAttribute( "_change_attached" ); } jQuery.buildFragment = function( args, nodes, scripts ) { - var fragment, cacheable, cacheresults, doc; + var fragment, cacheable, cacheresults, doc, + first = args[ 0 ]; - // nodes may contain either an explicit document object, - // a jQuery collection or context object. - // If nodes[0] contains a valid object to assign to doc - if ( nodes && nodes[0] ) { - doc = nodes[0].ownerDocument || nodes[0]; - } + // nodes may contain either an explicit document object, + // a jQuery collection or context object. + // If nodes[0] contains a valid object to assign to doc + if ( nodes && nodes[0] ) { + doc = nodes[0].ownerDocument || nodes[0]; + } - // Ensure that an attr object doesn't incorrectly stand in as a document object + // Ensure that an attr object doesn't incorrectly stand in as a document object // Chrome and Firefox seem to allow this to occur and will throw exception // Fixes #8950 if ( !doc.createDocumentFragment ) { @@ -5942,12 +6213,15 @@ jQuery.buildFragment = function( args, nodes, scripts ) { // Cloning options loses the selected state, so don't cache them // IE 6 doesn't like it when you put <object> or <embed> elements in a fragment // Also, WebKit does not clone 'checked' attributes on cloneNode, so don't cache - if ( args.length === 1 && typeof args[0] === "string" && args[0].length < 512 && doc === document && - args[0].charAt(0) === "<" && !rnocache.test( args[0] ) && (jQuery.support.checkClone || !rchecked.test( args[0] )) ) { + // Lastly, IE6,7,8 will not correctly reuse cached fragments that were created from unknown elems #10501 + if ( args.length === 1 && typeof first === "string" && first.length < 512 && doc === document && + first.charAt(0) === "<" && !rnocache.test( first ) && + (jQuery.support.checkClone || !rchecked.test( first )) && + (jQuery.support.html5Clone || !rnoshimcache.test( first )) ) { cacheable = true; - cacheresults = jQuery.fragments[ args[0] ]; + cacheresults = jQuery.fragments[ first ]; if ( cacheresults && cacheresults !== 1 ) { fragment = cacheresults; } @@ -5959,7 +6233,7 @@ jQuery.buildFragment = function( args, nodes, scripts ) { } if ( cacheable ) { - jQuery.fragments[ args[0] ] = cacheresults ? fragment : 1; + jQuery.fragments[ first ] = cacheresults ? fragment : 1; } return { fragment: fragment, cacheable: cacheable }; @@ -5985,7 +6259,7 @@ jQuery.each({ } else { for ( var i = 0, l = insert.length; i < l; i++ ) { - var elems = (i > 0 ? this.clone(true) : this).get(); + var elems = ( i > 0 ? this.clone(true) : this ).get(); jQuery( insert[i] )[ original ]( elems ); ret = ret.concat( elems ); } @@ -5996,10 +6270,10 @@ jQuery.each({ }); function getAll( elem ) { - if ( "getElementsByTagName" in elem ) { + if ( typeof elem.getElementsByTagName !== "undefined" ) { return elem.getElementsByTagName( "*" ); - } else if ( "querySelectorAll" in elem ) { + } else if ( typeof elem.querySelectorAll !== "undefined" ) { return elem.querySelectorAll( "*" ); } else { @@ -6015,19 +6289,33 @@ function fixDefaultChecked( elem ) { } // Finds all inputs and passes them to fixDefaultChecked function findInputs( elem ) { - if ( jQuery.nodeName( elem, "input" ) ) { + var nodeName = ( elem.nodeName || "" ).toLowerCase(); + if ( nodeName === "input" ) { fixDefaultChecked( elem ); - } else if ( "getElementsByTagName" in elem ) { + // Skip scripts, get other children + } else if ( nodeName !== "script" && typeof elem.getElementsByTagName !== "undefined" ) { jQuery.grep( elem.getElementsByTagName("input"), fixDefaultChecked ); } } +// Derived From: http://www.iecss.com/shimprove/javascript/shimprove.1-0-1.js +function shimCloneNode( elem ) { + var div = document.createElement( "div" ); + safeFragment.appendChild( div ); + + div.innerHTML = elem.outerHTML; + return div.firstChild; +} + jQuery.extend({ clone: function( elem, dataAndEvents, deepDataAndEvents ) { - var clone = elem.cloneNode(true), - srcElements, - destElements, - i; + var srcElements, + destElements, + i, + // IE<=8 does not properly clone detached, unknown element nodes + clone = jQuery.support.html5Clone || jQuery.isXMLDoc(elem) || !rnoshimcache.test( "<" + elem.nodeName + ">" ) ? + elem.cloneNode( true ) : + shimCloneNode( elem ); if ( (!jQuery.support.noCloneEvent || !jQuery.support.noCloneChecked) && (elem.nodeType === 1 || elem.nodeType === 11) && !jQuery.isXMLDoc(elem) ) { @@ -6039,8 +6327,7 @@ jQuery.extend({ cloneFixAttributes( elem, clone ); - // Using Sizzle here is crazy slow, so we use getElementsByTagName - // instead + // Using Sizzle here is crazy slow, so we use getElementsByTagName instead srcElements = getAll( elem ); destElements = getAll( clone ); @@ -6048,7 +6335,10 @@ jQuery.extend({ // with an element if you are cloning the body and one of the // elements on the page has a name or id of "length" for ( i = 0; srcElements[i]; ++i ) { - cloneFixAttributes( srcElements[i], destElements[i] ); + // Ensure that the destination node is not null; Fixes #9587 + if ( destElements[i] ) { + cloneFixAttributes( srcElements[i], destElements[i] ); + } } } @@ -6073,7 +6363,8 @@ jQuery.extend({ }, clean: function( elems, context, fragment, scripts ) { - var checkScriptType; + var checkScriptType, script, j, + ret = []; context = context || document; @@ -6082,8 +6373,6 @@ jQuery.extend({ context = context.ownerDocument || context[0] && context[0].ownerDocument || document; } - var ret = [], j; - for ( var i = 0, elem; (elem = elems[i]) != null; i++ ) { if ( typeof elem === "number" ) { elem += ""; @@ -6102,10 +6391,21 @@ jQuery.extend({ elem = elem.replace(rxhtmlTag, "<$1></$2>"); // Trim whitespace, otherwise indexOf won't work as expected - var tag = (rtagName.exec( elem ) || ["", ""])[1].toLowerCase(), + var tag = ( rtagName.exec( elem ) || ["", ""] )[1].toLowerCase(), wrap = wrapMap[ tag ] || wrapMap._default, depth = wrap[0], - div = context.createElement("div"); + div = context.createElement("div"), + safeChildNodes = safeFragment.childNodes, + remove; + + // Append wrapper element to unknown element safe doc fragment + if ( context === document ) { + // Use the fragment we've already created for this document + safeFragment.appendChild( div ); + } else { + // Use a fragment created with the owner document + createSafeFragment( context ).appendChild( div ); + } // Go to html and back, then peel off extra wrappers div.innerHTML = wrap[1] + elem + wrap[2]; @@ -6141,6 +6441,21 @@ jQuery.extend({ } elem = div.childNodes; + + // Clear elements from DocumentFragment (safeFragment or otherwise) + // to avoid hoarding elements. Fixes #11356 + if ( div ) { + div.parentNode.removeChild( div ); + + // Guard against -1 index exceptions in FF3.6 + if ( safeChildNodes.length > 0 ) { + remove = safeChildNodes[ safeChildNodes.length - 1 ]; + + if ( remove && remove.parentNode ) { + remove.parentNode.removeChild( remove ); + } + } + } } } @@ -6169,16 +6484,17 @@ jQuery.extend({ return !elem.type || rscriptType.test( elem.type ); }; for ( i = 0; ret[i]; i++ ) { - if ( scripts && jQuery.nodeName( ret[i], "script" ) && (!ret[i].type || ret[i].type.toLowerCase() === "text/javascript") ) { - scripts.push( ret[i].parentNode ? ret[i].parentNode.removeChild( ret[i] ) : ret[i] ); + script = ret[i]; + if ( scripts && jQuery.nodeName( script, "script" ) && (!script.type || rscriptType.test( script.type )) ) { + scripts.push( script.parentNode ? script.parentNode.removeChild( script ) : script ); } else { - if ( ret[i].nodeType === 1 ) { - var jsTags = jQuery.grep( ret[i].getElementsByTagName( "script" ), checkScriptType ); + if ( script.nodeType === 1 ) { + var jsTags = jQuery.grep( script.getElementsByTagName( "script" ), checkScriptType ); ret.splice.apply( ret, [i + 1, 0].concat( jsTags ) ); } - fragment.appendChild( ret[i] ); + fragment.appendChild( script ); } } } @@ -6187,7 +6503,9 @@ jQuery.extend({ }, cleanData: function( elems ) { - var data, id, cache = jQuery.cache, internalKey = jQuery.expando, special = jQuery.event.special, + var data, id, + cache = jQuery.cache, + special = jQuery.event.special, deleteExpando = jQuery.support.deleteExpando; for ( var i = 0, elem; (elem = elems[i]) != null; i++ ) { @@ -6198,7 +6516,7 @@ jQuery.extend({ id = elem[ jQuery.expando ]; if ( id ) { - data = cache[ id ] && cache[ id ][ internalKey ]; + data = cache[ id ]; if ( data && data.events ) { for ( var type in data.events ) { @@ -6230,21 +6548,6 @@ jQuery.extend({ } }); -function evalScript( i, elem ) { - if ( elem.src ) { - jQuery.ajax({ - url: elem.src, - async: false, - dataType: "script" - }); - } else { - jQuery.globalEval( ( elem.text || elem.textContent || elem.innerHTML || "" ).replace( rcleanScript, "/*$0*/" ) ); - } - - if ( elem.parentNode ) { - elem.parentNode.removeChild( elem ); - } -} @@ -6252,30 +6555,27 @@ var ralpha = /alpha\([^)]*\)/i, ropacity = /opacity=([^)]*)/, // fixed for IE9, see #8346 rupper = /([A-Z]|^ms)/g, - rnumpx = /^-?\d+(?:px)?$/i, - rnum = /^-?\d/, - rrelNum = /^[+\-]=/, - rrelNumFilter = /[^+\-\.\de]+/g, + rnum = /^[\-+]?(?:\d*\.)?\d+$/i, + rnumnonpx = /^-?(?:\d*\.)?\d+(?!px)[^\d\s]+$/i, + rrelNum = /^([\-+])=([\-+.\de]+)/, + rmargin = /^margin/, cssShow = { position: "absolute", visibility: "hidden", display: "block" }, - cssWidth = [ "Left", "Right" ], - cssHeight = [ "Top", "Bottom" ], + + // order is important! + cssExpand = [ "Top", "Right", "Bottom", "Left" ], + curCSS, getComputedStyle, currentStyle; jQuery.fn.css = function( name, value ) { - // Setting 'undefined' is a no-op - if ( arguments.length === 2 && value === undefined ) { - return this; - } - - return jQuery.access( this, name, value, true, function( elem, name, value ) { + return jQuery.access( this, function( elem, name, value ) { return value !== undefined ? jQuery.style( elem, name, value ) : jQuery.css( elem, name ); - }); + }, name, value, arguments.length > 1 ); }; jQuery.extend({ @@ -6286,7 +6586,7 @@ jQuery.extend({ get: function( elem, computed ) { if ( computed ) { // We should always get a number back from opacity - var ret = curCSS( elem, "opacity", "opacity" ); + var ret = curCSS( elem, "opacity" ); return ret === "" ? "1" : ret; } else { @@ -6332,18 +6632,18 @@ jQuery.extend({ if ( value !== undefined ) { type = typeof value; - // Make sure that NaN and null values aren't set. See: #7116 - if ( type === "number" && isNaN( value ) || value == null ) { - return; - } - // convert relative number strings (+= or -=) to relative numbers. #7345 - if ( type === "string" && rrelNum.test( value ) ) { - value = +value.replace( rrelNumFilter, "" ) + parseFloat( jQuery.css( elem, name ) ); + if ( type === "string" && (ret = rrelNum.exec( value )) ) { + value = ( +( ret[1] + 1) * +ret[2] ) + parseFloat( jQuery.css( elem, name ) ); // Fixes bug #9237 type = "number"; } + // Make sure that NaN and null values aren't set. See: #7116 + if ( value == null || type === "number" && isNaN( value ) ) { + return; + } + // If a number was passed in, add 'px' to the (except for certain CSS properties) if ( type === "number" && !jQuery.cssNumber[ origName ] ) { value += "px"; @@ -6394,154 +6694,87 @@ jQuery.extend({ // A method for quickly swapping in/out CSS properties to get correct calculations swap: function( elem, options, callback ) { - var old = {}; + var old = {}, + ret, name; // Remember the old values, and insert the new ones - for ( var name in options ) { + for ( name in options ) { old[ name ] = elem.style[ name ]; elem.style[ name ] = options[ name ]; } - callback.call( elem ); + ret = callback.call( elem ); // Revert the old values for ( name in options ) { elem.style[ name ] = old[ name ]; } + + return ret; } }); -// DEPRECATED, Use jQuery.css() instead +// DEPRECATED in 1.3, Use jQuery.css() instead jQuery.curCSS = jQuery.css; -jQuery.each(["height", "width"], function( i, name ) { - jQuery.cssHooks[ name ] = { - get: function( elem, computed, extra ) { - var val; - - if ( computed ) { - if ( elem.offsetWidth !== 0 ) { - return getWH( elem, name, extra ); - } else { - jQuery.swap( elem, cssShow, function() { - val = getWH( elem, name, extra ); - }); - } - - return val; - } - }, - - set: function( elem, value ) { - if ( rnumpx.test( value ) ) { - // ignore negative width and height values #1599 - value = parseFloat( value ); - - if ( value >= 0 ) { - return value + "px"; - } - - } else { - return value; - } - } - }; -}); - -if ( !jQuery.support.opacity ) { - jQuery.cssHooks.opacity = { - get: function( elem, computed ) { - // IE uses filters for opacity - return ropacity.test( (computed && elem.currentStyle ? elem.currentStyle.filter : elem.style.filter) || "" ) ? - ( parseFloat( RegExp.$1 ) / 100 ) + "" : - computed ? "1" : ""; - }, - - set: function( elem, value ) { - var style = elem.style, - currentStyle = elem.currentStyle; - - // IE has trouble with opacity if it does not have layout - // Force it by setting the zoom level - style.zoom = 1; - - // Set the alpha filter to set the opacity - var opacity = jQuery.isNaN( value ) ? - "" : - "alpha(opacity=" + value * 100 + ")", - filter = currentStyle && currentStyle.filter || style.filter || ""; - - style.filter = ralpha.test( filter ) ? - filter.replace( ralpha, opacity ) : - filter + " " + opacity; - } - }; -} - -jQuery(function() { - // This hook cannot be added until DOM ready because the support test - // for it is not run until after DOM ready - if ( !jQuery.support.reliableMarginRight ) { - jQuery.cssHooks.marginRight = { - get: function( elem, computed ) { - // WebKit Bug 13343 - getComputedStyle returns wrong value for margin-right - // Work around by temporarily setting element display to inline-block - var ret; - jQuery.swap( elem, { "display": "inline-block" }, function() { - if ( computed ) { - ret = curCSS( elem, "margin-right", "marginRight" ); - } else { - ret = elem.style.marginRight; - } - }); - return ret; - } - }; - } -}); - if ( document.defaultView && document.defaultView.getComputedStyle ) { getComputedStyle = function( elem, name ) { - var ret, defaultView, computedStyle; + var ret, defaultView, computedStyle, width, + style = elem.style; name = name.replace( rupper, "-$1" ).toLowerCase(); - if ( !(defaultView = elem.ownerDocument.defaultView) ) { - return undefined; - } + if ( (defaultView = elem.ownerDocument.defaultView) && + (computedStyle = defaultView.getComputedStyle( elem, null )) ) { - if ( (computedStyle = defaultView.getComputedStyle( elem, null )) ) { ret = computedStyle.getPropertyValue( name ); if ( ret === "" && !jQuery.contains( elem.ownerDocument.documentElement, elem ) ) { ret = jQuery.style( elem, name ); } } + // A tribute to the "awesome hack by Dean Edwards" + // WebKit uses "computed value (percentage if specified)" instead of "used value" for margins + // which is against the CSSOM draft spec: http://dev.w3.org/csswg/cssom/#resolved-values + if ( !jQuery.support.pixelMargin && computedStyle && rmargin.test( name ) && rnumnonpx.test( ret ) ) { + width = style.width; + style.width = ret; + ret = computedStyle.width; + style.width = width; + } + return ret; }; } if ( document.documentElement.currentStyle ) { currentStyle = function( elem, name ) { - var left, + var left, rsLeft, uncomputed, ret = elem.currentStyle && elem.currentStyle[ name ], - rsLeft = elem.runtimeStyle && elem.runtimeStyle[ name ], style = elem.style; + // Avoid setting ret to empty string here + // so we don't default to auto + if ( ret == null && style && (uncomputed = style[ name ]) ) { + ret = uncomputed; + } + // From the awesome hack by Dean Edwards // http://erik.eae.net/archives/2007/07/27/18.54.15/#comment-102291 // If we're not dealing with a regular pixel number // but a number that has a weird ending, we need to convert it to pixels - if ( !rnumpx.test( ret ) && rnum.test( ret ) ) { + if ( rnumnonpx.test( ret ) ) { + // Remember the original values left = style.left; + rsLeft = elem.runtimeStyle && elem.runtimeStyle.left; // Put in the new values to get a computed value out if ( rsLeft ) { elem.runtimeStyle.left = elem.currentStyle.left; } - style.left = name === "fontSize" ? "1em" : (ret || 0); + style.left = name === "fontSize" ? "1em" : ret; ret = style.pixelLeft + "px"; // Revert the changed values @@ -6557,59 +6790,149 @@ if ( document.documentElement.currentStyle ) { curCSS = getComputedStyle || currentStyle; -function getWH( elem, name, extra ) { +function getWidthOrHeight( elem, name, extra ) { // Start with offset property var val = name === "width" ? elem.offsetWidth : elem.offsetHeight, - which = name === "width" ? cssWidth : cssHeight; + i = name === "width" ? 1 : 0, + len = 4; if ( val > 0 ) { if ( extra !== "border" ) { - jQuery.each( which, function() { + for ( ; i < len; i += 2 ) { if ( !extra ) { - val -= parseFloat( jQuery.css( elem, "padding" + this ) ) || 0; + val -= parseFloat( jQuery.css( elem, "padding" + cssExpand[ i ] ) ) || 0; } if ( extra === "margin" ) { - val += parseFloat( jQuery.css( elem, extra + this ) ) || 0; + val += parseFloat( jQuery.css( elem, extra + cssExpand[ i ] ) ) || 0; } else { - val -= parseFloat( jQuery.css( elem, "border" + this + "Width" ) ) || 0; + val -= parseFloat( jQuery.css( elem, "border" + cssExpand[ i ] + "Width" ) ) || 0; } - }); + } } return val + "px"; } // Fall back to computed then uncomputed css if necessary - val = curCSS( elem, name, name ); + val = curCSS( elem, name ); if ( val < 0 || val == null ) { - val = elem.style[ name ] || 0; + val = elem.style[ name ]; } + + // Computed unit is not pixels. Stop here and return. + if ( rnumnonpx.test(val) ) { + return val; + } + // Normalize "", auto, and prepare for extra val = parseFloat( val ) || 0; // Add padding, border, margin if ( extra ) { - jQuery.each( which, function() { - val += parseFloat( jQuery.css( elem, "padding" + this ) ) || 0; + for ( ; i < len; i += 2 ) { + val += parseFloat( jQuery.css( elem, "padding" + cssExpand[ i ] ) ) || 0; if ( extra !== "padding" ) { - val += parseFloat( jQuery.css( elem, "border" + this + "Width" ) ) || 0; + val += parseFloat( jQuery.css( elem, "border" + cssExpand[ i ] + "Width" ) ) || 0; } if ( extra === "margin" ) { - val += parseFloat( jQuery.css( elem, extra + this ) ) || 0; + val += parseFloat( jQuery.css( elem, extra + cssExpand[ i ]) ) || 0; } - }); + } } return val + "px"; } +jQuery.each([ "height", "width" ], function( i, name ) { + jQuery.cssHooks[ name ] = { + get: function( elem, computed, extra ) { + if ( computed ) { + if ( elem.offsetWidth !== 0 ) { + return getWidthOrHeight( elem, name, extra ); + } else { + return jQuery.swap( elem, cssShow, function() { + return getWidthOrHeight( elem, name, extra ); + }); + } + } + }, + + set: function( elem, value ) { + return rnum.test( value ) ? + value + "px" : + value; + } + }; +}); + +if ( !jQuery.support.opacity ) { + jQuery.cssHooks.opacity = { + get: function( elem, computed ) { + // IE uses filters for opacity + return ropacity.test( (computed && elem.currentStyle ? elem.currentStyle.filter : elem.style.filter) || "" ) ? + ( parseFloat( RegExp.$1 ) / 100 ) + "" : + computed ? "1" : ""; + }, + + set: function( elem, value ) { + var style = elem.style, + currentStyle = elem.currentStyle, + opacity = jQuery.isNumeric( value ) ? "alpha(opacity=" + value * 100 + ")" : "", + filter = currentStyle && currentStyle.filter || style.filter || ""; + + // IE has trouble with opacity if it does not have layout + // Force it by setting the zoom level + style.zoom = 1; + + // if setting opacity to 1, and no other filters exist - attempt to remove filter attribute #6652 + if ( value >= 1 && jQuery.trim( filter.replace( ralpha, "" ) ) === "" ) { + + // Setting style.filter to null, "" & " " still leave "filter:" in the cssText + // if "filter:" is present at all, clearType is disabled, we want to avoid this + // style.removeAttribute is IE Only, but so apparently is this code path... + style.removeAttribute( "filter" ); + + // if there there is no filter style applied in a css rule, we are done + if ( currentStyle && !currentStyle.filter ) { + return; + } + } + + // otherwise, set new filter values + style.filter = ralpha.test( filter ) ? + filter.replace( ralpha, opacity ) : + filter + " " + opacity; + } + }; +} + +jQuery(function() { + // This hook cannot be added until DOM ready because the support test + // for it is not run until after DOM ready + if ( !jQuery.support.reliableMarginRight ) { + jQuery.cssHooks.marginRight = { + get: function( elem, computed ) { + // WebKit Bug 13343 - getComputedStyle returns wrong value for margin-right + // Work around by temporarily setting element display to inline-block + return jQuery.swap( elem, { "display": "inline-block" }, function() { + if ( computed ) { + return curCSS( elem, "margin-right" ); + } else { + return elem.style.marginRight; + } + }); + } + }; + } +}); + if ( jQuery.expr && jQuery.expr.filters ) { jQuery.expr.filters.hidden = function( elem ) { var width = elem.offsetWidth, height = elem.offsetHeight; - return (width === 0 && height === 0) || (!jQuery.support.reliableHiddenOffsets && (elem.style.display || jQuery.css( elem, "display" )) === "none"); + return ( width === 0 && height === 0 ) || (!jQuery.support.reliableHiddenOffsets && ((elem.style && elem.style.display) || jQuery.css( elem, "display" )) === "none"); }; jQuery.expr.filters.visible = function( elem ) { @@ -6617,6 +6940,31 @@ if ( jQuery.expr && jQuery.expr.filters ) { }; } +// These hooks are used by animate to expand properties +jQuery.each({ + margin: "", + padding: "", + border: "Width" +}, function( prefix, suffix ) { + + jQuery.cssHooks[ prefix + suffix ] = { + expand: function( value ) { + var i, + + // assumes a single number if not a string + parts = typeof value === "string" ? value.split(" ") : [ value ], + expanded = {}; + + for ( i = 0; i < 4; i++ ) { + expanded[ prefix + cssExpand[ i ] + suffix ] = + parts[ i ] || parts[ i - 2 ] || parts[ 0 ]; + } + + return expanded; + } + }; +}); + @@ -6625,9 +6973,9 @@ var r20 = /%20/g, rCRLF = /\r?\n/g, rhash = /#.*$/, rheaders = /^(.*?):[ \t]*([^\r\n]*)\r?$/mg, // IE leaves an \r character at EOL - rinput = /^(?:color|date|datetime|email|hidden|month|number|password|range|search|tel|text|time|url|week)$/i, + rinput = /^(?:color|date|datetime|datetime-local|email|hidden|month|number|password|range|search|tel|text|time|url|week)$/i, // #7653, #8125, #8152: local protocol detection - rlocalProtocol = /^(?:about|app|app\-storage|.+\-extension|file|widget):$/, + rlocalProtocol = /^(?:about|app|app\-storage|.+\-extension|file|res|widget):$/, rnoContent = /^(?:GET|HEAD)$/, rprotocol = /^\/\//, rquery = /\?/, @@ -6662,7 +7010,10 @@ var r20 = /%20/g, ajaxLocation, // Document location segments - ajaxLocParts; + ajaxLocParts, + + // Avoid comment-prolog char sequence (#10098); must appease lint and evade compression + allTypes = ["*/"] + ["*"]; // #8138, IE may throw an exception when accessing // a field from window.location if document.domain has been set @@ -6699,7 +7050,7 @@ function addToPrefiltersOrTransports( structure ) { placeBefore; // For each dataType in the dataTypeExpression - for(; i < length; i++ ) { + for ( ; i < length; i++ ) { dataType = dataTypes[ i ]; // We control if we're asked to add before // any existing element @@ -6730,7 +7081,7 @@ function inspectPrefiltersOrTransports( structure, options, originalOptions, jqX executeOnly = ( structure === prefilters ), selection; - for(; i < length && ( executeOnly || !selection ); i++ ) { + for ( ; i < length && ( executeOnly || !selection ); i++ ) { selection = list[ i ]( options, originalOptions, jqXHR ); // If we got redirected to another dataType // we try there if executing only and not done already @@ -6755,6 +7106,22 @@ function inspectPrefiltersOrTransports( structure, options, originalOptions, jqX return selection; } +// A special extend for ajax options +// that takes "flat" options (not to be deep extended) +// Fixes #9887 +function ajaxExtend( target, src ) { + var key, deep, + flatOptions = jQuery.ajaxSettings.flatOptions || {}; + for ( key in src ) { + if ( src[ key ] !== undefined ) { + ( flatOptions[ key ] ? target : ( deep || ( deep = {} ) ) )[ key ] = src[ key ]; + } + } + if ( deep ) { + jQuery.extend( true, target, deep ); + } +} + jQuery.fn.extend({ load: function( url, params, callback ) { if ( typeof url !== "string" && _load ) { @@ -6862,7 +7229,7 @@ jQuery.fn.extend({ // Attach a bunch of functions for handling common AJAX events jQuery.each( "ajaxStart ajaxStop ajaxComplete ajaxError ajaxSuccess ajaxSend".split( " " ), function( i, o ){ jQuery.fn[ o ] = function( f ){ - return this.bind( o, f ); + return this.on( o, f ); }; }); @@ -6898,23 +7265,16 @@ jQuery.extend({ // Creates a full fledged settings object into target // with both ajaxSettings and settings fields. // If target is omitted, writes into ajaxSettings. - ajaxSetup: function ( target, settings ) { - if ( !settings ) { - // Only one parameter, we extend ajaxSettings - settings = target; - target = jQuery.extend( true, jQuery.ajaxSettings, settings ); + ajaxSetup: function( target, settings ) { + if ( settings ) { + // Building a settings object + ajaxExtend( target, jQuery.ajaxSettings ); } else { - // target was provided, we extend into it - jQuery.extend( true, target, jQuery.ajaxSettings, settings ); - } - // Flatten fields we don't want deep extended - for( var field in { context: 1, url: 1 } ) { - if ( field in settings ) { - target[ field ] = settings[ field ]; - } else if( field in jQuery.ajaxSettings ) { - target[ field ] = jQuery.ajaxSettings[ field ]; - } + // Extending ajaxSettings + settings = target; + target = jQuery.ajaxSettings; } + ajaxExtend( target, settings ); return target; }, @@ -6923,7 +7283,7 @@ jQuery.extend({ isLocal: rlocalProtocol.test( ajaxLocParts[ 1 ] ), global: true, type: "GET", - contentType: "application/x-www-form-urlencoded", + contentType: "application/x-www-form-urlencoded; charset=UTF-8", processData: true, async: true, /* @@ -6942,7 +7302,7 @@ jQuery.extend({ html: "text/html", text: "text/plain", json: "application/json, text/javascript", - "*": "*/*" + "*": allTypes }, contents: { @@ -6972,6 +7332,15 @@ jQuery.extend({ // Parse text as xml "text xml": jQuery.parseXML + }, + + // For options that shouldn't be deep extended: + // you can add your own custom options here if + // and when you create one that shouldn't be + // deep extended (see ajaxExtend) + flatOptions: { + context: true, + url: true } }, @@ -7002,7 +7371,7 @@ jQuery.extend({ jQuery( callbackContext ) : jQuery.event, // Deferreds deferred = jQuery.Deferred(), - completeDeferred = jQuery._Deferred(), + completeDeferred = jQuery.Callbacks( "once memory" ), // Status-dependent callbacks statusCode = s.statusCode || {}, // ifModified key @@ -7082,7 +7451,7 @@ jQuery.extend({ // Callback for when everything is done // It is defined here because jslint complains if it is declared // at the end of the function (which would be more logical and readable) - function done( status, statusText, responses, headers ) { + function done( status, nativeStatusText, responses, headers ) { // Called once if ( state === 2 ) { @@ -7105,11 +7474,12 @@ jQuery.extend({ responseHeadersString = headers || ""; // Set readyState - jqXHR.readyState = status ? 4 : 0; + jqXHR.readyState = status > 0 ? 4 : 0; var isSuccess, success, error, + statusText = nativeStatusText, response = responses ? ajaxHandleResponses( s, jqXHR, responses ) : undefined, lastModified, etag; @@ -7151,7 +7521,7 @@ jQuery.extend({ // We extract error from statusText // then normalize statusText and status for non-aborts error = statusText; - if( !statusText || status ) { + if ( !statusText || status ) { statusText = "error"; if ( status < 0 ) { status = 0; @@ -7161,7 +7531,7 @@ jQuery.extend({ // Set data for the fake xhr object jqXHR.status = status; - jqXHR.statusText = statusText; + jqXHR.statusText = "" + ( nativeStatusText || statusText ); // Success/Error if ( isSuccess ) { @@ -7180,10 +7550,10 @@ jQuery.extend({ } // Complete - completeDeferred.resolveWith( callbackContext, [ jqXHR, statusText ] ); + completeDeferred.fireWith( callbackContext, [ jqXHR, statusText ] ); if ( fireGlobals ) { - globalEventContext.trigger( "ajaxComplete", [ jqXHR, s] ); + globalEventContext.trigger( "ajaxComplete", [ jqXHR, s ] ); // Handle the global AJAX counter if ( !( --jQuery.active ) ) { jQuery.event.trigger( "ajaxStop" ); @@ -7195,14 +7565,14 @@ jQuery.extend({ deferred.promise( jqXHR ); jqXHR.success = jqXHR.done; jqXHR.error = jqXHR.fail; - jqXHR.complete = completeDeferred.done; + jqXHR.complete = completeDeferred.add; // Status-dependent callbacks jqXHR.statusCode = function( map ) { if ( map ) { var tmp; if ( state < 2 ) { - for( tmp in map ) { + for ( tmp in map ) { statusCode[ tmp ] = [ statusCode[tmp], map[tmp] ]; } } else { @@ -7239,7 +7609,7 @@ jQuery.extend({ // Apply prefilters inspectPrefiltersOrTransports( prefilters, s, options, jqXHR ); - // If request was aborted inside a prefiler, stop there + // If request was aborted inside a prefilter, stop there if ( state === 2 ) { return false; } @@ -7264,6 +7634,8 @@ jQuery.extend({ // If data is available, append data to url if ( s.data ) { s.url += ( rquery.test( s.url ) ? "&" : "?" ) + s.data; + // #9682: remove data so that it's not used in an eventual retry + delete s.data; } // Get ifModifiedKey before adding the anti-cache parameter @@ -7277,7 +7649,7 @@ jQuery.extend({ ret = s.url.replace( rts, "$1_=" + ts ); // if nothing was replaced, add timestamp to the end - s.url = ret + ( (ret === s.url ) ? ( rquery.test( s.url ) ? "&" : "?" ) + "_=" + ts : "" ); + s.url = ret + ( ( ret === s.url ) ? ( rquery.test( s.url ) ? "&" : "?" ) + "_=" + ts : "" ); } } @@ -7301,7 +7673,7 @@ jQuery.extend({ jqXHR.setRequestHeader( "Accept", s.dataTypes[ 0 ] && s.accepts[ s.dataTypes[0] ] ? - s.accepts[ s.dataTypes[0] ] + ( s.dataTypes[ 0 ] !== "*" ? ", */*; q=0.01" : "" ) : + s.accepts[ s.dataTypes[0] ] + ( s.dataTypes[ 0 ] !== "*" ? ", " + allTypes + "; q=0.01" : "" ) : s.accepts[ "*" ] ); @@ -7347,11 +7719,11 @@ jQuery.extend({ transport.send( requestHeaders, done ); } catch (e) { // Propagate exception as error if not done - if ( status < 2 ) { + if ( state < 2 ) { done( -1, e ); // Simply rethrow otherwise } else { - jQuery.error( e ); + throw e; } } } @@ -7410,11 +7782,11 @@ function buildParams( prefix, obj, traditional, add ) { // a server error. Possible fixes are to modify rack's // deserialization algorithm or to provide an option or flag // to force array serialization to be shallow. - buildParams( prefix + "[" + ( typeof v === "object" || jQuery.isArray(v) ? i : "" ) + "]", v, traditional, add ); + buildParams( prefix + "[" + ( typeof v === "object" ? i : "" ) + "]", v, traditional, add ); } }); - } else if ( !traditional && obj != null && typeof obj === "object" ) { + } else if ( !traditional && jQuery.type( obj ) === "object" ) { // Serialize object item. for ( var name in obj ) { buildParams( prefix + "[" + name + "]", obj[ name ], traditional, add ); @@ -7455,7 +7827,7 @@ function ajaxHandleResponses( s, jqXHR, responses ) { firstDataType; // Fill responseXXX fields - for( type in responseFields ) { + for ( type in responseFields ) { if ( type in responses ) { jqXHR[ responseFields[type] ] = responses[ type ]; } @@ -7534,13 +7906,13 @@ function ajaxConvert( s, response ) { conv2; // For each dataType in the chain - for( i = 1; i < length; i++ ) { + for ( i = 1; i < length; i++ ) { // Create converters map // with lowercased keys if ( i === 1 ) { - for( key in s.converters ) { - if( typeof key === "string" ) { + for ( key in s.converters ) { + if ( typeof key === "string" ) { converters[ key.toLowerCase() ] = s.converters[ key ]; } } @@ -7551,7 +7923,7 @@ function ajaxConvert( s, response ) { current = dataTypes[ i ]; // If current is auto dataType, update it to prev - if( current === "*" ) { + if ( current === "*" ) { current = prev; // If no auto and dataTypes are actually different } else if ( prev !== "*" && prev !== current ) { @@ -7563,7 +7935,7 @@ function ajaxConvert( s, response ) { // If there is no direct converter, search transitively if ( !conv ) { conv2 = undefined; - for( conv1 in converters ) { + for ( conv1 in converters ) { tmp = conv1.split( " " ); if ( tmp[ 0 ] === prev || tmp[ 0 ] === "*" ) { conv2 = converters[ tmp[1] + " " + current ]; @@ -7610,8 +7982,7 @@ jQuery.ajaxSetup({ // Detect, normalize options and install callbacks for jsonp requests jQuery.ajaxPrefilter( "json jsonp", function( s, originalSettings, jqXHR ) { - var inspectData = s.contentType === "application/x-www-form-urlencoded" && - ( typeof s.data === "string" ); + var inspectData = ( typeof s.data === "string" ) && /^application\/x\-www\-form\-urlencoded/.test( s.contentType ); if ( s.dataTypes[ 0 ] === "jsonp" || s.jsonp !== false && ( jsre.test( s.url ) || @@ -7912,7 +8283,13 @@ if ( jQuery.support.ajax ) { if ( xml && xml.documentElement /* #4958 */ ) { responses.xml = xml; } - responses.text = xhr.responseText; + + // When requesting binary data, IE6-9 will throw an exception + // on any attempt to access responseText (#11426) + try { + responses.text = xhr.responseText; + } catch( _ ) { + } // Firefox throws an exception when accessing // statusText for faulty cross-domain requests @@ -7995,21 +8372,18 @@ var elemdisplay = {}, // opacity animations [ "opacity" ] ], - fxNow, - requestAnimationFrame = window.webkitRequestAnimationFrame || - window.mozRequestAnimationFrame || - window.oRequestAnimationFrame; + fxNow; jQuery.fn.extend({ show: function( speed, easing, callback ) { var elem, display; if ( speed || speed === 0 ) { - return this.animate( genFx("show", 3), speed, easing, callback); + return this.animate( genFx("show", 3), speed, easing, callback ); } else { for ( var i = 0, j = this.length; i < j; i++ ) { - elem = this[i]; + elem = this[ i ]; if ( elem.style ) { display = elem.style.display; @@ -8023,8 +8397,9 @@ jQuery.fn.extend({ // Set elements which have been overridden with display: none // in a stylesheet to whatever the default browser style is // for such an element - if ( display === "" && jQuery.css( elem, "display" ) === "none" ) { - jQuery._data(elem, "olddisplay", defaultDisplay(elem.nodeName)); + if ( (display === "" && jQuery.css(elem, "display") === "none") || + !jQuery.contains( elem.ownerDocument.documentElement, elem ) ) { + jQuery._data( elem, "olddisplay", defaultDisplay(elem.nodeName) ); } } } @@ -8032,13 +8407,13 @@ jQuery.fn.extend({ // Set the display of most of the elements in a second loop // to avoid the constant reflow for ( i = 0; i < j; i++ ) { - elem = this[i]; + elem = this[ i ]; if ( elem.style ) { display = elem.style.display; if ( display === "" || display === "none" ) { - elem.style.display = jQuery._data(elem, "olddisplay") || ""; + elem.style.display = jQuery._data( elem, "olddisplay" ) || ""; } } } @@ -8052,12 +8427,17 @@ jQuery.fn.extend({ return this.animate( genFx("hide", 3), speed, easing, callback); } else { - for ( var i = 0, j = this.length; i < j; i++ ) { - if ( this[i].style ) { - var display = jQuery.css( this[i], "display" ); + var elem, display, + i = 0, + j = this.length; - if ( display !== "none" && !jQuery._data( this[i], "olddisplay" ) ) { - jQuery._data( this[i], "olddisplay", display ); + for ( ; i < j; i++ ) { + elem = this[i]; + if ( elem.style ) { + display = jQuery.css( elem, "display" ); + + if ( display !== "none" && !jQuery._data( elem, "olddisplay" ) ) { + jQuery._data( elem, "olddisplay", display ); } } } @@ -8102,7 +8482,7 @@ jQuery.fn.extend({ }, animate: function( prop, speed, easing, callback ) { - var optall = jQuery.speed(speed, easing, callback); + var optall = jQuery.speed( speed, easing, callback ); if ( jQuery.isEmptyObject( prop ) ) { return this.each( optall.complete, [ false ] ); @@ -8111,7 +8491,7 @@ jQuery.fn.extend({ // Do not change referenced properties as per-property easing will be lost prop = jQuery.extend( {}, prop ); - return this[ optall.queue === false ? "each" : "queue" ](function() { + function doAnimation() { // XXX 'this' does not always have a nodeName when running the // test suite @@ -8122,24 +8502,37 @@ jQuery.fn.extend({ var opt = jQuery.extend( {}, optall ), isElement = this.nodeType === 1, hidden = isElement && jQuery(this).is(":hidden"), - name, val, p, - display, e, - parts, start, end, unit; + name, val, p, e, hooks, replace, + parts, start, end, unit, + method; // will store per property easing and be used to determine when an animation is complete opt.animatedProperties = {}; + // first pass over propertys to expand / normalize for ( p in prop ) { - - // property name normalization name = jQuery.camelCase( p ); if ( p !== name ) { prop[ name ] = prop[ p ]; delete prop[ p ]; } - val = prop[ name ]; + if ( ( hooks = jQuery.cssHooks[ name ] ) && "expand" in hooks ) { + replace = hooks.expand( prop[ name ] ); + delete prop[ name ]; + // not quite $.extend, this wont overwrite keys already present. + // also - reusing 'p' from above because we have the correct "name" + for ( p in replace ) { + if ( ! ( p in prop ) ) { + prop[ p ] = replace[ p ]; + } + } + } + } + + for ( name in prop ) { + val = prop[ name ]; // easing resolution: per property > opt.specialEasing > opt.easing > 'swing' (default) if ( jQuery.isArray( val ) ) { opt.animatedProperties[ name ] = val[ 1 ]; @@ -8160,25 +8553,17 @@ jQuery.fn.extend({ opt.overflow = [ this.style.overflow, this.style.overflowX, this.style.overflowY ]; // Set display property to inline-block for height/width - // animations on inline elements that are having width/height - // animated + // animations on inline elements that are having width/height animated if ( jQuery.css( this, "display" ) === "inline" && jQuery.css( this, "float" ) === "none" ) { - if ( !jQuery.support.inlineBlockNeedsLayout ) { + + // inline-level elements accept inline-block; + // block-level elements need to be inline with layout + if ( !jQuery.support.inlineBlockNeedsLayout || defaultDisplay( this.nodeName ) === "inline" ) { this.style.display = "inline-block"; } else { - display = defaultDisplay( this.nodeName ); - - // inline-level elements accept inline-block; - // block-level elements need to be inline with layout - if ( display === "inline" ) { - this.style.display = "inline-block"; - - } else { - this.style.display = "inline"; - this.style.zoom = 1; - } + this.style.zoom = 1; } } } @@ -8192,8 +8577,17 @@ jQuery.fn.extend({ e = new jQuery.fx( this, opt, p ); val = prop[ p ]; - if ( rfxtypes.test(val) ) { - e[ val === "toggle" ? hidden ? "show" : "hide" : val ](); + if ( rfxtypes.test( val ) ) { + + // Tracks whether to show or hide based on private + // data attached to the element + method = jQuery._data( this, "toggle" + p ) || ( val === "toggle" ? hidden ? "show" : "hide" : 0 ); + if ( method ) { + jQuery._data( this, "toggle" + p, method === "show" ? "hide" : "show" ); + e[ method ](); + } else { + e[ val ](); + } } else { parts = rfxnum.exec( val ); @@ -8206,7 +8600,7 @@ jQuery.fn.extend({ // We need to compute starting value if ( unit !== "px" ) { jQuery.style( this, p, (end || 1) + unit); - start = ((end || 1) / e.cur()) * start; + start = ( (end || 1) / e.cur() ) * start; jQuery.style( this, p, start + unit); } @@ -8225,39 +8619,71 @@ jQuery.fn.extend({ // For JS strict compliance return true; - }); - }, - - stop: function( clearQueue, gotoEnd ) { - if ( clearQueue ) { - this.queue([]); } - this.each(function() { - var timers = jQuery.timers, - i = timers.length; + return optall.queue === false ? + this.each( doAnimation ) : + this.queue( optall.queue, doAnimation ); + }, + + stop: function( type, clearQueue, gotoEnd ) { + if ( typeof type !== "string" ) { + gotoEnd = clearQueue; + clearQueue = type; + type = undefined; + } + if ( clearQueue && type !== false ) { + this.queue( type || "fx", [] ); + } + + return this.each(function() { + var index, + hadTimers = false, + timers = jQuery.timers, + data = jQuery._data( this ); + // clear marker counters if we know they won't be if ( !gotoEnd ) { jQuery._unmark( true, this ); } - while ( i-- ) { - if ( timers[i].elem === this ) { - if (gotoEnd) { - // force the next step to be the last - timers[i](true); - } - timers.splice(i, 1); + function stopQueue( elem, data, index ) { + var hooks = data[ index ]; + jQuery.removeData( elem, index, true ); + hooks.stop( gotoEnd ); + } + + if ( type == null ) { + for ( index in data ) { + if ( data[ index ] && data[ index ].stop && index.indexOf(".run") === index.length - 4 ) { + stopQueue( this, data, index ); + } + } + } else if ( data[ index = type + ".run" ] && data[ index ].stop ){ + stopQueue( this, data, index ); + } + + for ( index = timers.length; index--; ) { + if ( timers[ index ].elem === this && (type == null || timers[ index ].queue === type) ) { + if ( gotoEnd ) { + + // force the next step to be the last + timers[ index ]( true ); + } else { + timers[ index ].saveState(); + } + hadTimers = true; + timers.splice( index, 1 ); } } + + // start the next in the queue if the last step wasn't forced + // timers currently will call their complete callbacks, which will dequeue + // but only if they were gotoEnd + if ( !( gotoEnd && hadTimers ) ) { + jQuery.dequeue( this, type ); + } }); - - // start the next in the queue if the last step wasn't forced - if ( !gotoEnd ) { - this.dequeue(); - } - - return this; } }); @@ -8276,7 +8702,7 @@ function clearFxNow() { function genFx( type, num ) { var obj = {}; - jQuery.each( fxAttrs.concat.apply([], fxAttrs.slice(0,num)), function() { + jQuery.each( fxAttrs.concat.apply([], fxAttrs.slice( 0, num )), function() { obj[ this ] = type; }); @@ -8285,9 +8711,9 @@ function genFx( type, num ) { // Generate shortcuts for custom animations jQuery.each({ - slideDown: genFx("show", 1), - slideUp: genFx("hide", 1), - slideToggle: genFx("toggle", 1), + slideDown: genFx( "show", 1 ), + slideUp: genFx( "hide", 1 ), + slideToggle: genFx( "toggle", 1 ), fadeIn: { opacity: "show" }, fadeOut: { opacity: "hide" }, fadeToggle: { opacity: "toggle" } @@ -8299,25 +8725,31 @@ jQuery.each({ jQuery.extend({ speed: function( speed, easing, fn ) { - var opt = speed && typeof speed === "object" ? jQuery.extend({}, speed) : { + var opt = speed && typeof speed === "object" ? jQuery.extend( {}, speed ) : { complete: fn || !fn && easing || jQuery.isFunction( speed ) && speed, duration: speed, - easing: fn && easing || easing && !jQuery.isFunction(easing) && easing + easing: fn && easing || easing && !jQuery.isFunction( easing ) && easing }; opt.duration = jQuery.fx.off ? 0 : typeof opt.duration === "number" ? opt.duration : - opt.duration in jQuery.fx.speeds ? jQuery.fx.speeds[opt.duration] : jQuery.fx.speeds._default; + opt.duration in jQuery.fx.speeds ? jQuery.fx.speeds[ opt.duration ] : jQuery.fx.speeds._default; + + // normalize opt.queue - true/undefined/null -> "fx" + if ( opt.queue == null || opt.queue === true ) { + opt.queue = "fx"; + } // Queueing opt.old = opt.complete; + opt.complete = function( noUnmark ) { if ( jQuery.isFunction( opt.old ) ) { opt.old.call( this ); } - if ( opt.queue !== false ) { - jQuery.dequeue( this ); + if ( opt.queue ) { + jQuery.dequeue( this, opt.queue ); } else if ( noUnmark !== false ) { jQuery._unmark( this ); } @@ -8327,11 +8759,11 @@ jQuery.extend({ }, easing: { - linear: function( p, n, firstNum, diff ) { - return firstNum + diff * p; + linear: function( p ) { + return p; }, - swing: function( p, n, firstNum, diff ) { - return ((-Math.cos(p*Math.PI)/2) + 0.5) * diff + firstNum; + swing: function( p ) { + return ( -Math.cos( p*Math.PI ) / 2 ) + 0.5; } }, @@ -8354,12 +8786,12 @@ jQuery.fx.prototype = { this.options.step.call( this.elem, this.now, this ); } - (jQuery.fx.step[this.prop] || jQuery.fx.step._default)( this ); + ( jQuery.fx.step[ this.prop ] || jQuery.fx.step._default )( this ); }, // Get the current size cur: function() { - if ( this.elem[this.prop] != null && (!this.elem.style || this.elem.style[this.prop] == null) ) { + if ( this.elem[ this.prop ] != null && (!this.elem.style || this.elem.style[ this.prop ] == null) ) { return this.elem[ this.prop ]; } @@ -8374,50 +8806,51 @@ jQuery.fx.prototype = { // Start an animation from one number to another custom: function( from, to, unit ) { var self = this, - fx = jQuery.fx, - raf; + fx = jQuery.fx; this.startTime = fxNow || createFxNow(); - this.start = from; this.end = to; - this.unit = unit || this.unit || ( jQuery.cssNumber[ this.prop ] ? "" : "px" ); - this.now = this.start; + this.now = this.start = from; this.pos = this.state = 0; + this.unit = unit || this.unit || ( jQuery.cssNumber[ this.prop ] ? "" : "px" ); function t( gotoEnd ) { - return self.step(gotoEnd); + return self.step( gotoEnd ); } + t.queue = this.options.queue; t.elem = this.elem; + t.saveState = function() { + if ( jQuery._data( self.elem, "fxshow" + self.prop ) === undefined ) { + if ( self.options.hide ) { + jQuery._data( self.elem, "fxshow" + self.prop, self.start ); + } else if ( self.options.show ) { + jQuery._data( self.elem, "fxshow" + self.prop, self.end ); + } + } + }; if ( t() && jQuery.timers.push(t) && !timerId ) { - // Use requestAnimationFrame instead of setInterval if available - if ( requestAnimationFrame ) { - timerId = true; - raf = function() { - // When timerId gets set to null at any point, this stops - if ( timerId ) { - requestAnimationFrame( raf ); - fx.tick(); - } - }; - requestAnimationFrame( raf ); - } else { - timerId = setInterval( fx.tick, fx.interval ); - } + timerId = setInterval( fx.tick, fx.interval ); } }, // Simple 'show' function show: function() { + var dataShow = jQuery._data( this.elem, "fxshow" + this.prop ); + // Remember where we started, so that we can go back to it later - this.options.orig[this.prop] = jQuery.style( this.elem, this.prop ); + this.options.orig[ this.prop ] = dataShow || jQuery.style( this.elem, this.prop ); this.options.show = true; // Begin the animation - // Make sure that we start at a small width/height to avoid any - // flash of content - this.custom(this.prop === "width" || this.prop === "height" ? 1 : 0, this.cur()); + // Make sure that we start at a small width/height to avoid any flash of content + if ( dataShow !== undefined ) { + // This show is picking up where a previous hide or show left off + this.custom( this.cur(), dataShow ); + } else { + this.custom( this.prop === "width" || this.prop === "height" ? 1 : 0, this.cur() ); + } // Start by showing the element jQuery( this.elem ).show(); @@ -8426,20 +8859,20 @@ jQuery.fx.prototype = { // Simple 'hide' function hide: function() { // Remember where we started, so that we can go back to it later - this.options.orig[this.prop] = jQuery.style( this.elem, this.prop ); + this.options.orig[ this.prop ] = jQuery._data( this.elem, "fxshow" + this.prop ) || jQuery.style( this.elem, this.prop ); this.options.hide = true; // Begin the animation - this.custom(this.cur(), 0); + this.custom( this.cur(), 0 ); }, // Each step of an animation step: function( gotoEnd ) { - var t = fxNow || createFxNow(), + var p, n, complete, + t = fxNow || createFxNow(), done = true, elem = this.elem, - options = this.options, - i, n; + options = this.options; if ( gotoEnd || t >= options.duration + this.startTime ) { this.now = this.end; @@ -8448,8 +8881,8 @@ jQuery.fx.prototype = { options.animatedProperties[ this.prop ] = true; - for ( i in options.animatedProperties ) { - if ( options.animatedProperties[i] !== true ) { + for ( p in options.animatedProperties ) { + if ( options.animatedProperties[ p ] !== true ) { done = false; } } @@ -8458,25 +8891,36 @@ jQuery.fx.prototype = { // Reset the overflow if ( options.overflow != null && !jQuery.support.shrinkWrapBlocks ) { - jQuery.each( [ "", "X", "Y" ], function (index, value) { - elem.style[ "overflow" + value ] = options.overflow[index]; + jQuery.each( [ "", "X", "Y" ], function( index, value ) { + elem.style[ "overflow" + value ] = options.overflow[ index ]; }); } // Hide the element if the "hide" operation was done if ( options.hide ) { - jQuery(elem).hide(); + jQuery( elem ).hide(); } // Reset the properties, if the item has been hidden or shown if ( options.hide || options.show ) { - for ( var p in options.animatedProperties ) { - jQuery.style( elem, p, options.orig[p] ); + for ( p in options.animatedProperties ) { + jQuery.style( elem, p, options.orig[ p ] ); + jQuery.removeData( elem, "fxshow" + p, true ); + // Toggle data is no longer needed + jQuery.removeData( elem, "toggle" + p, true ); } } // Execute the complete function - options.complete.call( elem ); + // in the event that the complete function throws an exception + // we must ensure it won't be called twice. #5684 + + complete = options.complete; + if ( complete ) { + + options.complete = false; + complete.call( elem ); + } } return false; @@ -8490,8 +8934,8 @@ jQuery.fx.prototype = { this.state = n / options.duration; // Perform the easing function, defaults to swing - this.pos = jQuery.easing[ options.animatedProperties[ this.prop ] ]( this.state, n, 0, 1, options.duration ); - this.now = this.start + ((this.end - this.start) * this.pos); + this.pos = jQuery.easing[ options.animatedProperties[this.prop] ]( this.state, n, 0, 1, options.duration ); + this.now = this.start + ( (this.end - this.start) * this.pos ); } // Perform the next step of the animation this.update(); @@ -8503,9 +8947,15 @@ jQuery.fx.prototype = { jQuery.extend( jQuery.fx, { tick: function() { - for ( var timers = jQuery.timers, i = 0 ; i < timers.length ; ++i ) { - if ( !timers[i]() ) { - timers.splice(i--, 1); + var timer, + timers = jQuery.timers, + i = 0; + + for ( ; i < timers.length; i++ ) { + timer = timers[ i ]; + // Checks the timer has not already been removed + if ( !timer() && timers[ i ] === timer ) { + timers.splice( i--, 1 ); } } @@ -8535,7 +8985,7 @@ jQuery.extend( jQuery.fx, { _default: function( fx ) { if ( fx.elem.style && fx.elem.style[ fx.prop ] != null ) { - fx.elem.style[ fx.prop ] = (fx.prop === "width" || fx.prop === "height" ? Math.max(0, fx.now) : fx.now) + fx.unit; + fx.elem.style[ fx.prop ] = fx.now + fx.unit; } else { fx.elem[ fx.prop ] = fx.now; } @@ -8543,6 +8993,16 @@ jQuery.extend( jQuery.fx, { } }); +// Ensure props that can't be negative don't go there on undershoot easing +jQuery.each( fxAttrs.concat.apply( [], fxAttrs ), function( i, prop ) { + // exclude marginTop, marginLeft, marginBottom and marginRight from this list + if ( prop.indexOf( "margin" ) ) { + jQuery.fx.step[ prop ] = function( fx ) { + jQuery.style( fx.elem, prop, Math.max(0, fx.now) + fx.unit ); + }; + } +}); + if ( jQuery.expr && jQuery.expr.filters ) { jQuery.expr.filters.animated = function( elem ) { return jQuery.grep(jQuery.timers, function( fn ) { @@ -8559,7 +9019,6 @@ function defaultDisplay( nodeName ) { var body = document.body, elem = jQuery( "<" + nodeName + ">" ).appendTo( body ), display = elem.css( "display" ); - elem.remove(); // If the simple way fails, @@ -8578,7 +9037,7 @@ function defaultDisplay( nodeName ) { // document to it; WebKit & Firefox won't allow reusing the iframe document. if ( !iframeDoc || !iframe.createElement ) { iframeDoc = ( iframe.contentWindow || iframe.contentDocument ).document; - iframeDoc.write( ( document.compatMode === "CSS1Compat" ? "<!doctype html>" : "" ) + "<html><body>" ); + iframeDoc.write( ( jQuery.support.boxModel ? "<!doctype html>" : "" ) + "<html><body>" ); iframeDoc.close(); } @@ -8587,7 +9046,6 @@ function defaultDisplay( nodeName ) { iframeDoc.body.appendChild( elem ); display = jQuery.css( elem, "display" ); - body.removeChild( iframe ); } @@ -8601,41 +9059,23 @@ function defaultDisplay( nodeName ) { -var rtable = /^t(?:able|d|h)$/i, +var getOffset, + rtable = /^t(?:able|d|h)$/i, rroot = /^(?:body|html)$/i; if ( "getBoundingClientRect" in document.documentElement ) { - jQuery.fn.offset = function( options ) { - var elem = this[0], box; - - if ( options ) { - return this.each(function( i ) { - jQuery.offset.setOffset( this, options, i ); - }); - } - - if ( !elem || !elem.ownerDocument ) { - return null; - } - - if ( elem === elem.ownerDocument.body ) { - return jQuery.offset.bodyOffset( elem ); - } - + getOffset = function( elem, doc, docElem, box ) { try { box = elem.getBoundingClientRect(); } catch(e) {} - var doc = elem.ownerDocument, - docElem = doc.documentElement; - // Make sure we're not dealing with a disconnected DOM node if ( !box || !jQuery.contains( docElem, elem ) ) { return box ? { top: box.top, left: box.left } : { top: 0, left: 0 }; } var body = doc.body, - win = getWindow(doc), + win = getWindow( doc ), clientTop = docElem.clientTop || body.clientTop || 0, clientLeft = docElem.clientLeft || body.clientLeft || 0, scrollTop = win.pageYOffset || jQuery.support.boxModel && docElem.scrollTop || body.scrollTop, @@ -8647,30 +9087,10 @@ if ( "getBoundingClientRect" in document.documentElement ) { }; } else { - jQuery.fn.offset = function( options ) { - var elem = this[0]; - - if ( options ) { - return this.each(function( i ) { - jQuery.offset.setOffset( this, options, i ); - }); - } - - if ( !elem || !elem.ownerDocument ) { - return null; - } - - if ( elem === elem.ownerDocument.body ) { - return jQuery.offset.bodyOffset( elem ); - } - - jQuery.offset.initialize(); - + getOffset = function( elem, doc, docElem ) { var computedStyle, offsetParent = elem.offsetParent, prevOffsetParent = elem, - doc = elem.ownerDocument, - docElem = doc.documentElement, body = doc.body, defaultView = doc.defaultView, prevComputedStyle = defaultView ? defaultView.getComputedStyle( elem, null ) : elem.currentStyle, @@ -8678,7 +9098,7 @@ if ( "getBoundingClientRect" in document.documentElement ) { left = elem.offsetLeft; while ( (elem = elem.parentNode) && elem !== body && elem !== docElem ) { - if ( jQuery.offset.supportsFixedPosition && prevComputedStyle.position === "fixed" ) { + if ( jQuery.support.fixedPosition && prevComputedStyle.position === "fixed" ) { break; } @@ -8690,7 +9110,7 @@ if ( "getBoundingClientRect" in document.documentElement ) { top += elem.offsetTop; left += elem.offsetLeft; - if ( jQuery.offset.doesNotAddBorder && !(jQuery.offset.doesAddBorderForTableAndCells && rtable.test(elem.nodeName)) ) { + if ( jQuery.support.doesNotAddBorder && !(jQuery.support.doesAddBorderForTableAndCells && rtable.test(elem.nodeName)) ) { top += parseFloat( computedStyle.borderTopWidth ) || 0; left += parseFloat( computedStyle.borderLeftWidth ) || 0; } @@ -8699,7 +9119,7 @@ if ( "getBoundingClientRect" in document.documentElement ) { offsetParent = elem.offsetParent; } - if ( jQuery.offset.subtractsBorderForOverflowNotVisible && computedStyle.overflow !== "visible" ) { + if ( jQuery.support.subtractsBorderForOverflowNotVisible && computedStyle.overflow !== "visible" ) { top += parseFloat( computedStyle.borderTopWidth ) || 0; left += parseFloat( computedStyle.borderLeftWidth ) || 0; } @@ -8712,7 +9132,7 @@ if ( "getBoundingClientRect" in document.documentElement ) { left += body.offsetLeft; } - if ( jQuery.offset.supportsFixedPosition && prevComputedStyle.position === "fixed" ) { + if ( jQuery.support.fixedPosition && prevComputedStyle.position === "fixed" ) { top += Math.max( docElem.scrollTop, body.scrollTop ); left += Math.max( docElem.scrollLeft, body.scrollLeft ); } @@ -8721,47 +9141,36 @@ if ( "getBoundingClientRect" in document.documentElement ) { }; } +jQuery.fn.offset = function( options ) { + if ( arguments.length ) { + return options === undefined ? + this : + this.each(function( i ) { + jQuery.offset.setOffset( this, options, i ); + }); + } + + var elem = this[0], + doc = elem && elem.ownerDocument; + + if ( !doc ) { + return null; + } + + if ( elem === doc.body ) { + return jQuery.offset.bodyOffset( elem ); + } + + return getOffset( elem, doc, doc.documentElement ); +}; + jQuery.offset = { - initialize: function() { - var body = document.body, container = document.createElement("div"), innerDiv, checkDiv, table, td, bodyMarginTop = parseFloat( jQuery.css(body, "marginTop") ) || 0, - html = "<div style='position:absolute;top:0;left:0;margin:0;border:5px solid #000;padding:0;width:1px;height:1px;'><div></div></div><table style='position:absolute;top:0;left:0;margin:0;border:5px solid #000;padding:0;width:1px;height:1px;' cellpadding='0' cellspacing='0'><tr><td></td></tr></table>"; - - jQuery.extend( container.style, { position: "absolute", top: 0, left: 0, margin: 0, border: 0, width: "1px", height: "1px", visibility: "hidden" } ); - - container.innerHTML = html; - body.insertBefore( container, body.firstChild ); - innerDiv = container.firstChild; - checkDiv = innerDiv.firstChild; - td = innerDiv.nextSibling.firstChild.firstChild; - - this.doesNotAddBorder = (checkDiv.offsetTop !== 5); - this.doesAddBorderForTableAndCells = (td.offsetTop === 5); - - checkDiv.style.position = "fixed"; - checkDiv.style.top = "20px"; - - // safari subtracts parent border width here which is 5px - this.supportsFixedPosition = (checkDiv.offsetTop === 20 || checkDiv.offsetTop === 15); - checkDiv.style.position = checkDiv.style.top = ""; - - innerDiv.style.overflow = "hidden"; - innerDiv.style.position = "relative"; - - this.subtractsBorderForOverflowNotVisible = (checkDiv.offsetTop === -5); - - this.doesNotIncludeMarginInBodyOffset = (body.offsetTop !== bodyMarginTop); - - body.removeChild( container ); - jQuery.offset.initialize = jQuery.noop; - }, bodyOffset: function( body ) { var top = body.offsetTop, left = body.offsetLeft; - jQuery.offset.initialize(); - - if ( jQuery.offset.doesNotIncludeMarginInBodyOffset ) { + if ( jQuery.support.doesNotIncludeMarginInBodyOffset ) { top += parseFloat( jQuery.css(body, "marginTop") ) || 0; left += parseFloat( jQuery.css(body, "marginLeft") ) || 0; } @@ -8781,7 +9190,7 @@ jQuery.offset = { curOffset = curElem.offset(), curCSSTop = jQuery.css( elem, "top" ), curCSSLeft = jQuery.css( elem, "left" ), - calculatePosition = (position === "absolute" || position === "fixed") && jQuery.inArray("auto", [curCSSTop, curCSSLeft]) > -1, + calculatePosition = ( position === "absolute" || position === "fixed" ) && jQuery.inArray("auto", [curCSSTop, curCSSLeft]) > -1, props = {}, curPosition = {}, curTop, curLeft; // need to be able to calculate position if either top or left is auto and position is either absolute or fixed @@ -8798,11 +9207,11 @@ jQuery.offset = { options = options.call( elem, i, curOffset ); } - if (options.top != null) { - props.top = (options.top - curOffset.top) + curTop; + if ( options.top != null ) { + props.top = ( options.top - curOffset.top ) + curTop; } - if (options.left != null) { - props.left = (options.left - curOffset.left) + curLeft; + if ( options.left != null ) { + props.left = ( options.left - curOffset.left ) + curLeft; } if ( "using" in options ) { @@ -8815,6 +9224,7 @@ jQuery.offset = { jQuery.fn.extend({ + position: function() { if ( !this[0] ) { return null; @@ -8859,42 +9269,30 @@ jQuery.fn.extend({ // Create scrollLeft and scrollTop methods -jQuery.each( ["Left", "Top"], function( i, name ) { - var method = "scroll" + name; +jQuery.each( {scrollLeft: "pageXOffset", scrollTop: "pageYOffset"}, function( method, prop ) { + var top = /Y/.test( prop ); jQuery.fn[ method ] = function( val ) { - var elem, win; + return jQuery.access( this, function( elem, method, val ) { + var win = getWindow( elem ); - if ( val === undefined ) { - elem = this[ 0 ]; - - if ( !elem ) { - return null; + if ( val === undefined ) { + return win ? (prop in win) ? win[ prop ] : + jQuery.support.boxModel && win.document.documentElement[ method ] || + win.document.body[ method ] : + elem[ method ]; } - win = getWindow( elem ); - - // Return the scroll offset - return win ? ("pageXOffset" in win) ? win[ i ? "pageYOffset" : "pageXOffset" ] : - jQuery.support.boxModel && win.document.documentElement[ method ] || - win.document.body[ method ] : - elem[ method ]; - } - - // Set the scroll offset - return this.each(function() { - win = getWindow( this ); - if ( win ) { win.scrollTo( - !i ? val : jQuery( win ).scrollLeft(), - i ? val : jQuery( win ).scrollTop() + !top ? val : jQuery( win ).scrollLeft(), + top ? val : jQuery( win ).scrollTop() ); } else { - this[ method ] = val; + elem[ method ] = val; } - }); + }, method, val, arguments.length, null ); }; }); @@ -8910,72 +9308,97 @@ function getWindow( elem ) { // Create width, height, innerHeight, innerWidth, outerHeight and outerWidth methods -jQuery.each([ "Height", "Width" ], function( i, name ) { - - var type = name.toLowerCase(); +jQuery.each( { Height: "height", Width: "width" }, function( name, type ) { + var clientProp = "client" + name, + scrollProp = "scroll" + name, + offsetProp = "offset" + name; // innerHeight and innerWidth jQuery.fn[ "inner" + name ] = function() { var elem = this[0]; - return elem && elem.style ? + return elem ? + elem.style ? parseFloat( jQuery.css( elem, type, "padding" ) ) : + this[ type ]() : null; }; // outerHeight and outerWidth jQuery.fn[ "outer" + name ] = function( margin ) { var elem = this[0]; - return elem && elem.style ? + return elem ? + elem.style ? parseFloat( jQuery.css( elem, type, margin ? "margin" : "border" ) ) : + this[ type ]() : null; }; - jQuery.fn[ type ] = function( size ) { - // Get window width or height - var elem = this[0]; - if ( !elem ) { - return size == null ? null : this; - } + jQuery.fn[ type ] = function( value ) { + return jQuery.access( this, function( elem, type, value ) { + var doc, docElemProp, orig, ret; - if ( jQuery.isFunction( size ) ) { - return this.each(function( i ) { - var self = jQuery( this ); - self[ type ]( size.call( this, i, self[ type ]() ) ); - }); - } + if ( jQuery.isWindow( elem ) ) { + // 3rd condition allows Nokia support, as it supports the docElem prop but not CSS1Compat + doc = elem.document; + docElemProp = doc.documentElement[ clientProp ]; + return jQuery.support.boxModel && docElemProp || + doc.body && doc.body[ clientProp ] || docElemProp; + } - if ( jQuery.isWindow( elem ) ) { - // Everyone else use document.documentElement or document.body depending on Quirks vs Standards mode - // 3rd condition allows Nokia support, as it supports the docElem prop but not CSS1Compat - var docElemProp = elem.document.documentElement[ "client" + name ]; - return elem.document.compatMode === "CSS1Compat" && docElemProp || - elem.document.body[ "client" + name ] || docElemProp; + // Get document width or height + if ( elem.nodeType === 9 ) { + // Either scroll[Width/Height] or offset[Width/Height], whichever is greater + doc = elem.documentElement; - // Get document width or height - } else if ( elem.nodeType === 9 ) { - // Either scroll[Width/Height] or offset[Width/Height], whichever is greater - return Math.max( - elem.documentElement["client" + name], - elem.body["scroll" + name], elem.documentElement["scroll" + name], - elem.body["offset" + name], elem.documentElement["offset" + name] - ); + // when a window > document, IE6 reports a offset[Width/Height] > client[Width/Height] + // so we can't use max, as it'll choose the incorrect offset[Width/Height] + // instead we use the correct client[Width/Height] + // support:IE6 + if ( doc[ clientProp ] >= doc[ scrollProp ] ) { + return doc[ clientProp ]; + } - // Get or set width or height on the element - } else if ( size === undefined ) { - var orig = jQuery.css( elem, type ), + return Math.max( + elem.body[ scrollProp ], doc[ scrollProp ], + elem.body[ offsetProp ], doc[ offsetProp ] + ); + } + + // Get width or height on the element + if ( value === undefined ) { + orig = jQuery.css( elem, type ); ret = parseFloat( orig ); + return jQuery.isNumeric( ret ) ? ret : orig; + } - return jQuery.isNaN( ret ) ? orig : ret; - - // Set the width or height on the element (default to pixels if value is unitless) - } else { - return this.css( type, typeof size === "string" ? size : size + "px" ); - } + // Set the width or height on the element + jQuery( elem ).css( type, value ); + }, type, value, arguments.length, null ); }; - }); + + // Expose jQuery to the global object window.jQuery = window.$ = jQuery; -})(window); + +// Expose jQuery as an AMD module, but only for AMD loaders that +// understand the issues with loading multiple versions of jQuery +// in a page that all might call define(). The loader will indicate +// they have special allowances for multiple jQuery versions by +// specifying define.amd.jQuery = true. Register as a named module, +// since jQuery can be concatenated with other files that may use define, +// but not use a proper concatenation script that understands anonymous +// AMD modules. A named AMD is safest and most robust way to register. +// Lowercase jquery is used because AMD module names are derived from +// file names, and jQuery is normally delivered in a lowercase file name. +// Do this after creating the global so that if an AMD module wants to call +// noConflict to hide this version of jQuery, it will work. +if ( typeof define === "function" && define.amd && define.amd.jQuery ) { + define( "jquery", [], function () { return jQuery; } ); +} + + + +})( window ); From 7e3c1e008d6b2eff10d412993df293fce2156151 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Fri, 27 Jul 2012 04:48:50 -0400 Subject: [PATCH 133/331] webapp now uses twitter bootstrap mocked up the main screen, and am actually pretty happy with it! --- Assistant/Threads/WebApp.hs | 24 +- debian/copyright | 382 +--------- .../blog/day_45__long_polling/full.png | Bin 0 -> 55185 bytes .../blog/day_45__long_polling/phone.png | Bin 0 -> 41602 bytes static/css/bootstrap-responsive.css | 686 ++++++++++++++++++ static/{ => css}/bootstrap.css | 4 +- static/glyphicons-halflings-white.png | Bin 4352 -> 0 bytes static/glyphicons-halflings.png | Bin 4352 -> 0 bytes static/js/bootstrap-dropdown.js | 92 +++ templates/bootstrap.hamlet | 52 ++ templates/default-layout.hamlet | 13 +- templates/longpolling.julius | 4 +- templates/status.hamlet | 28 +- 13 files changed, 877 insertions(+), 408 deletions(-) create mode 100644 doc/design/assistant/blog/day_45__long_polling/full.png create mode 100644 doc/design/assistant/blog/day_45__long_polling/phone.png create mode 100644 static/css/bootstrap-responsive.css rename static/{ => css}/bootstrap.css (99%) delete mode 100644 static/glyphicons-halflings-white.png delete mode 100644 static/glyphicons-halflings.png create mode 100644 static/js/bootstrap-dropdown.js create mode 100644 templates/bootstrap.hamlet diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index f82a1fb6b9..050d62cf17 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -47,11 +47,16 @@ mkYesod "WebApp" [parseRoutes| |] instance Yesod WebApp where - defaultLayout contents = do - page <- widgetToPageContent contents + defaultLayout widget = do mmsg <- getMessage webapp <- getYesod - hamletToRepHtml $(hamletFile $ hamletTemplate "default-layout") + page <- widgetToPageContent $ do + addStylesheet $ StaticR css_bootstrap_css + addStylesheet $ StaticR css_bootstrap_responsive_css + addScript $ StaticR jquery_full_js + addScript $ StaticR js_bootstrap_dropdown_js + $(widgetFile "default-layout") + hamletToRepHtml $(hamletFile $ hamletTemplate "bootstrap") {- Require an auth token be set when accessing any (non-static route) -} isAuthorized _ _ = checkAuthToken secretToken @@ -68,7 +73,7 @@ instance Yesod WebApp where {- Add to any widget to make it auto-update. - - - The widget should have a html element with id=poll, which will be + - The widget should have a html element with id=updating, which will be - replaced when it's updated. - - Updating is done by getting html from the gethtml route. @@ -80,7 +85,7 @@ instance Yesod WebApp where - state. -} autoUpdate :: Text -> Route WebApp -> Route WebApp -> Int -> Int -> Widget -autoUpdate poll gethtml home ms_delay ms_startdelay = do +autoUpdate updating gethtml home ms_delay ms_startdelay = do {- Fallback refreshing is provided for non-javascript browsers. -} let delayseconds = show $ ms_to_seconds ms_delay toWidgetHead $(hamletFile $ hamletTemplate "metarefresh") @@ -88,7 +93,6 @@ autoUpdate poll gethtml home ms_delay ms_startdelay = do {- Use long polling to update the status display. -} let delay = show ms_delay let startdelay = show ms_startdelay - addScript $ StaticR jquery_full_js $(widgetFile "longpolling") where ms_to_seconds :: Int -> Int @@ -100,15 +104,13 @@ statusDisplay = do webapp <- lift getYesod time <- show <$> liftIO getCurrentTime - poll <- lift newIdent + updating <- lift newIdent $(widgetFile "status") - autoUpdate poll StatusR HomeR (3000 :: Int) (40 :: Int) + autoUpdate updating StatusR HomeR (3000 :: Int) (40 :: Int) getHomeR :: Handler RepHtml -getHomeR = defaultLayout $ do - statusDisplay - [whamlet|<p><a href="@{ConfigR}">config|] +getHomeR = defaultLayout statusDisplay {- Called by client to poll for a new webapp status display. - diff --git a/debian/copyright b/debian/copyright index 7f906a64aa..4cab3a048f 100644 --- a/debian/copyright +++ b/debian/copyright @@ -57,7 +57,7 @@ License: MIT or GPL-2 OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -Files: static/bootstrap.css +Files: static/*/bootstrap* Copyright: 2011-2012 Twitter, Inc. License: Apache-2.0 Licensed under the Apache License, Version 2.0 (the "License"); @@ -74,383 +74,3 @@ License: Apache-2.0 . The complete text of the Apache License is distributed in /usr/share/common-licenses/Apache-2.0 on Debian systems. - -Files: static/glyphicons* -Copyright: 2010-2012 Jan Kovarik <glyphicons@gmail.com> -License: CC-BY-3.0 - Creative Commons Attribution 3.0 License - . - THE WORK (AS DEFINED BELOW) IS PROVIDED UNDER THE TERMS - OF THIS CREATIVE COMMONS PUBLIC LICENSE ("CCPL" OR - "LICENSE"). THE WORK IS PROTECTED BY COPYRIGHT AND/OR OTHER - APPLICABLE LAW. ANY USE OF THE WORK OTHER THAN AS - AUTHORIZED UNDER THIS LICENSE OR COPYRIGHT LAW IS - PROHIBITED. - . - BY EXERCISING ANY RIGHTS TO THE WORK PROVIDED HERE, YOU - ACCEPT AND AGREE TO BE BOUND BY THE TERMS OF THIS LICENSE. - TO THE EXTENT THIS LICENSE MAY BE CONSIDERED TO BE A - CONTRACT, THE LICENSOR GRANTS YOU THE RIGHTS CONTAINED HERE - IN CONSIDERATION OF YOUR ACCEPTANCE OF SUCH TERMS AND - CONDITIONS. - . - 1. Definitions - . - a) "Adaptation" means a work based upon - the Work, or upon the Work and other pre-existing works, - such as a translation, adaptation, derivative work, - arrangement of music or other alterations of a literary - or artistic work, or phonogram or performance and - includes cinematographic adaptations or any other form in - which the Work may be recast, transformed, or adapted - including in any form recognizably derived from the - original, except that a work that constitutes a - Collection will not be considered an Adaptation for the - purpose of this License. For the avoidance of doubt, - where the Work is a musical work, performance or - phonogram, the synchronization of the Work in - timed-relation with a moving image ("synching") will be - considered an Adaptation for the purpose of this - License. - . - b) "Collection"</strong> means a collection of - literary or artistic works, such as encyclopedias and - anthologies, or performances, phonograms or broadcasts, - or other works or subject matter other than works listed - in Section 1(f) below, which, by reason of the selection - and arrangement of their contents, constitute - intellectual creations, in which the Work is included in - its entirety in unmodified form along with one or more - other contributions, each constituting separate and - independent works in themselves, which together are - assembled into a collective whole. A work that - constitutes a Collection will not be considered an - Adaptation (as defined above) for the purposes of this - License. - . - c) "Distribute" means to make available - to the public the original and copies of the Work or - Adaptation, as appropriate, through sale or other - transfer of ownership. - . - d) "Licensor" means the individual, - individuals, entity or entities that offer(s) the Work - under the terms of this License. - . - e) "Original Author" means, in the case - of a literary or artistic work, the individual, - individuals, entity or entities who created the Work or - if no individual or entity can be identified, the - publisher; and in addition (i) in the case of a - performance the actors, singers, musicians, dancers, and - other persons who act, sing, deliver, declaim, play in, - interpret or otherwise perform literary or artistic works - or expressions of folklore; (ii) in the case of a - phonogram the producer being the person or legal entity - who first fixes the sounds of a performance or other - sounds; and, (iii) in the case of broadcasts, the - organization that transmits the broadcast. - . - f) "Work" means the literary and/or - artistic work offered under the terms of this License - including without limitation any production in the - literary, scientific and artistic domain, whatever may be - the mode or form of its expression including digital - form, such as a book, pamphlet and other writing; a - lecture, address, sermon or other work of the same - nature; a dramatic or dramatico-musical work; a - choreographic work or entertainment in dumb show; a - musical composition with or without words; a - cinematographic work to which are assimilated works - expressed by a process analogous to cinematography; a - work of drawing, painting, architecture, sculpture, - engraving or lithography; a photographic work to which - are assimilated works expressed by a process analogous to - photography; a work of applied art; an illustration, map, - plan, sketch or three-dimensional work relative to - geography, topography, architecture or science; a - performance; a broadcast; a phonogram; a compilation of - data to the extent it is protected as a copyrightable - work; or a work performed by a variety or circus - performer to the extent it is not otherwise considered a - literary or artistic work. - . - g) "You"</strong> means an individual or entity - exercising rights under this License who has not - previously violated the terms of this License with - respect to the Work, or who has received express - permission from the Licensor to exercise rights under - this License despite a previous violation. - . - h) "Publicly Perform" means to perform - public recitations of the Work and to communicate to the - public those public recitations, by any means or process, - including by wire or wireless means or public digital - performances; to make available to the public Works in - such a way that members of the public may access these - Works from a place and at a place individually chosen by - them; to perform the Work to the public by any means or - process and the communication to the public of the - performances of the Work, including by public digital - performance; to broadcast and rebroadcast the Work by any - means including signs, sounds or images. - . - i) "Reproduce" means to make copies of - the Work by any means including without limitation by - sound or visual recordings and the right of fixation and - reproducing fixations of the Work, including storage of a - protected performance or phonogram in digital form or - other electronic medium. - . - 2. Fair Dealing Rights. Nothing in this - License is intended to reduce, limit, or restrict any uses - free from copyright or rights arising from limitations or - exceptions that are provided for in connection with the - copyright protection under copyright law or other - applicable laws. - . - 3. License Grant. Subject to the terms - and conditions of this License, Licensor hereby grants You - a worldwide, royalty-free, non-exclusive, perpetual (for - the duration of the applicable copyright) license to - exercise the rights in the Work as stated below:</p> - . - a) to Reproduce the Work, to incorporate the Work into - one or more Collections, and to Reproduce the Work as - incorporated in the Collections; - . - b) to create and Reproduce Adaptations provided that any - such Adaptation, including any translation in any medium, - takes reasonable steps to clearly label, demarcate or - otherwise identify that changes were made to the original - Work. For example, a translation could be marked "The - original work was translated from English to Spanish," or - a modification could indicate "The original work has been - modified."; - . - c) to Distribute and Publicly Perform the Work including - as incorporated in Collections; and, - . - d) to Distribute and Publicly Perform Adaptations. - . - e) For the avoidance of doubt: - . - i) Non-waivable Compulsory License - Schemes. In those jurisdictions in which the - right to collect royalties through any statutory or - compulsory licensing scheme cannot be waived, the - Licensor reserves the exclusive right to collect such - royalties for any exercise by You of the rights - granted under this License; - . - ii) Waivable Compulsory License - Schemes. In those jurisdictions in which the - right to collect royalties through any statutory or - compulsory licensing scheme can be waived, the - Licensor waives the exclusive right to collect such - royalties for any exercise by You of the rights - granted under this License; and, - . - iii) Voluntary License Schemes. The - Licensor waives the right to collect royalties, - whether individually or, in the event that the - Licensor is a member of a collecting society that - administers voluntary licensing schemes, via that - society, from any exercise by You of the rights - granted under this License. - . - The above rights may be exercised in all media and - formats whether now known or hereafter devised. The above - rights include the right to make such modifications as are - technically necessary to exercise the rights in other media - and formats. Subject to Section 8(f), all rights not - expressly granted by Licensor are hereby reserved. - . - 4. Restrictions. The license granted in - Section 3 above is expressly made subject to and limited by - the following restrictions: - . - a) You may Distribute or Publicly Perform the Work only - under the terms of this License. You must include a copy - of, or the Uniform Resource Identifier (URI) for, this - License with every copy of the Work You Distribute or - Publicly Perform. You may not offer or impose any terms - on the Work that restrict the terms of this License or - the ability of the recipient of the Work to exercise the - rights granted to that recipient under the terms of the - License. You may not sublicense the Work. You must keep - intact all notices that refer to this License and to the - disclaimer of warranties with every copy of the Work You - Distribute or Publicly Perform. When You Distribute or - Publicly Perform the Work, You may not impose any - effective technological measures on the Work that - restrict the ability of a recipient of the Work from You - to exercise the rights granted to that recipient under - the terms of the License. This Section 4(a) applies to - the Work as incorporated in a Collection, but this does - not require the Collection apart from the Work itself to - be made subject to the terms of this License. If You - create a Collection, upon notice from any Licensor You - must, to the extent practicable, remove from the - Collection any credit as required by Section 4(b), as - requested. If You create an Adaptation, upon notice from - any Licensor You must, to the extent practicable, remove - from the Adaptation any credit as required by Section - 4(b), as requested. - . - b) If You Distribute, or Publicly Perform the Work or - any Adaptations or Collections, You must, unless a - request has been made pursuant to Section 4(a), keep - intact all copyright notices for the Work and provide, - reasonable to the medium or means You are utilizing: (i) - the name of the Original Author (or pseudonym, if - applicable) if supplied, and/or if the Original Author - and/or Licensor designate another party or parties (e.g., - a sponsor institute, publishing entity, journal) for - attribution ("Attribution Parties") in Licensor's - copyright notice, terms of service or by other reasonable - means, the name of such party or parties; (ii) the title - of the Work if supplied; (iii) to the extent reasonably - practicable, the URI, if any, that Licensor specifies to - be associated with the Work, unless such URI does not - refer to the copyright notice or licensing information - for the Work; and (iv) , consistent with Section 3(b), in - the case of an Adaptation, a credit identifying the use - of the Work in the Adaptation (e.g., "French translation - of the Work by Original Author," or "Screenplay based on - original Work by Original Author"). The credit required - by this Section 4 (b) may be implemented in any - reasonable manner; provided, however, that in the case of - a Adaptation or Collection, at a minimum such credit will - appear, if a credit for all contributing authors of the - Adaptation or Collection appears, then as part of these - credits and in a manner at least as prominent as the - credits for the other contributing authors. For the - avoidance of doubt, You may only use the credit required - by this Section for the purpose of attribution in the - manner set out above and, by exercising Your rights under - this License, You may not implicitly or explicitly assert - or imply any connection with, sponsorship or endorsement - by the Original Author, Licensor and/or Attribution - Parties, as appropriate, of You or Your use of the Work, - without the separate, express prior written permission of - the Original Author, Licensor and/or Attribution - Parties. - . - c) Except as otherwise agreed in writing by the Licensor - or as may be otherwise permitted by applicable law, if - You Reproduce, Distribute or Publicly Perform the Work - either by itself or as part of any Adaptations or - Collections, You must not distort, mutilate, modify or - take other derogatory action in relation to the Work - which would be prejudicial to the Original Author's honor - or reputation. Licensor agrees that in those - jurisdictions (e.g. Japan), in which any exercise of the - right granted in Section 3(b) of this License (the right - to make Adaptations) would be deemed to be a distortion, - mutilation, modification or other derogatory action - prejudicial to the Original Author's honor and - reputation, the Licensor will waive or not assert, as - appropriate, this Section, to the fullest extent - permitted by the applicable national law, to enable You - to reasonably exercise Your right under Section 3(b) of - this License (right to make Adaptations) but not - otherwise. - . - 5. Representations, Warranties and - Disclaimer - . - UNLESS OTHERWISE MUTUALLY AGREED TO BY THE PARTIES IN - WRITING, LICENSOR OFFERS THE WORK AS-IS AND MAKES NO - REPRESENTATIONS OR WARRANTIES OF ANY KIND CONCERNING THE - WORK, EXPRESS, IMPLIED, STATUTORY OR OTHERWISE, INCLUDING, - WITHOUT LIMITATION, WARRANTIES OF TITLE, MERCHANTIBILITY, - FITNESS FOR A PARTICULAR PURPOSE, NONINFRINGEMENT, OR THE - ABSENCE OF LATENT OR OTHER DEFECTS, ACCURACY, OR THE - PRESENCE OF ABSENCE OF ERRORS, WHETHER OR NOT DISCOVERABLE. - SOME JURISDICTIONS DO NOT ALLOW THE EXCLUSION OF IMPLIED - WARRANTIES, SO SUCH EXCLUSION MAY NOT APPLY TO YOU. - . - 6. Limitation on Liability. EXCEPT TO - THE EXTENT REQUIRED BY APPLICABLE LAW, IN NO EVENT WILL - LICENSOR BE LIABLE TO YOU ON ANY LEGAL THEORY FOR ANY - SPECIAL, INCIDENTAL, CONSEQUENTIAL, PUNITIVE OR EXEMPLARY - DAMAGES ARISING OUT OF THIS LICENSE OR THE USE OF THE WORK, - EVEN IF LICENSOR HAS BEEN ADVISED OF THE POSSIBILITY OF - SUCH DAMAGES. - . - 7. Termination - . - a) This License and the rights granted hereunder will - terminate automatically upon any breach by You of the - terms of this License. Individuals or entities who have - received Adaptations or Collections from You under this - License, however, will not have their licenses terminated - provided such individuals or entities remain in full - compliance with those licenses. Sections 1, 2, 5, 6, 7, - and 8 will survive any termination of this License.</li> - . - b) Subject to the above terms and conditions, the - license granted here is perpetual (for the duration of - the applicable copyright in the Work). Notwithstanding - the above, Licensor reserves the right to release the - Work under different license terms or to stop - distributing the Work at any time; provided, however that - any such election will not serve to withdraw this License - (or any other license that has been, or is required to - be, granted under the terms of this License), and this - License will continue in full force and effect unless - terminated as stated above. - . - 8. Miscellaneous - . - a) Each time You Distribute or Publicly Perform the Work - or a Collection, the Licensor offers to the recipient a - license to the Work on the same terms and conditions as - the license granted to You under this License. - . - b) Each time You Distribute or Publicly Perform an - Adaptation, Licensor offers to the recipient a license to - the original Work on the same terms and conditions as the - license granted to You under this License. - . - c) If any provision of this License is invalid or - unenforceable under applicable law, it shall not affect - the validity or enforceability of the remainder of the - terms of this License, and without further action by the - parties to this agreement, such provision shall be - reformed to the minimum extent necessary to make such - provision valid and enforceable. - . - d) No term or provision of this License shall be deemed - waived and no breach consented to unless such waiver or - consent shall be in writing and signed by the party to be - charged with such waiver or consent. - . - e) This License constitutes the entire agreement between - the parties with respect to the Work licensed here. There - are no understandings, agreements or representations with - respect to the Work not specified here. Licensor shall - not be bound by any additional provisions that may appear - in any communication from You. This License may not be - modified without the mutual written agreement of the - Licensor and You. - . - f) The rights granted under, and the subject matter - referenced, in this License were drafted utilizing the - terminology of the Berne Convention for the Protection of - Literary and Artistic Works (as amended on September 28, - 1979), the Rome Convention of 1961, the WIPO Copyright - Treaty of 1996, the WIPO Performances and Phonograms - Treaty of 1996 and the Universal Copyright Convention (as - revised on July 24, 1971). These rights and subject - matter take effect in the relevant jurisdiction in which - the License terms are sought to be enforced according to - the corresponding provisions of the implementation of - those treaty provisions in the applicable national law. - If the standard suite of rights granted under applicable - copyright law includes additional rights not granted - under this License, such additional rights are deemed to - be included in the License; this License is not intended - to restrict the license of any rights under applicable - law. diff --git a/doc/design/assistant/blog/day_45__long_polling/full.png b/doc/design/assistant/blog/day_45__long_polling/full.png new file mode 100644 index 0000000000000000000000000000000000000000..3963ae1dcb26d2590c08ab036d9ec68fe266bbe0 GIT binary patch literal 55185 zcmYg%1z1yW-1cZCML{|Qm6Glj>6Y#ikZwjdQc^1Ah@nV#cL~CP0i(McM%U<l)BpQk z?>8=XYR@^(Ip-JmbN}uq=DnIc0WKvj001CRRFKgG05DOj==zV)Q40@u3{TVo(?&{F z3IM1|#JjV=LT#gYXv)6>ln+zyqBiI)6*N@=0KeA&K*%Qm;0CoTWCs8MasdE)<^X`m zcL0FQHM3bm40QnegR;B~0QvXtM_WM>YR_X=1p^P%QsLjfT)%?^syRSWMoQafZhz6+ zSmy$Xb3EOY(MD{LBh(q1o5S2Fzr|cP5owrjU@*%?Ri9=cK;2R8VwVR>*-{!xiNPRC zXC|a3BgT{xAUhO+BOnp*2!BrF$ehz4iGYcw>|5b%;BZrb#CE{2u*&iYEJq-R{!tG7 zX)7~s4)YXcHlI3vH&@)JuS%~_Ukd5XLZ6<zd-UQDw!sjMp9YDn)QT{p!-R)ic&A%f zryvm2@1(@=RmqA6^o~WZFqa35@hcbp_(TN5zg9YZ_78?6m{Wy<w)}0s7_obLWV{nx zHCZy62R8(C$|qmFD%hX%KHs?Z%&W;T{`nzyET4nq#owkyVKKow6#mOGVVzajfd;!* z#P?typSaF5bX7D4{wJz>ai5NKADY;>4L0{UlGyAxp8Rdr=aiSv1_<k{!8UR9jAEjt z?LHHOxp@)+ic*+AYcVAZ5A=&>yO}VgDB1zuK0>u{7p<BXeufpgtsh<<@ZK18elf^n zboI92wMUT_YyL76o||Hj&tW4IJ^y<3LU5)Ho&J%S!wAGHerJ)<@QIH`>u5Zl%e;ma z7Pi<+bn}pU5>{aqK^*1Wks4Pooa84j8FJ%{bJ{)Yi%JxoX(BDGcnkt6{GSribR?U+ zOz9sYLlgQH%D>msydXcUkgEwY&VR4CqlEtVatfA};(#ZzsLm}FQt_8|?0$Hg;(;^- zYbd^u4b30v8HxaUPyO(`PXz*c<NZcdS2?0`jkWgIw;;z)ZFh^Lh6ua4+?yP2JHSP3 zf~QI;GOX6*j{#FZ4o2DMX8UJPay|V_f}}M3<RVqdzp?CKd!pX+r!SG!sEcBTS`rXD zh55^PZwZ&*4AN=fqP3Dd6@)ofvfQP7kP9v<6Adxx;#aRKjIGT|%U~i>z<Qgz-N`44 z->r~0X1dtyxKPDeAj6r$ma7@V{5hWtYbRa~lJrf<njOQ?$JZ}YMYx+gPNm#-Z-Dsk zRTpL*)k~iEB=GJ);>q9OhQ${lHKRo^m`*pjz|10uGc&lJBNE=(lZ-*8rHfkI?wHDE z7SSVQWID|m29!Jm8!t<-6u|g&u{?d#eyz)ompyKvijiSR8Hgl`-o*C{-8T1A{jP1Q zuWel5iK(&SWBT*GXWV`#1%avw`@h>31;?`ia_EoW;Dy2$8Rxb<BxkGLn_80MLV2yK zOliV<Z#K?e-6l{2Mk@4LD<&8**)!?Ca%;-5SSv$a?6EFi@54oZWN*UrWqx-m*p~MV z<xErI;^ARn7^O>>n?O%4FEv?9YK6PGG>dY*5rs#3$ex-~m3;G;PeH~S@AY@q*G;BX zurxf~yqs6JlgzYP^@`J*3I5vXyF+t<a=;^WSWP6@gz?o=ITA;Fz(zaAd!^ivmQbRw zm%Tdz3hVszFzdHqD1E$M+$j5_r`{NxSU-~c0!`jb2kzFnRBV%~e!sIQpj9t7J>v|S zk+>%;ySJ5teW#`Q<<-hN`u=LU0MRQayHw+9Y!=$)Y{*ux-XXp$hWyh>5$LBnf4tDf zU}mqz^}^yP<l$b$?ehNkG_Kup9cRdPPq!_D^!anJu)n~?9o9HRIc=f<mdV1wQI)`w zqC|@8YvscXqg3Jik~*-_^Xe5fWRlTLiX=P?UHDgd5mm_F;Ic8S8wj9JKSc6V($acl zGk+GyzAdtRuUQ_U@g+vdn5D7WnKQ#xV0eYb=J?~YVN-(!GCf?YoTqX>bB#+Zi%VOM z&p;1BrVc^Ah`}m4x-70flB*@c>z3QZfZ(ecWh3Q$@l)XbUfZoYo!QZx_o8~q5F3XO zUH$&@5rW3_A>4CjuVPy-S$E_>)U(`dnKnN$8%$_W>wW+5iBxs5*t@2)Gxf!b7a$NQ zZG2o6Iag2MGTOB)^7`+~bR0ZJD;=djCiVWNkayaZlXGLup4NYNe`m|^FC-~Q>#L$Y zl?7YsxGP3^l{qauIDAI$BXL)-=5p`R^SIo<lAo~Mq$UbUQKS&GIU3=DJxBY}Zxtua zN$7J1()g{USgA=&Mm1Znl@=<Y1W3a17WUh_x*8Cw5aW^Q1$34q65P8VmO@OiLU`q$ z-HRelwR9G2j&CfbvtGtwP<+FV*%>h{(l&0+#ePCTOiWE}#Y@@E#RKB2HgRZ@*$~!! ztrupI>n>{{^|K?}O#GBohP%@Gt?7e-AN7CzZ_}asYkU+0(zl*b%ya%n6(r`lJW?yK zcw%f+ri-Lp6z=Xk$v95MTu6N6iabwT&{!~{m70uUlMl3o^oY+7nX&IEH+~iyr|!fF zZhgkQ6#_kf7m!)L<)8|E{P-4!aNi-}*^XjOw@Y0*9gOoUDhMhfI1UoC+8Fdi6kk0p zQYmL)o3yVR9tQf57lM@X+&w%-Yf80WyX+M|`xiUD7N0N4Xlw{4@KVYV?lMK^m~WrA zX<{-)$EgfJD_67GEAA^_LiNut+J`FcPwwN8xBGDR;OD~1Lc#+CA}lMcWlK_4-)}N= zIft9|tG)z|_B5;|*IZ)*+}TW;bK5-?X()(Ci!33$HZaq+bZgH1-8^&Y+a7nh@awQ| zDnDCOlZ-k_u{0c4k04b*pD)b+Qbm=OIDku}#A>xnT2?CL{#sOwjokMIFQ?$DkLHee zR*ETmE_>iQB>wQMGdf`Od%^VSm*UJ!3Sw#_abhOK^UWqExZwy8Y4no39JjYrvK>Sh zyo?EWrKdG+uw3r6#|!#2F<<8(obQYL{aY$Dl%0{0VK^^;YnyB)&e8A1+m@-HxD-Ca zwzL2e5)yL!i~T?Tetw_D*hKi6;{LkaCv80-pwmOlfts33tNV@)AV!p;)LZRn;cRN> z{IE_WZfN{v{g*33qY>ugs^s%_r>>R_9}|$5X9#M&xqh%1m+*7H%)W1yak@M3hTySM z-CL-1B>rkq72D#yElZ=r{!-~pm-Wzb(c0FQ)9h(S^ZertIW@JXx@T=mOGew((-@i8 zNxd?%r==PjY+IiFBx=*{?t6NG$K5{uzK^NrC)lO_#y)rXW;db`=FeiVD(rjdUr~=y zSj7ugxfd^IV-r!Lw7a?XV)C^5sfmNlay>#4Jt3T)y)9E`ZS-B26l=K33$n7U+d&E{ z37dVtGe|cM0+dF^e%IA{x5N01F3>9HdVPX?Sv@hp2Bg*nZVN9MtO5}>`6eq_*V#N= z-P}w(S@tA0A3T1*Nyyd_YErOrkF?lO(lHJC*^s73z=-27(>Xm|ppeCp*MR=d5+@e_ z<q+4>-}8&J%P@Ho%+5o=+s#rg@qY1I>-X@^m6T;<E|fE3_)!+O#khcF5yxv*!`EK{ zuI}HagYaAfN&mD?H+XAn3DOru><WYcf+h8sgdvnNKR+aXVM!*Nv@ffdfL$PtkDp*A zd_?<~IVYrhNC6roz6qQ7H&sLgQMP{fX^TrKnC7`Fz8b~J1nu5e+3=}Bv(t+U_%xQ3 ztA_^_pOvd^OTD@4y<dBFN5!AfZxgcv1@nSHIB^sgK4TIT8-kdrW{S}h;(q!V6)Kv- zp7ro<4@Y2P`TF@4YXg0%3)Bk8;QoTb|3C^a<d5VzJ|J|PpqWQfujiYu3-bm~LdouH z=*kyDr95q$m1HGQ-w&07TX;o$=!@TPpmM;y{Uf*w7rAwu%+D{}3<Cq_O~Q7nCaPn9 zgc8`^u!2O9R0M1qB27xUq!rFw;$ErS`Wh=V>hWI{ta0;<rPKpo{ey_S6s)h2<nhg? z<>I2n$)D5xk%01#;ELyC1x9+~Vdcz7C5<30z0V6?FQ3L_WGLTGy@*mX{W3t}F4wQ{ z67ceA(L0@NGW37m@a5(!U`79zhThbR(#`M0(wIN<=Yt;?(M4L2xL<!?#R$I_k8kEl z;O7Iz{7cE{EFg`FNfJ|{)3bn;r3WeYd*6hz)l0K?dr=nTF)~k=L^j$(tAZWpbhMMV z_jc$12N2sOd{1ygT<k4;Jnbf`cNqV?Eezh?U1i;P&3#~K12Z$Mahs1hqfj-W{)b7n zqMJNdRZxNdUmu^i$1b!Mcs~7m=*c^0Q9c0u-^cJGm*Oiw5G`7ok8&txT|T{;<lkQJ z8vkYlDpWe`X)bv30UCKTg@QJ~hi(6N{23(ioQf;ANZD<C6tJT9bTPgc@UN+$GB3zg z3ISN~%wZ-WA;rxZnZWuN(_ZA7VuWbMM{fSn>9}{c!Yb4CPEvaPSwYNG!RE;&je_I3 z;4@obGaL)cplQ0?%DR|$tisBAi}d-<Icn$t6j|)yyU06-ZW=mu^R5YTuro@Rzt6Ka zUKP50T}S%g6$p#Z06!XYWqx`pN`Owcs9cT~>Xccv7IMEGsH?OhA8^LU#$Kxh>=%%- z`TlgnMiU8tuve>>VU68$SI?e#2*+L!bv%x4cMG43lqc6e{E%*#<<{hK*Vz|6tXIuL z^*wFLyzx7Dsz(0EKga)kZ<Og`>{XU&a8i2gf6rKc;(#_J=i5^zrUqV{;RHI#pv7iM zn?awg?nKG&4}X#~G^%OEKOhbl{g(p~PV@B#S>8**NB0c{s#&ZlTm*`|9fj|$zR!RI zNpT}aZAak1{F+nurmpVpb?^=?HRNCsSrHpsGHT1r!C|LhN*VupeXj0jcq9wSz}VOa zK|zFt^x=G!hmr03FHupqL$=)i>_9YY)K<*%yhF3hRMR)zkYr^m*V8*SHF@Lr!ZQ-t zChesn2TpZ$nBn-{vbuwMRvY<b)#A7oL=brIj0YqKkfbCRYM0v#X9gbs#+fcR;q}^Y z+=Qlyi=3=xXjfz0KBEn?8Z!%aq7-(YNT3mw@IkIOECpHip6~M5i60p;v$D8(dBGQ0 z25k9A$jJJwG-G6n-!oH0qK23S<B!pgHZ~TR>MK}+q(AO&kdlz3JYN=ceA)f>7t2>A zYf9Cal9Ks8VuZ_lyN=BW)>VV;pZYQQMHCU8nwlC12Zum}kDs5Myga10w^+MaZZP`q zd)UYq@x2+uDVXnHXvG3!(0^We!Eb*`*5L2)wuH@`A|$*|%Id|o*S`PO(rv+Xruj!* zXM4l?j3{q=Lod|2!u$2}-%p8XB~si|*M$IK^nKRVGc(_v5uQ#9Q;h+_fd|=e<Si%2 zf}D=-s6B99F1{7k(~}q4FER(>VCB$YH5mqr+Z^6k=r`qfA1#%hd|brfvO4|&lgJjd z9a&*Fs>i1iaD*h#WCw@^?;_i`uWlApjmjtOFK&jjay&)KOe^$QQ_^{c`ja>QNZ&qO zdvAkkSYGA5!i~_Zn5K&N18<|bzR~OWW@BYCNkxDlq<Hb@odHPh=leYZzle7Ry7|PI zK^xJd)`nR(r<=X@h3Dtz5qM+|w?`es#Khu$=Q}f1>)*L885kG{=_FcRSG!O@$f)-H zFEE5vpSmY}rM&Q)GUrNv*acE2AF842iwj}s2lhysx=f@@rmqy$km)GtMAet+C~f9J z39?q4P7iOhsYNn3wzjrbS62@Ymx^^th#BQ6<L(A@I{2L(FtM;AK7GRe_syJAyx8(g z;>IV)*Vh*#31|y=uWg*8-IOV+mxoyX<?o$3>FeXe=Pd4$tkNZR{pZ=4#J%mv52-Eg z&Vn<E+mE}Nsq66MWaiI$)#bgHalDlAZyb{Qa}^<pFKI;Ir17vDUESW^6my!*UBfP= z<p~vEK1Csq9)N!NFa|*Ci6*CsC-7{4*}L+$`3SrYH-hKlZnmS|Q7pqx?sb~OfKr{v z!N~7!lZAzE>IIM9Nz)M|gTW7HFiBBSQ3wRm(%g)VgCj31i-m(jL?;o@8%F^KgC&u7 zyzyxNFh{``t~iYX{ym^v)^OoCrKe$=8pIB25RO)=W(8y@!6=E)fTryTS6%k6+Gveq zMO#K9h-Ik7gX&jbiKV#DEiRgn$d>75piY{S0^A+TLnYo4ZB{zEj?ByjIY)vNC1H;( z-lKMevu(+Hl-vIJ@#EC};F6|=^1I`KRtRovY>HA^&GxYP`HD1Y8<JEKWrA6jK#8TL zcztOH&BtdGwRUvDcdJG&Z8g4UTN=OQ4i=g$9}4hHv(5%ex3iO=xrF&z<>NQkS5T{J zR9K042MXAe3^$z?&iRE(MQ3D3E#9>SQA_~vwrX3j)RRULLV$j%cvkvco`?3W7qOue z1>}SWw0}G*jfFMskBAn|@+&VaEVM}ki#Sm@@SPu$2H)%#Nh``*9`5G9pE#4VZ!<-r zj8k6b?*|nlJg9Bbk1f;jw+{|zXlMe@cSe_kk@tCNrqy7)T+O1-v9VM_@_m_)y170C zW=|#GS*V=PN4+R&mwMKIf1@3fYn<$<YmY6-Ga<}{{Z?aO*{D8i$Rey+)aKIvR0E_{ zIrM#Vv$^7VMY)2)2wv;fP*Vk)Rou`dnz0a&k6&Jrp?&>pb{gH-l@Q)F5y8R!vZZzw z>$e)jZAg%Ms09F(Mo^tawuiHwHjh1HYZujjIU4&}!t`baLYFEWHHVM+#lsPjjWp#* ziEO`Hc+ZrwAX3+rWYpj&nKkqYGY0hQ5WYsr-*q=Ri;*#X_~5cPQS|fYPk_v*tKAuq z=<p7{>)!Z48RAzWhCT}V1`%V(5t{e?0Jr%As~Xs;H_WwW=B)&vmM!<}hH`l%r6pdg zu#_lHYh!`q@qAT0Lc)4e=tuuK$2_@GpDZs@c)Ts|h`#$tcJ@>@cciE8M?%oemj&?! zQ}eRPhL1HAPS{hGY*Q&fwpr1)jvo!-a(64?L`(ih;xluTP9G<Z7bmy8ytzh97oD6x zH~{UNBVF&jyZta`*{re>Aoh@mizVkXTl+T&N1q9<Ep1#Hsz5E_p_i1)->$z@f%1pw zFf-(%tod=o5$VE#;c844zEV$Q-ae64`w}u4D~F*^BNRz&@YM!-(K<~3Ie<Md@vdua ze<AF0^`|M=+2S|*a0%}zUTk2SI90V<gVXY>G`80&-$y!vkq*=4Lm*z8>(fnu#KYBk zV`Jk+Qb8mRzEdfU;*(D~T>-&n6%g7$&y%%RtSJK!$oAW{RUAmXokDdTK0u`n=}}aa z+J<yqY(B|c8XrG9q7n6j^fJ9Z>~Oi_Dw65K>)I*{MkK^5i`60@zA{>CMv3fLTU)c* zG^BKtem|eFYHJ@{oGjD+^_49%$na!+0+P)~Sql@ppNOJsLtGjifevwInmiz3u#N!h zOJ&XuA?R=Jw;CF5RuB#`nBvQ^yRf@Vhv^&<AWyIZALRgaKqiz-_Af(9A|pj28)^x6 zB?>|1Z7&|*<IbNb+RL6V4<94)cln|y#R{0igd%eH`6U15;4BStpL{0x$8X!dHt-@# zb!<z??ecuXWnyfJ8K;=AFhwUS(xcMyN8JAY{;&O3DA0k`=|&B4qY?GuTcmwLMKvFC zzp=G<vikVmSmPs5m^EOo6itaGgoY(euiOAJsLUOi<FM=~CVst{X4Eu*R7EA#t%|Bd zSS`hPPtR_aU;$`MxZdS<7M}C2cgBe3t-Zay%+c*<AEN30iq^f?l4d_lE{DPdTb7|* zguob;hcwrNtoEEwMQ3Gu)?pqG_b`~_?i=f4=y2}cg(yTN-I@1E=W@TEoVwo+9dqRj z#Tc>M4pm6+U;zKv^ydCW^-=rnX}p>=MG<w#3*;I&wzZ(A@qQ(>j%kKNy?qI0(3QLE zVyy4K*UycHhQ{v_E4NJG=*;84S=C={{Zz1`y4>(^BnCqc`nmm9(%)g$sv;%*(}i3u zMWfe6{tt_!El+$UArIi<kpmt0q`Ixsu*7BPBd;M2%1Z=rGjO8YRA`o?r&^ka;wal& z1pF2coYt@fOr!^PuZ|)wu&edtA%b}qZW>N54ZeK*sUin|-D2D45I~JzJAIX)H@;PY zS(=bwKiT^AjrqtfIRz(fEB(7CzaQgs?qK~QEKOY{*D!~AzH<Zp;E$%(3Iw={UGED@ z-VJ|$c+UI2FNKvXt?#l7AXD!Ge8Ik+mDs^wjU5f3|Geg*F1{e%Y?)PGp_KQ*pj@X! z7hr5`tbzwXM@Qdqzg}fj>^^e(gw}Z&jM&)ROr+)S>gnk*A0Z>%ta$_9*g(ZqC1qu* z?>?#+A#2~BMl4(}G<gt-^DQmhc5H+FeU?_>2W{5335tno!mcZwmWiqc*HCq$ILanp z=oE_<Sj^{mWj!hTZnwaiNLYXmHT-%_D|S8_br$q+T`)6a3fRCc=#EN!bG2WB0*@Da zlUlD+1_QQ0L=pjrMQ@3j*6WI|jPj^dbXLMi)_%T*S7YX@$Wd|6ASb1P8ZbAE+9oUI zf%JG$)EIdzhoQ{v<-E7^WO53q87UZv1{BT?ydFsLk6PG<!;K6L8B&xku)FIIjP3&i z=jw}u(7L%)w71pBI85dm?beU|qm=W;;s(!Getc;^xmN=#9g=EgA8Nb1yL)=pD&_H* zmA)_1&Jy)b?Y9C5C7hj~zhPrLLm(=A0j}2TaF|%zp3t~|HME0n-(Zzeg!1iS=(UTA zab*PE9AOb#M{vo({d!0IQT3I3%Tvo)HVY;*r5QHwn8MWIRbR`3!0!HmL}b%>j921d z4XC=)6!}r%+@@&My$P}LWrB!^CPT<6o<6$$U<>10DX&Lnik!j*{x86joKo_Yx@W^C zo(=@`j1_|rSY1j9_1lViQ?pVSRoQf(w(}G>do=PsZDISNh`*Er7aOR%TWBu%7()^e zQnB^M7(<nb^;>GNf8z|Klgi(J>yH|0&~dwWaU&c1yzSuz4#1SU+DKAg^4-p=%NPb+ zIi8?}_+B(g0Ll-Mf#Vud9|plfd$dO!;SMv&v>er|9Hjp4*<6ze(5L>PB}lOpU)3|X z3zH$HamJ;7!)XbQcbTxel<g$0o?IM!bt<1T*L{@#W#4yPPofX780QyX2GF7zTI}vG ziJyU&PN7H@J6y->rDuBurl6fS7JyofNxsbb*{)3r9IrCfR{Br=j4liJ_pPFy)y`~M zgSEjyvwj1z{iYO>)xY$%{hjKIhg3f%0(;nvKJI-Y6eyXRmNsC|vOlmhVf8PwGVz8# z$sqOSOTS31t0Q*8P9-x@XM0W;gO5H^VR_6H?AH7ZU23HaLvVkfxLQ=WUaBl()ayr< z$>`U7kK7bTT6zKAx&~rAt$O4&Lim@Mr{{Tm#%!rKaGqk)+8cP+=*l(n@vEb=Hxm&Z zJh1;H-{X#}fx`CIySrFSK=8}ZJCPtULpriaLaz+@r0|rwDu~FXmSe>o0n$=0u%QYO z)minHh-_wI+liXTi>LaU&7#bZe`pn*Z4V#2vXve;j2@RkAG|87y8->3f+wd4Qe$R) z77LZZV8bn+RG&5-8U}i~c>sX~_Pcl?7B2zKGWFc|i1Q{WKt==b1<2k}TDouV<!pij zz(?^5)gOn_r%nA2V3NqzfNOVOUt!o;fm+t*xVU5mN;rSZH<an40NK(DX>1<+B%kBT zmJCrqjLe6<U49u=ICMh|x&N@8M`mVPvz1t732~aOekF1PzH80AJeWh@c}C^E(iyti z9py4p+3xK~9b(#cLoMdxdUd=CpRS0FKUg<^tXpb)(htclH)=Q>m8bK+%@WMcI+-}7 zOAEg4nTAi5W$@XZW=@;>`cC1wgU)9QvV%4!(}IjI&(isW<0$$4ZW9h_%mNSQ^N@(O zGhT<GoKj=9r2e`&cNAFt3L1UIGj?i3<ei9i5=b?ZFzxPfe}B)Pt_f1nH8yUwp5Kc0 zIta(WD3Ntot}j!{Gi(T2JYMZyG+rDVo1_KPPM@8@)9lpLhEY4wzS}$$qN*u+dgBc! z7%@F9C@I;YnjwHgNL`s0EdbX(&ovV)<Rq|NJ>PPPqN5h}k{{p?Txu%x?=Z~FywnmU zQj<yjio>;^y#Zon39-Y|<Mi2%Z8BpoNu7wS6t=0pxyv$iMTSgm(}HYxH#-Cm=11ID zCfhpD`vh<S5Bd@oi=XAsINL4eGW04;=j)y3!Q%euW5yl!_nUFhOfu2?6GgxRMwim* zXZ#48<fSb4;eBG+s>;Se$<85>{Mier4W3Menv>x~<&Dlo#E;|4Et|o;ih|Oc`{NzE zaaFX{L`f<}OMs(Dru*@7c;Hdn@<-)_;2+~S{lV=LY)b(f*=KS7&R%^z0gHRt?LqBO zb3g~jZ5@5bkGan%Mmre<smgJE=sT=TkS_jH`6%H0XCd<bXas}E6YtTZm5T`I6xeU$ z+Q5=z%u&3<akMM#qqmLKa8iEH{qm{g;!HQC?8ycb9na*NcGt(WVQC}(rSC4OX=ZOc z+}IWM>o-eB<uxT%Lcxaztf!03Yh-FG{#X6Y5(1`M69ZfIE4A0l5AMh9HfEITWh64T zm{pPW%{z<R5qe#`bqfeQGMMwC>eiZ`bcvxePsV1Ifg3cnzb)0e!hTY}+`8sYz^K3Z zP{63WdCi<$K8IVgXo%gRjo8U~_HK=blZb5m;f=-0=Aq_$&EB(C;1BByc&!x8Z@^Sb z4x{R}x#fWIT`AF%43KF<9kGGxAtD1NaXD7{#AY`27a5?gY2z|T#gP_VcUTS-;n*Y5 zFH;a`@K=6i>0#zxxl6swwm(^AXgMe5<8Z}ZtgC>ND4zk5tqWfi2}8w)gsm&}6W}es z(+Zs^T>Q@#9XbS~jB0u7MfXH&bBevZe4TwHg52rz*6u39sPVQnEd%T^IwlG?7JVBh zA@RseTJ;0f)*8QICF2*-C<q^bRTy%Vy+gNl&-+T+WrUMRJ~n^KM&|<CE|9b}e7Mb) zPU9_yZVc$Y2rXnJ&XHj_IXMAwTgq8j{8Y;GyIPG>O*BV)GGAh2@~pPV`)I~#-V0Ty z4ZMAd=HufdBrJ^fM0RwxXLBGWPPc4N5?Gdx25=Z5+?PC#qH7Ocizz~3b>H(*$W*z> zd^1o#Na|-rA|mup+p}KD8`MzhVt>{FnyR|qyAXW55-Lv%s`b0r`~LlVhk(oXtC8@8 zWb@P9e&vo^uYnCn$JN>yq(BVKeD9eS@(7tKcJgQ9Iy+D#a83)LpI~-6)UX`f;0Rwf zl8+;A@;x&P$0i7Z9|$ge=Y@QILyk=i;f|9*ab7B~qY2tBrqUDByr=3M1@)%S*>)d4 zZt?eoAHvryc|Y2^Rx0H!+)d|8xVim&QO1!ed33O;16e3`K)E0a;JUh2HX&TTWoHxp zC@syW+GsdXO`uqCc#FpbpcAKt^Qju8r?uT?TV~;0WX%j?gv3d)<&lI~?Cuzt(P{D0 z;Kki!mJ66#A1{4c0?5f+iRr&SmJ1(BHu|&Vy;_v$CAm<425mz>ynb33^s{vwV?A&~ zFmibPb^NnX_I?ASw6e_8E;#$brZ{cTDm?qLB?hU;xNe*YJB}OtsKP}WbLYJ#<JsVx zpZ(Imq#!@vYi9(SxtmRexS)}&k2ULQeIsFaQ7>%}5tp61J%GN)W#I6(z#MQ8koCaz znE}SDxobI2SK>x+($Nvz`m$sD`f9ii3%#>P86@X)UG5Sr7|7RE@uP2Lo!!y2*?A^8 z%@4ErrF9yz&U187xW>~L^w|F7+D?aKt};xfWHb|xS`erW*NTWl-fqE#Ipz8n@1rDz z8C6)UWltK!Z8%Dek$vNw^Ny>rdvB0aWg`A;XbR*$3Lwh4;$UqDz>DGPAIDFCeri!_ zLHxDFo3Am<O=vSn5f>iib@p}6JaElfmA$bPhsnL5VO<A(J>w^s@;Na%<|a}$51%jO zCblwb2sd7&tn^l7Vu}&55b5LS&SvdZOVPYIwMMxzkYk(rQB?z(0o~smUqkHiZmu5J zEftNNoF*t>KK|SMHFs6u%c<s;solmxE%Q2t*@Z)X+BbEAS?m50Z6dnJ#Y!D8CD9CP zgy*qOt*`Nf--?jF0o=A|oBE!m{AWJFou!@=ksaNtRhB3K2ZN%h1h{Ud)Zo@Pv*5(4 zS229EQ>d$YCeG$wv{B;FV)DvaF7z3e1_>qwlq_t~V6S<IX{0b}iJANy-DYFpVo;_e z#(va9L?uN*uVTK=_x2%~ciYTo&%$P#Rnp9`EU2HTqrk@0+uPg!{I`FLm%UK|oghFd zugi8Lfm-<V9<fYDLh>kVWqTWeVze5Z<}Xh-q4`mY0+|^l&~PI0M$215GBUDpgWxj? zxhdPbwGvr%N&YgA?Pik}t`a-I%I2oQd+mufe*|5y;pLxo^@mgFXT_xaQj?a~Z{ED= z_+h>gh`7JJEncc}GpcuN4L)ZE5G_dBPZpE5`9qxMY7c+AS<<`-mC{@4FzfJM4!-SY z0$at46mE!>98FgoQMt6Ed>J3iTbX%R5)s?}U_Y8bGk<#l@9>3g{SL>5W!?5tRlqcu zsnfyCX-Wig;o7XkvZIqdI=@C6g@oth?5t*!c?)W)YudzGo4pR!4)?aq+2`t<JT~5c z_&B8l-Zn8d2}$qm)RbdL>3@287|vXa`*?Ts0DR*l#%pG_9334!UZ9S8FuJdknwp!_ zhx4N%B2rRPChx-H+#4Hzes~SS&*ZJ$j5DHG--=;?+S(xQ7mt|kNAae+bjE_~T{4k9 zNCT!#V__^^+{!Rp-p%jkX_nLKtsdpB%V|vLUS2aEuT*mic{KO-Gy^kuI-|=&>0Eg1 zp|!)#<<fIaL?H2}AsQa{<Lk%gCv{}cLON5yVo48wVxJAUIhJvlHhR__MMn*~;Tlxv zf=N5feDydUe8Mug9TL*w6kC%0R#r5$P1X5`Wm_Okt*7be7{@ux7`hL~4(*eqA!Mdm zENM^x_w~`{t<szXLP2sjei8D~94ox=5g{<x$~{F&*6U-wY2F_34m$no5$kLv;DO=E zW}N%_MagnNJ^9<1pBpfp;3dJE_Ee`i9(>+hEj)n6(tu1bf=&39)8f4mTONP}pI4xM za{5+TR)bF+RO4vD_)GieKt`EUeM$_v+*_=-kHd*SQ+_aX;ensdls3N7Q#Z@dk&bsv z9r&m@1#BQhrRh*&n$NFsr$|-A3hS4mBPgkirkI3kTXP@f0OZg$nAupoE{<2Rev4FY zu})NisNL9G`uy}fb9bp7RRB{s(L*XGZH6;5(eH&6SzoKClMR-lQZZdj!hZQRMH;mj z#~!(Un?gCbeJZ1|QO0uH+^ukzdV$S;N#_mK_||VD<Ka1BbEk>Xuj?l=>GA6f)yh^w z#MGswKt4$DXQ#u@TiN-McU2|zQ8NqaPh@d0Fv6Yo&jg4lGAOXH=V<{mck3SvR6Pd2 zb#)1BV!2m^koi19hv2<|u@a1ln^)KgRcUwaVd_FWL^L)&W#+)Ae1QiO0*!gg-jXhj z-@Pt2o3exXT@qqzl6Fhn%MMeT@O(7JnsttO)#ENs%3<SgMCIf%m4w++lx$$&`@@!_ z=BB3m8+Zj7rzt)zF8UL?=@wc$!*yThnUUY+<>m7YM_iQnVz7+J=k84lJv|ZDvlZ>8 zVs>NQ;n;+Q@@sX2nx`kHPcbbK&f=-aM#sCW7&hHIzM#8L(6n)3Fw2`a)c(jFK=6^9 zB`w$D5nGZHlNcYz%fg=SXT4AwaOTG0;Z|<4IC5}&n6)XYMHGMvK7wSE`)Q`9t{z@) zZufie2(#ci+uO^7laoL}mj{QDPAQkRi<`fGEHZVA^FzCkFI_WaRj6L8pl||@%t`JU zrp3|2y@`l?2OoSgG(3`8+;8y2OPfW<q{TCpYY^iX#4GXeWVs&+FowaFA7JGvC3+QC z7t`5#WplMa2WL~-kWcrwk<0#O%Z)-zOa)7Aek`Pfswp+kpFH`Jo^Ee=d2tb+kkIbA ztLg538j68aZrX<1IXTHMAfQ_@J?$!Q=!v`~y!TM?cM=Sd?r1w$@N!i)YXD0h%_Cgw z`>!Vf^pw7VbFx|f0kL7ODI}etk{w>TJ_1?-_6aw<5t1_3`42O^(yYdf9{}{;ms_=@ zutA>G!|ii2v`3CC1-z4LtwDYzgTilj_i#g|OVFaj4p$QR5B$%)zj0rFKvxh4?aww_ z;vuM7K40uz>v1+=*J~Ku>13Z&#x~gWl!l}0QtTC9eB%c24Ab&pu_oi1YM(X-0H!Ae zFP{}HD4IL?@f{@>(E4u<8B9Ka{E$rb9Lmgu!G~WTPN@V7XYgBJFt-NIrF=UrWh7PA z`-b^;b5XNkboUH~K4PLiYIn|B5z;6jzBL%=HbqtQv5gx#K7aO8kx14n=G^nEf0XBN zhYvZxsF<V8bZ2i_X#?uBt^;@y;ed1ko;Y=L)f)*3wJxSWeIvt208f0svQ^LOzD`qr z1z4%20PU5gTCDQ_DXs5!Ooe>xVV^BEEb}iNLgny*=EJEM0&Iuod>N#*O{g*Yjeipt z*r^;mi${N^5;j<nl^B&Y^cK1|Z5J-mwN<{OFfKf!B=8r3&n-lwSvXbXnGs)W0%pnB z5<ZAZzV=F#k@wPrB*r#l&M|)*QguZ6dF@|6cf_7^R6&gfJUZu?bHgFOhSs~PH=X2M zE32nQsgW%81`l%Ae{(j9$zBf?_=~zNZGcpcv^0~&b_s(DR<GoK{$YMj*+Y#HJlSc= z?M@L^Ra%)jv>t~gS3lDC+|BVZB-NcqG!gCM<kAP8!eqr0QBY9Ogdpndne87R*Ltnh zdNJ_q0)CI7psb8T|5agOana0oGo=9Rw}&cpTpS;BMeHxswFLDWjwe4y9Fm?*>Y0fl zyUsWV{Z_+?B%@<uxXJN(K!Z?d35vQwnf`22WdkkC^pYy#;&Paid4IGGQoSiDCJdab zrVIWq0K7@B3;u)|WekHN5NAO8G`|nR53#5qaCNbEFyDYGYPrmwPOtoy-fq9|U6?lW zZbcCNi0Cj|`}s!$5zoQKc5!y$Ktb-g-|=iQr$x6-Sz63}Umuc?HQ$if7$AGFwx4dM z-|5ymxEd9Y&dkh;kB4`5d3oaieGP~rqyr0`XaskBZu&{anYG+*Igi08zeP%d62Wcn z@3-z&s1n#^@9gY+`t%761N-|ST4gKM)mWbL_4W1W=%`<tgs`x0X9(Km(->TLaP^Iq z&$LbR`l?I=OUcs*%#q*n*K@<qEHJjuw@n*6J#WmfVTi=IV7t+{#4c(5?eh6s@zn$~ z2X^pKa`61&{S==1rSu0}x~C#e4l*ro0n+)%nF`<$v+Szi-U85wXTDzNazExn*|;~9 zqlHTFjKR~Hn@GjKYeLrS#Kzfo3tL=!IO`~Iuf0BG@jF264q?{N$eo&3Z7R-x(P}pa zp8ZD0sRCYr^4Z#x(Kg>JAlhQvpKhR$8OfG>K@UM|CdxjC3kJ)H#B9$mI+#|eBDf_v z?q0ktrn+8pD2#<SO$)xV#$tBY9hL-i_6!}YZktt8*fynB)Oe0efMSsfk2WPZqdc1Q z_Mz&(=Vhk?2L~gd4UsDqDxdzuW$Ye&KyU@Gtm5b*YXy&wU==TZKxekm#YiK1t`4It z!3!1G8usULG=h0)ZO<>=zV)j5Uc$4zA|D5D^9EtikyDKh%Nc>FS@&G;pszrs)zEw1 z023?IRWD23c`I4U2%xW{ZtGMr+RW{Aud<CMpWJE%sbo>^H>PDDsC$Z+my$Jakv;He z!qlGh!>_e^-CCNmDcq_32YE=v&2DyQS+)(EsO0%ZI6r2(aJ!U~z%SsBHj~lNe2+rz zitQ~!I{HhVx+dc8qpWtn(R2=0OLzSqF~^J+KLYt2#ukSbSNTLd2!_+t;@0bW-^!WN zui^91EmMn{1Ock?rQZ&1q5G4gRqIvG5aldFG`MZn-1KU}OmBtr<MCrjuc?;!p#>WJ z+Sx1ig^j7GxHfx3B>jw-NU@GbNY55CKj2BNSi!n*c;~LKE@N~v`mfaOKkkvdxS3Kb z@nOs%4amXE^?n;)a0?SF`r9U5#CY+A7E`>3n^!Xv>jy-;B_s(pb+KetQ(`dd?ChMw z9Qo;!af{c``Abib%IimA85u@%n`{@#Q~A}^W7XA~!DgHQ>XK}slNVA?zJ2?KVz#5A zaJsoV?&~j61UPSYmPUaUNSSO{=qYE%kC1f`qkN)@zxz$GSup5iVm$cnME?EzAF)YY zknMc2cd_eNSZ0Au$8h9)yQP1C@g0gji^8W6K$J}{`<)GmTs){gEH=38tXLc#9)>ad z_+L|txbIk<20L|kqblWi=w`;6?x*LwUQTlabP_y_XVs6AQ<D!DGr0EJSAheY1!h6M z$i>9Zv3MPZSDUpEI^=3Ww#3a!Qdn33cw0rC+_2VXb&!Jh;iv^Ul#TG+nq*Uca5*Uj z)h++QH#h5&M0g&NE|#TP|1hmEYjm~H*PrPol61rs_S*mM+uKo5;j%rPg{to&&d)tF zj?m~|Lm!UdQTeb_?MaJVc~nXLOU6sLqleg<;0;+RC>2nwgiId;wukv5PhPhQ4wQl% z%W0U)f=Ojoc5jz_+_p*t#;*?x>g3fkgM;RzS@ZUxNTZ+AHLNKCmuHD^f(0ZyvSwSH z1`HBe@+->@(qC}t{6hH|aZMJRnVIPWMqFIbpo$rLlO?a7qO|9z_;`eRC!kzjhYq8R zw4`mT$)nTDv!IWM=gudi1deo^F3Zb7MwXNqkHUV8@0Oc&EY&%r*?_@^J`4$J6DJoZ z{ZQBuDj*X{21o|pXrXwFEl`0?5V9M2xI0%DI$3E0T@FUko;j#1UF<$<@P(R5N8$T> z96GqbvWya!Bttl8L=PA00=urF>I@g_GWTb|ZH%IxDs5ky1y6ny6xf(UQxnzG_YM!i zz=LAbiZm!Gm7o*(L`SfR$EuJTiEP5UiVN`;YR$rmz>L#a2p(aOUjcBXW_!2cQ%}oD zRd3Y{zuV3ZUTSn(M^T<StU8Ib;wWWE=``G$$H3L~xHq0kOG_);XYKLc{j~Yb8K<Dw zKk*<Rt{O?Xhr8NJZL187*N+w(%}{rOgzB7{bB7|76jP1FCnS`9Ca@YBlZ-dax|uS# zFDZDK%!Wd7^^zII4;!)8MDY|`rJ7)cruQ9dAllxe)m3iC8Lo(Ts|N>J+1Z?*QF=|K zyi?c_a(}MQVWsbF#Jf?3+=!AEhu$9isXp{Zcj5aC^@oOl`7!Kzbq$LL#zYl>IVA>) zlB%;EUEAnSMyarXdnCK&3_zc_!t9Epi`Kit#TJycA@kLP?NQ<z(D_cX0jC6V)&GdE z^0k1hJVHT1VQ0Q!IbW43lCTYd5(l)MO&OuGbp|eq1G<LHNy^1jzj_pQbBe{Op6xt} zK<OEvXXp?&O4a_N@%~}8Vb+v!RBv-cya{nj&n$oHCt%1VSPG|_RG*6y=REqlE`-_w zqh^g*H*r2^4`WWp#-N`6fd&YvtgK`L`>Y|BgVj}4QSj7xxjoR&PXrM0?qtz>8O>)c zhN-Ko%efc(-|QGWPo<{n?--n1n_}mgg=CnFoVLQh@^dqv`Tp*F)XIFCLmy&6pEM`Y zV^BW13w*-{$#=RHZ*8RuJYKq*DaRqqHg0qNyYH1I1+04d4DUV=E*5WnNL8bES1rQH z8H_5?X%<aD$1Tl~KE!>4t<BcZ)I0b!SrR9BAzN&#zbeTLgugPes>Qh^i5F6kXrmaU z_=`^i^%Cw8iG!`_pp2xF_sk@?5g8d7*LlzcS5H)x@`HxP*CeGp-RzizcAI`Ad(cA@ zS^L%LSwX%k=bJa@r>7tG9xk=~eZV#bUPnvfS_NwJjdtBXLc>vHe~NHL>$i-g^`j%E zG-zHzn`L9Vf3sY+s;WuT>Gs!Oa<@LW_Dag-W-#t*xkw9?Xj6st?DDj~ukXqmc33$w zQf|^b!QwXFmuM-hK_U#kz3TSm0Z~8E@RbT#*ViD~hTW=g=zZ@NPFVLfW%$aMdx3h` zrhdDx#^FIIosT0fN+cB*|M!#Uf&43UYzp^`Is7J$SVEOc<*Wc2pE_f63erks^7>f% zEII+`n9(`RdVTUsqH`Y^IEK~A-Wh$|eqM)5`2A+5Z)61kIH@v`4mY~1^>g^>W$Ie! zBJPI-kVpD{_#6)z={euQHlIGt@+(tgNLfH$-OmTj*TZ31W@Wd{K#0H|ZyN3y9#vI} z(A4o-Y|V3a!_15%wnts#>agR>%Qatl*c(w1z=-VtiIR11O5Bu1St7OgT!{^gLR~%h zV=r%0(=18}MyU#FY5Ao-SV{`RyT-y|l*dQjz&VfF5beHa65#7|-aX~L%Y*q%GLoy? z>uDE&ITty)Q9X$eO4C?px+HOcn#k~&@Z$7bVCQ0U?)2_1tXp0nCB<GuP7V{hcCf!+ zN4O|cn>BCjr~El8Hcr}$i;JmcE4q1mLz}&HNLZIxOVyOu^$*v2Vl6Bz(kcpNf3C&W zLemx(7d=I?l9IIU?XB`Pi?H#@-*;!V|EEgDBqK|6OB6ZhC`u2!+8Qq+8)KY{GQf_+ z#%V>&@xhPfUcLo9856J?A5djV1Y<r~5ZGA*`3(zIXT;L))TNV|Wuo|ugo=s^<6c`R zl-jI~kO)p9TO}QJxw$!KAsv;RoE&g`DEbCkk4xaV^4QS<H$se=Ys8jM;`UtY)vH$( zt$Zb|t*u54{xTZJr>CW6ruikfa=%6w7u#$Q-%&@#Sy=oLhm%zJ_~amz%#rmjAfSsu zv{+lIO$x>pC&T(xF%JdYzb-Y=KN4wc2kOsMl<1|T+W%1s+1Xv4ZFibCX?b8_Vd0L5 zW{}Z1zdUc=2HUnRy=B^c{8!*gnbl_cFoYU7aJ9MW{?x8SF?4+BUj|$TjBHgc0Vq_F zz-vnY%+N87@<*A{SEams-g`AQ*0W$2>_`ihf~EVr05l;{QGPC|BJI7sy<*KG{9$ae zw%^^0Z92BhP&af~hCmEz+Fq_EiXlhk5!?ur0-H63Cu;d4YM7F#T`XW>@j^<9K?eS4 z@i3;`RGuq8j?()|=AUvf9hVaqpcJc=wU}knwg5;bNjVm@007=T!3>u&OC*JJ0UGi8 zP&55hw$|3hc3712GzC$g2DuCz*?;X1g<AVC6z0<S_J3MPm4(O2Sq_|#XssMbj~&1K z_k%|-@X6K8g+uQ<)Ke9#$9@yxgOPg$*S@~_Z?PMoxrtjqtbg-?P=Mi2_atKlb0XQb zG8t$50dMaq8w(?WqsF%U;PT6a_Q&7(*yH6q)~>$hbNrJg_bu+Dw9S+}zit<Tw>yGt z6jy;%>UZa-7k-;b245FN_<*Enlz{&vzGI~$;{OSqKk+gCe<Erc;q-|K>;E*>pB5NY zP$J)qX8c?)Sy@?ClTWWv#OdUO?7zcJ^L;WJjy|lP7Vv95{^_y#M4EB_r|Ta-VgKLR zv7#5+ZMR?kwS7BJ&;Px<kDtl`U*^dUGXMERd_wvE_AG9M6yScFla=(hr@5nxkM#f~ zfj@Ro^C|!9)`l~^!yfvC^X#Y#no44V^Iq70x8x3K!N><(ynR|ci2e8z1AcF~stJet z_~L^o(_gFWquC~GL_c;M^n@m2m<60vF-55#&D9k_|9fwJS=*OQ=uaNWI&=coecxip z61{zF$q*vLO$hiS(@F5T5Q0q@hbH4o2grYPdHr^j@;y2>c}?g()iU!M03#0a=Clo; zMCjbf`X#dn;P5R=+-^ud4_Cgs3A8bP?<HDq##BgaPjxL?i~<dwV>0^mx6*FW0zh=U z#z}^@)<1#se4mpWR%aPx9?`-3f`e<huzx9;vT=JIMpk~kFhnz+lLL4oSx?egTUc1h zA#wC3kf+z=vH5j}I%QlWD14s)un-U#{2XBwka=Wn79oex@MnK&KJB4o_Keb8o0&v8 zk$nip8n`_xOB5hxXa2pnFm5hrpz=PC>8E1R_58rbx?k)4EC%-@?c8m~{R+#0KZ&N& zziA`78eI=8(>t%Gqa<U(2Dn4i7rG9VNoR3PDYI=`?e2raM{wdW0T|&EJ{qi?pJYrE zWs<)!CSVFEg;FsYn8GN<ePeJsp*_Y$xWI!yXL4Xt44nbvtQRASp!psCe{&d`%D7Oa zdgr;P%w5<Ib-r$2UI2%Z5?`4JsFBltmvlM^lsW`7d+wsszk1bEyN@lya=ds#0)TlQ zq0^751&i2^<<ObYeaeNk2l`K16BxEwY(bLnxho_uFVoLe=|E$AfS4kj>ZPC)?RvK@ z<!&Q&{o~pCq!QB%ZFs}`Pl4ytTijCDI9p=1ELAJ*%nee@_jT;ch&q4y?(Y&T0|yso zh=9PiXX`Zx6zzL5mgt|~!z}6VxKgZ@?$_{5x1>zCi_^X?_na#Pj*U1-3-fMmd7Ae8 z?FZTw(C}AYo$Om}@nf<&KX)IW%^u7m9dq`Q`NySR?u#T+h9F1P%&aU2J2LPl#t~c~ zSG7=?7^0|d;@#2e)Di}B{lS$&O7c=7@byIkkMs2dqKdcI`6@_y61ZCp_-oUL0;)*z z5ykP>IA~O4LARqU>s|z4<BY|d3HJ<c{^#NkGQSp4(A%4~Pm_{RjMru;adzg{@5EW3 ztpnA=P6$lGJmD862dCN1wJ)mWRzSuh^RXZ02?3(6V}smM3OClPHS>7&4#yvIwmLcS zj?Q{I6~_UkB6-5s&{$5$Z6rZ3&D)vdX_Ry=`);!*^8A5j6z2*hSPVKu%#7m5!<LXM zW*JOMbBQHa2{r~*Wm0iAJ@qSWhN>%Zr87-DU-+3AT;nw2xIc?yCNvTE)yQ#2lFq+d zVI3p!8GiDCWL;SL5oUX2T-*mbunt9!k5+l<%oKBPhz-@|@A9$dCfStJ3_ByRBFTy& z)7#rG)n(z4J|N}3y-b2gdfjbDj-S6rG|h#>e@6UX;jE+v#Q4MIEyae*7Km0x5GiEI zm{Yc{g5-ve-q>)}wiZz({0$=;&mC^iIs;E=0Hxxt1Ju<4LmdPvX9p08?78h(ODrX3 zk+-85pBpXHnE@u@$*H4LFZ0u%bCB5rwC~3b8^&M%LDO$%>8JLX%zp_;I*Jtx3~;hw z;BYZMKEafo$;F~m@7#>%3^F}y!;QDhCT`)oV#n)#NK5Uw%9>vC874WTMfSJc>LNj6 zw@Kab1)M+&+;h6y?p8)+qzZ~8ZwC%sc@M?Z`W?ev5(iCETlvnvB6)GJ<NSiJzcyu4 zn-<t3qFH2~a$W6yVlVk-Bbikx`&6XMSq}Hk^#gE_YPnnqOb}v+=wphSW|!od_SngY z*W7G(6EELazY-nt8I4Y&yi5H8{0LDT*K5_XMeJ(P`u%i4Equ}h@;lvN>Yi|(5BoJ3 zbUv$SX=;pUasGU`Zzqz$0KYb_QIhzxoe5-7zhySf&eTb}8>eb3*8G1@HP!AWBZM(v z5iQqxGXu|^j~`lVZcuN(*?OWutoKS76==1?-w~f3c7iO|4AX8{t5dj`o$``&?77&< z_fDOr>Ae9=XCl$3Tv}KCVy{97iQDrZ8DO{a!@Jc5AjszHi$@zBBJl1zqoqE)se}8A zx}z-&K+s($8$63xGP{pTknb+d#anX3jw56UFUrN2{$?90yN><o?&dd?h@eE@%{i^i zDDsf<IaO`IYP<imF6J<yc(e5mlNQ|p|Is+i6jb@V)8T9>?smK9sC{1W0u&UK-Oe9; zN;pqJ!M%X-tvWjx-aypZs-EqDIE$4mTS5%{x(~5&D3dJ{wP|^uSSMNm`bF_ZKzCu~ z!NP7nfd(3VNW3Rjd-PLv7cf^ye`DHutZe90IX|<i6)fIy-&cKM3C;jI&iZM{*jgt@ zM_!(`HNLvm@BJb1)uKB3wWQoXFhM!$<o1jU5Z@C3MpvbAPPyOhKpF&P&NcCdbgouZ zJbZ|A*$u_;*t+vK&?*ikju!T8CdRv4-0I)bWChUoFRsn2rg2}tWN2R7P;~4FP&OLd zSOEV1<?j1C8iX^@C1ZV8&i<aW@X<MJzQy7^^_k?|DPqcrThtVr^^n}O(pE1WyT!{o zOKVZ#AQ*m`Z}+A3=Fjl-JCzsDu<HYNHoNU8Gj9)%v-_R4=V6aJ!+=rad;r&A#21Tk zLK{0*=fzcsslzAx;t&RQhqHIOX|CCI%hse6UxVK`-0@08v33*DD*iv(-ZCn#VA~en zjRyh*C%7cR-Q9u&cXxujJ2Xyk65QS0-4fgq+$C6WcYB@W+#~m$fA9Oo=pLg-@4ahR zt+Kgh&00mnOhzYjp7s)8zQKQH3x9d`VC|?Hi<YvnS5=fPQ}y`A4mK$TolyE@VQ2W! z1Ijnba5FxzByi&8Uvb))e&8et><8$5mZa&hLn>pF3F%}5hK#?O;Jy?qMZiMx3(yVw zwHIC{(BhIl=ddO<|Lo%uzBrk0?D>mDW_ZWL>*3DSh`Y6vu8_0+aSfxhW0}WxICoJh z^M3nMz^-R1B&4`dx7^VD)<f`f{*P36SR%m`F;s~OR*!RuuO?!^#2L+m5=f(<{_HYp zD(5Qw3k}Xz24jLc%!`6kFd`)@F6cvccTtT*$#)W{wUPooYa!L<qk6-1k>0;3%aQdF z3lK3+nBW_rtEzu@-$s?^{GL$vjBO*Mc*al18>DYE5efh78X9I>2DMX|eqlYyGDs(! z+ibrIg{i=(Tj7Qe)(T<ZPxgOUmgBuyAJ_8lxG{t@P7Yzmr|ri4UET&tyPBqAN4bMV z3q+lIFUgs-qy4Du{pPN@jSv#Mm;qH2XI-8RGuOfZIn)>0wR>yO>D#k06(h}9g))g; zjZh;xhv>;ll!dKi=WS?aEV(6AyT)U5oYqkzr6Re?O(!MXlsR%UpCV(1NJ1eBz?08| zL(=Yk_CZB{Bgl4UZ3cb;%CNc=&R4DG_<#1F<(Wf@44%qc)`6GXeZ}(5+(?wz>3d*u z0jzihK)^UB&4zk1*&6%_Z}I_u_0xFrWSf0)wvQTcWvk6~6`#R(l=^U7qb9T7p@5<L z^z>*AFH7Whi3VV-=uAu#X7WFE|4=+Fop;pJsJ4A*m6~bum^A&2D=oKRk7|D2m3OO@ zG#f(C90Z@K^(eph1uwv3ZPLC=CEz)C=z;B=-M8W6hwY9)Hi`-O45KNw!X?Lvb5EZY zjQfGQk+085!c(5U`=<wup3ldNPvc|C$B*T~5ww%dK3AFa(O#Z6iCfV9s7`re^+#zG zC=@8(W<y~Ur<#{kMasH_Mr0xtPmQ;FKv1F*lp#@**Dv`+{&u8Er82pzuTNOuvwbx$ zp2!hidot>VFXaDd9s#V6O5mrPb^NT0W{v_%vK8>6w;zU225zkKBx3#!aMRZYT4lP* zNn1QY26x+fp*G&X;&lK1**QQmF<JE`!3EJ099v%3u<8?}3#@n<2WmZ_H!T;2x^1+- zJ&tzfh~T;d0joEOtHfw=SJ(HQZ?>S-6XG)K?<cRtVQ%|6y}sa|LHhUjbMnK(nD^Jl zh}&CVRQ@KKQp2?K)Ben3%~_lCgr=t4%;U$Sjr7)F=os3Jmi==7QSpq0dgU6MvE1$V zv>0VKod(BQ!{Hpqp8C5=#o+=zi<k{->9A5Ew#!~0dwTfy1$?Z9kY8&Q+;+OIJe?L# zjouT5wzlC0w<A|NN=A`do)5kDt}Wo5y&UZS`Yz~A!a;>wpz_a*Z}8mONoU%#3I;n@ zN2~%tyCuB~YKL@bbB&MP8OBN(Q3zv_O@msIf2Mv_BQkPwh_|Eeka@hO_RjRyWt3s` zT4sUsIslp`Dh>8~wUIbrI{x%B%c!41I(8L*lgEB#SYs&b;h{`CxWkyG8v)kmiFt+3 zXXHabrLdz$^L;c<hh#cGr`>_)_!d<_jTD>C;}Y#;S%OqOLAi+G(n&9k!jO;=1C7?b zFh*Rx?={Dw$#W?aHKu^A&cvh)i_Ndn;`s5$=(FDA)&zo4HD0DO*r{ukF1Uc~ZG=b6 zcqULi+O10GVLlin!QO-OtEh{g9C%N?2EPf~iQqt=H?6nQ{FN_QEGi9HgY{vj#6C_Z z#Tus+NH6=5tFE&{LQ`;dA=xGR!=Jg~mi2_YDX$>-t14=*mojKE*m)RNl_<Z9*TGuS z^|0^j2}0U$oc=r5ibz9tI4LD|BcE88Hxa<#f|bcx5gQ#TqI+U+UN55xwm|_X>Q30L z)N62N;4ghC=#lb*FE*jg`@%j56ks8Pi}lQt3ykS!xHLm3!R&}PP;ex}p$9`<8Ho6> z;R=E;2-tEmmVLX_S7W~t%4Ey4^2U0Edi`2I|J1usc7Aww*<PtKcHMbowU_W`j5KGJ z@x`!v_>6@X8%tBj>&$fzh76M9)xa3x<Ko3BSY`G)4?5idIYv1Vi_Won><9NZguDer zUVWPIyzM#9&VZn_o6_T7D{m)`o)&6bpSgehBhrnzv?4KaW&vF{k5D3UhihQneyB)4 zmt96!DAlp=trdQvV<!LkP%l}>`tB+rjF8zL87t^hp81i20#1#_pgC9nI1yiLdbVX0 zogBn)F|D|h*&-XfG1V(eU|X@9D=(k-DYoN^P4KU4mXw}vJKgVno1_azZ6V00IQ%=z zrh~f@&YxY+n>JtTY*#yqhXFuHFa}C83sZtcc=81En4X}Y%^58PEIo6fH1(%$j+h&z z;AxNsa#)`J_|<_+A7!42fZq-##093Cys(9O_l;<Q>n{;Qr~~@zQ|G<TrU5puME|<V z61llFz~9GN$srE=e|O*i<>50Y82=#&M$glm{>cTr<Kby-YfIa?EujDNG6=SQ_gOL@ zvfGszBF$>nmWBRDu8wRJi<PtG843Dd_zOmB{mv-l-lIMU(L`oYwEx?5kT5{!LUN$L z@suEW1^w}U5J*Q6kbys!5zNKR{suD=hM4AmQcgkpC*2Y89r$n5#6NeB|9_TbO#wYX z>WUlC4dEHxGHm~n6L}gjlKGPPkaDuC`bSWP$>>lCAHDP^iHna{n9clM-o^}NYG-HX zcnLg%Clp9@r*8^V_Y}X&t+ejmQC3!_@Hq!kXq0Sof#2pa*W?|?e;FKHC;}-e!31SL z{vR8OKnfY76(almI}k(OAe&^!ztb@PrK}PndNA)ooAQ3(RBOMcV0G3(sP0yIclvpF zp{4kZv=UCxpQ>R0o`vK0smpI459ibSx3Lp6L4${%pzEM2F#_Fu8-rhh!otE*TB!fj z8-z}@&__g0fy$$w9)8^y@A16J{tkNSts>XgBB@Im9qivNF{WTP3nWN7>@HDsE_VbF zp=*#1vpG}!smT=G05||oHfEyD!hs@&`TKY4zX@MplKg)3m2e8y|68Tn90K6s(x-9e zC0(z6C7Y!r72LggRimvH+*?(BYfLarJr+hi%pXE4hUYsSAuytspV2AF_uQX%EATEk zfu_e-I_25ubNfwH;ZhS5U4DUfokmZ~x|=6k`#d#^u@WlLjl=Y<#cIW}OAocl^z{CU z;UCj%UcG6JPmataf?wOP<$!kc^dNw2ivr^lDnf`b!EF^ZUk9G>`uepYkl;2Hr<z=| z50eZ<gR#$aVrhQY)?rJG_X=hq8B~c$Av8?tyo!l3VioODscU<;YMOUqGqgjv;s=s* zkQx9m6NBN^tmc_rX6wJk*?#ajGA(o-m)TRUw-WsXyS35G+x3EZ_FT}|1w4WgqsgX; z)&-IrSlVxT{L@b*CR_8N!6*cJ*2%Ru?9UVP_3#d$<y`0<-X3nK8^>ETpmH2HdsLRM zN`Ovu2MR%F$qD*ie8^i%t3W$Csfc&+QEb|HAG2fWv**eHD5+EOu@6H94zN0nhi)Bz zD71%Sa5`uGh8p$R6Hcv^t#ojuiR(5+fs1*ebqGh>d}!sXCv!dk*Ra|8GAd+bUK!n# zf_I^HbOCy{YrpRr)j0BDA@|k+cZ3eQg4X!Bn=cv2JEfbq3ApE+Ak?ebq6YiU=3Tn= ztP(UCYN>ugJ69{-$PL)Y)d6Yq_*!fz5Dr69xv-kAZY};HO_$*NbTgBiKkH^(lw&2m zs=pHx)#&j2cLYLql_~`6vH5%|ERKl<{of3jn`P#T(avYuAbx;V1Oa;1QupOBI>ZN) zdwx%ySod`NS)~aMe1=e*w)UspZC2_2yFIYfmHO(MDe^TnU4@6xk6KZCjWxiqOGZP* z<w9V%Z(?_|Ugi5l_JnnKl(Z+wQLgL#xBIjEr8G;v;&Q1{4#FWYAEXMiy`#?5YdDM& z-;5ZUJt&YT9E=yKUw_}NoJuRxD|77Bm8wASM420yT_B&_0C?5wu|<eNnN{d&EJLX_ z$9u9?zT9)8M(R0G&Muj~BR(E=#>0B<n(7d>f9&M`#`T%%PjQ>emnLWcHhiL=>(srv zf;#P!C~U_tzZM8qCtCvaq6f=$RQO+6QT%k1_AFCEC~C9&;kQwG=?>8)br9#r-a*a8 zufh`0VQ17!GM;L3f%~;u@!WjIGw|1aOTt0CM9O`@hpvLU9vg3~Ix)CtE<#>y(KmpF zj;Jxa4kZjD`IJr^8QP7O4zHcyp$dzRbFpf;ybvQSqO_<I-%4o^>P^zCtv4MWh;PSy z?2F-hxI?a9n%h^)u-<U9)Bnl8xkcj-pi2kk$Cz4xSTAJTPf#?ycA{PrHfj5n`Z4ye zxpqIMbvs>cW5gNLHl0b?gXPT2)*qkZx#y+ikpOu{`Juc7$j)`Z>q-lc1mwm1(nafQ zy5E5EEqf+B&|EguuW8?4(X9pRA^9G=ip$Q!#jDc&9&w4Iz*VV8{2Ez|1Ttp-?&Zy2 zm&BmKc(U&VF!Y;z71w-QWLu|O;sQMR`C?kDj6{qy^);ZiIx+c|)14#x2TmV(n$I&C zR*fkVUaq|#)88z;n#`A7b4HboQW@A(eByqe-#%0IgIST{g!@O9@hGuO$<ol$4Sr5# znf{tYv~tIN3+r;>qKhwM<Ugik*Cd_|QGLsX4Bh4jd4bXSTcLSC5|bY}`i0=p0W68Y zqnDV6m^GCIP}K_=SL`Cypxlz0$pkzR?Vtb=*?P_=At8Wy%5-{<b@*f~mJo2$=0;14 zuko3W-Qd|fDH<J%jRmH5cbKPkMu-ib{YvU%?y7n%aBD0hZyx(5)y6W+%13>AZw=wJ z_tVh+Q8h9Suw8|HukeTanlhdb$GnWrotx_jbkhr7zNk+0hi0<HWzFi3@*VR^(Eo)! zt9n#sTwm6X>EH70W4`vCnd525m(slN<$A}@=t?_Qv=^;~-j#k6<ezY`ZQJ-Q4Z+4~ zpP;$v=fRaIyW~ciAnx<mSA{?QxA9amiCbuQhR>mM;7|}9s@MQttXYQ&CYQnNVcN9` z{;Oh6;!ra1c@@XnX?47Q&@P6DcinAW8iTi~LsmKg4fe-&!_`G!{xw05;vVPk-&Zb| z|Aa;mmiS`uUZL!IsMS$QWHYR#BAz}G3c<)dm6Sa(9oGy~8g3jwh!3j}Q(#z-t({3y z>U_rUl4B7A>=H;s$bLW@<k-QYtM<%E3B5C=7s^5Z1}<rAr_OI0k#Nf@rvwHJ-;{+W zO#ftTqK`Ght-}rqM}N_kWI+M?=<rVFV}xMQdnZFtRi`30+F4`pOvFHSj((x_=%JD9 zw>vGY0IN^m5MWOHjbZld)7}o4yn%hWK^NAYBkv==44pQJ2j5uq+=}#PzJ~j^`C5h% zVAOG1I|!W9N>G+nL${JqbY*;3+RVGr=m<V5d>tS|st5)(Ehy>(R3xe^%$5w6lQJDM z_Ey`5vJILFgyzV@&hAT1I&&@7qwCt!u>0sKpKBuY9qE*Gtk`?4qyDzdW+YZG;5&>G zxCu|>fDVamC2dcC#C3K{81H+tnx`Yeu{vT-x{qT$*5TzR>uo~@4ROt{vCh`Pi{bjU zf$Xy_8+VU?^89VW`T{dcYpr<Ko;uX}y^!3p`X6X8LCaPN67-CM&$8V!{Eb`!Uri{d z%mQFbH}pRb1}+UAMO^=5ok<uE_Fv#JWeb2z{1_RtW*?^MVq12!IxosuEc9n0=RW^= zax=j!3L0F$C_DEuvr}?e{loO&1MwFd3-8h0alP1&$EA1Gi=R1~#s1u!w_-C7*{kZH znnY8jK33}0)P}81lvRF*Wm%o00wY!6)C6S*tCFdz2S<-eSsI}lr!J2|kE*Rv57Q@S zV;YNTMTg@z+-kqD=%Wa9#jAd@;t>Xc&sBu2*`a9nwgd@FnF}-D#ZM<W=hkn!pQ~2r zKH@c!{2j$_^B^%DeA?AIv~5meBndxh7{2PfHP*{4B9Yi!s|#0qb5)}K<j~tKo4!yI z0n78u-Eyj~k$k7<mPD~RwpQgft&1wM8|Hg{|2{-8RgF(rMXzFMQ8W9|+;lAVi<$^l zuZ@o%pe{3Z71_`JtfuOuyUacJp~OL}TE)8~@6BZd5xS_EVElE@Qxz>~hbIqko_NSc zr%u0<DbV54AAd+8#jH5l!-wpE+KKm>dXTr>XYsb2f_0C@yqs@HIRi8;IlQf>QNO;~ zF`0r8eRjB)!&Go!HGMi9@43ihu6EGm@@sQiUesPgcTA4Q(Xzs*zKxx*(@gStmG$vN z!go=F!$Qi2+lOf-K&OF@=F&;?o+No`ep2_)CSTFdcB7>1de4K8PaxrU<B%C294z*u zTFRjTG9-6ZDgkE?dcgUv9;5Ajx(~9T#a(@=E(mgEA+Q!cAU8z%(36qVV?X;GAo==& z+=Z+DHB&tUfR9$fZT&6tt<WRIwKEZ3=carGmEGaf`3LJ()Z_(@X6x(vdj=@nGeJ!7 z>Es4kYp}8uX}v=?v-9~`zo%omSg!zMy{&@wb0vyB8%6!*D>eS2XK1DSgx+4?dY<8y zIvSKboyemVUx!thw;kJpsm{FC-)!^gJmrq|d0C%Ip_@D71E(~_Jy&p7dv#|b7e52+ z@%LAmOV<`oBSX;UY*T;e_rN8?Ml*l}>NGt7W3mQ#quYi(RUq@T*An<VQPJy)g5?)j zx>cKdLu55}K*>+qKG*hhgRm|4J<%1px<{K@IMG@rvVv}DTH|N8dM}qcHPl#N(gm8| z^Srze@ZE3Y5w}`ah0^{iT#E0NipP57E0;U+A8ZtCTd_6_uy{FhX==j5ELQE#H@}>h z4<ssy*2Kl#QlSsog&VP%ekZ*RJxN%U%jego&#*6MI|xti<q6It+&x`&))}oQ|I?=$ zC(1q1)K^vMwhy0e5!GDY)E)#;*-NSFru4)Uj?<>{44}TM@5&LNA0}A`d#&`hB@`<5 zKmiA$Rhv|38bD9vE4nq(_$qLrvSEsw&EEH!jY$3RsAD!;J-_?D3me4CUme{D2kIh< zE4zh0E1BsAPR56MeNbb}FOY61Z6mr5*!?fW+6jtt`Pv@K@Y~<E$D=!nvCaO&ypoMJ zz;{I|W}heVs0>vY7$<u}%nlIbx5)#P=Fod0AP!abs6w7QU?=|}GF6hUC98p49o;H$ z@MSP_^Tc!(U8#|=yWkL>&BrM<RYto!aq3lXos^?V>sEoJnd;zpoP&`QVrD0aDoN1c z&amrZ7#S08okM=DkfnR7Re9uhO6R&{XY$66q8|f{Hy8eAFqpSlHWG9v;U{z2+U>as z)mMG*_3^~E5NU(lUxwndR--wcfJ>c-dx7iTj}71S2Ho}<1a{bZL@615kcf-q*{3X3 z1FURC;s$kOk%r~zJlWgbLj3_*E+3<kyK8(oJuc6jdiHy)o$%Lo<y^&HovI8?#h$no zq5X;=3bP93@U>n1EdIooA}&Kg!yNfhRricOsTv#}QUw`GUt`iej^cdf1w|}=OCuqY zklFH9C_rBxzmx8TkGGaP^smJ}*I}PdA?pVKtt;<oUGIqw^@ff{e3$oQ=<ViR<R>y0 zGWD}+-Ha&#!$G|ou%iaoQFg6(BYXNn27mUfc&gm+?S$()_yt<iN}qOqS<W5uQRKbl z7hz$w>ovO7$A<#Mb|me}>)d8$wn|y;c?JFABTqE*ItB-vBsHmRH_Ogy{9ZZn#)0<G zt+ex>@nRgxb)IEo@GQ%6BR!@y#es8QX%C}5gwlE|)8zp=s!N`YWrK|r7Os;d7hmy^ z|EYpqT!pg5_NoMzorK^4tf>A(z}(>jC(Q{MQ-1iZwR-oIPCSSk_6sQ^KbdBjzbpWD zYG#cnZ$g?jfssmx9UXRn>qUGQVk(@U^F@eNMqQ0*AVDHR5YT%YU%dMKI2nNk#3>fN z{zO8C-t$@vz3&C^ACo@)R9xI=KTYb`PiAz8crU(y3Xs*_`iBWcy;nqhAKIhwK@_{5 z-G9URW4$PgYW@Rju3mlpf$?$^T{8U_C(J-)v7ab)5Z%kK@7Qhg%o-bO*hiPT?L|eu zR1=eakD%Ye5);*+m74OQAwFmLqL{IYEonS}E?DPwsa%dm@L|3#LEc%nb$1IkVHbin zP0P5RCnMIkF#$W3FQ1_zR6u24m<#p81_4Daj^Px=4XgMWU2;y{{`41xj#@#oHitIL z5mz-fWeKd6Z)+_|QySMs#r{$|OR#wSKvTXFSiZhhqkNxAec4mf5=LCHp*g`B{$e@u z_VE6qTGp@Bo^I}VI7JQfke527F-*hqcj^t$xxpV`l!#`U7e`vEH7D8<oPV;}3jKi# z4oFLTpf2nE;@$RzPf)9G3JYxguX4K1i=KN4|K5<80}>3nO0#Qpdh+vV|MizsVufb~ ziUj#g{@gM_u+;KTjFCd{FN|Sx3V_Sq_{wkJ*0a%0p{iL_ThSB;7wBEH;wR+>Y!%o4 zbe1TIZTK5yu=#Om2n3{hoOC6YjzL4bXlq0W>7aNSG*r1~df0%mZS0tmfS1%U3W;vC zxz>pMkzTGG%axaEKk`o|gpcqbLz4XG%=>wBo#z*apoq++F-*6PGp%#~TN*oe0JQ?p z7K-m5b<D>io!KdD&iUr=VCTLzL_JxS(Gz(AvJ+i9D@o&Nl&sPWEGbQubjUpc0J<h# zLCYuYQ#v(yKJtn>k0b4s$nZB<C8}R&itv&lN+oD4*ES0k4n)1TllZ+&sTs+CG*uH3 zOD&+T&va^_ht_w<U75qtbKxdWd&4RpX2&u#9~N(WOFvhp%do@N+^VToay8vFp3jbD z-Z_X~o=?&=7{}u>`NrRM?HVc#)Snk7sLFJwL87s2(D+DYbngA!V+*NIHZ7MjWbt=* zW`7<ETSZ}bI`sPBu@~uF=gu=r2q9y7)AvyXJ#$yne0L9iu8vjS99FSEhf(FdIltIr z6W^(9Y5Ljt_3bVN2>kV@%7<ccS+C~39QR&y=nm~z7+EAB&E+(Ve0z&Q?M*x`_0Wby zFJWcMTRIAzmUqo$N*J=OPNP(G6z!kx5&wcPbDL#gEq2!)AW9>GCz<wPJy$D?ys3Rt z^t{<ICbE%8FvJF1!5QPyEF%3p=<PdvE@179;xPcN0QAX4hacb>BHq?A7P(Gij_mrj zam<=4KR_S>cJJl$UQA>mcp*Yx*SpuRuJp(9z1&f2@weHwq5p+Z@NwY&0|petybWnO z6M7_0T4<!De=1$p_%{$!=`Jdle^H_a=H|lzb3ZP;(9MzUgd<^lT!3IAxqQ~?^)Mb? zHYs{$OxQ-b_81eC4_w|Av}NT;|G-h3V@~^b_Jo`(7kd4fP0wzX*!*jrfs_;~SC`Sc zv))V#!|-js*Vt65riUW1-El!(f>jcvePpn;=%$@bQ_u$KBA&r@O>^(?+T;rn#4Go) zqt6_miSgFk3(uz9d#2BBq1|oS3uQ2$*Y|$L#>WyzoLoY$l1>=Skfu|893o#P>s8FH z=H$kV){HwmMOon|8&~zg^t&1B{$!5Rv)CZp=0;Z}llm=uwr4SzB3~!`n83j2hiy9b zk;Jlr0{8=yP^UF7&W~zn5_q*MEr)IvjN@$Amw#g_XG1CyTzgX)!26aAsVm2I2r5JI z1riL;A|;n?e2_Du$$vo*g$T53v|p;g(Pw=sm~>UYqKBC!I7u?EnL<2i-frJuk^U23 zl$z`n$0;N2E|&DRJwD5<4@G@UXlHzDGdLur)Ks&PZ0rbs3o_*Uol&}a`vkML9*FjL zuEx6mSvE5fCIs@A9V^ry`o5WEd4`3{%31F%T!3nY(@Y%pG)EAkw=pcVxJTaE@@)Pt z|8m29fH~nlZg$Qaxbm&?_91u*S2fD??sLVC5dsUwxWV`eIFaP$?*D}}X64rsBx6s{ z1spEw$VjrnF>+6kIUO!oH*mfyzMHWlwn4^n%{xlqM8oh5@x9)OLWO#K;?3aM$~N13 z{A<JJqbeLf_q)5&@pOOE`}Ynhhq!+sg-iJd@6OYU_*x20%UV7AjwH}*i`dBpvV5jg zFe%SgkFlfvK709Af0PU5_=PN=$3x}h_Q{kZglbS4Pd`INWDMH8ulMMdS^jD#%A0`5 zDdgCz%k|&UPU-a%VMP<Ub7etlA?qr`$IFH{I)bJ28BX`dgcR_7Ul`wYyHylR{T?}E z3S7f0ftxAI^}e&B4xL0R0gRZ>i!HVkX|?vA`xh_T`4_x2#}YeOxW1bpZo_I+&Rt(+ zqH@OQme>)p)-^^JR1;<!Uj8r8AmjJtF2wh?k$0`Jj3EC!hBUr#I^V~%jmJvc@f|$T z<WVI;8WAzmedR~jpz00qfX&%Y*IAw0lTWHDNM2vF*nPCnAMP5?;J!CT9w$8d1S}-& zJl}9?+l!Z)w0DKMy?JMKyFF6a-(a+R@l2S1u-V9iV=Xb{7b^-z+O}Gno_hP6nv%dU zdSCrS*s|Q5PwEh~aXPs*!I)6F@4r<enKP=deJP0Vy}Oxt^~h@UzMfY3WzAc3@>g9* z>`IIboKi8P5{S5cT9^T%*-I7^5u*qkl078iWK^(Z@7K%T|Hd63!Lr>S5h9{P6LPXx z%E|s6J|F;+a2Cby-{sU(n!S;ROJdiKhtm4|pFl`R@bYX*+rGcl#1Z3TLHgsbrl*ik z%imH=ahCi3g**nbHB1{*ar$1$&~eZO1N5yfbmn{LkWC!Te6PE4gz@yzdIA^#pcqx( z{_$BXi|Y-%VkfmdK{pQcT?v<_NxJD}eEQiGX+Hta{IUT==8Tur1L5}vsBM+YC;hk1 zGDacMta;pT8#z55ell>a=tb`vriYtHuN~&;zovx66|8$!q}fN9DRoqVehdCKL(N<o zF+%#1q+YULcXGN)+YvG^XkNmKplHS1&o@|li=p6RW;u8{uG*w*09{F}PMg}3KWn8{ zuN`{3z?|o<j3s`|U07kS=8|5hS_Wzr5edv+sWxl*KzR5(d#s}9f(KXQuA9?%kk@Wd zU~MrkI0_B%`pR2|5ZPPR;q3IKAl@>I1lB8LFvIwVrE~%who&4^@3XTDrF*6D%QGJ% zxW&6OJ4M9;QG<hoLRs{git?20^pbUGuogFLXz8r~mctz%Q|eXP^*Rf4x=6<B`2`bt zuShDp2Ezp-!tU+81V8_2<fbbk-;XG0gl_NAce<GMv|!*%Rjt=^SDDXAQFmu;C9))& zjO3m<<Z5Xkk*Co!y@|WJbXtKd#?#FSSe`FKjzjB*{suZ*Oblaw*IoFQGkEJWlIoqE z6~D{+VJ?kZ|K)Fllt<lh;bvj*NmS5WOj5W->)Tp}A_?i~FCdZSNJs%dp(ssnMNNbX ziMAzXWX9|2-P{NZO=`J(^7DQ%NY6yx!)Ki)KC_c1*+TR=M0!}zbF27ETY=5?V!!nx zCW+;E$k1d)D78@%P`qZ1iOfp;xb5lW!Jw9vP8m1DtxwjNtP~0*t3eA54AFa^joiP$ znq?uA&q%S0IdpVbffs=5;+e=ssHe2N7>2#P8Ej~j{PqhJsl^Uyct{`f9tsg58?c`s z&Fw8)sgkmG6B0mD;ysl7ttpEVaMxV-Bf$YuQ4oQM-d$5fZLz+)*`ziiFDgJ{8H5F# zaJhRlWSWxZ0VSDnT+VzX4TaC!CDG#5Y8lkhEU~nvl=B%q$}fMBIzwxxw5+F&5MDvr z6v(d);&v~;oVxE6<+c+h5pRFynP@B5)1*)3KT>aAnrgOXI+$+8PY8VJiPhEZV5QMK zfmu6)z(&QBd~rw?g4n+^_c(w99tY`J)k`wn5M(X+<ZQ94ZdR^JU?2#hbg7NE=Kuxm zO9)TgH~ZkzcUF+Wy!r6tZhvt1?w71kf}i`_1;CbL(g9qkrJFtT5Dz5=YkL>8sT7ro z7#*d$?jfqSm{Lt*xjOc3l<J<n@Z+0<z*BB;;ApWwIIvR*gS}9*5{+=nmT$c&_$=vg zv8|K$@n*f8>QgFeVgW^b$rp5);k~choLjFURW8tCd;a=z?C`rOoAV+^GLIGHa3J`m zg$zeIJhYuIZ7K)PFa>1|cJHMay9vy*naw7@iX@iipB3Osc$yx|NPV@j1Y6Vg6ilKQ zMxPITvC(Ia8*i(5`A%<UzP?Bue`71hxcw%TeCp{-`MARIO1<rQ^2TEH9!pe800zhL zv?-xL%cEP*HcLT7L>sI9xdATS%9;V~a^r1PY+{dkT6`0Yy`{s?nYgrXI#`8ekfrMi zm(v?xezYG)Dmy1tV5zM-qIgLQAF1M{a#3?t2XoaL$Pf3iUg;SM=@cKg^YyP<sQYw2 zb))nTt`8AXPTx<u4Zgw`dbr5RNQ!Os&V~Mfw$hEScXusrKT{tvj@8D)<n*dyH96_d z8~G?B5o*qL+b1&drRI?r9u*0npL3dJd+JAAfzACp$B^Hv609*TML$hhc)O+_^nm2} z^?I?YogfV!#qd`URsKPK14D^VGgDuiwslz4?Z#2w!FQqD#pdD($DwPA%-6haWV}?1 z3?J>vh+`b6b05qkl{>R6K0(e<8AI5^K-(UN3Xv=J3k&a`r@f&a&jKw6Y+}8p%A-UL z9gvhmwpg9Sq@dwbA%2w|BkcX))}nQNas&cobq0P=JmbuG3o6+{f_pcA`rS3o-h4H( zY~hl$uzy!2<1`+aI|wXXM99iMH5xUp4}Q=}H<EURJz!qO(x+l8&08HHk;4L-#9<B= zJs6=7VxZ!m%i)V3S-$9y`7dE1AUbHEUhJwjTiGu(8701&yo9|j$_gA6-}A!nUiOF3 z(X2{{xS*h(r}v4P<jRi6Ki?KRb`r9qkwTl!v?{|HhsTU8^B?v=4roF0_el9_`8X&$ zI`cB})LsDqn-*62Rz8?MQRgUy`c9L6C=6vUzGsK8KSq%N@w2hjDs}z<#y(=B;958( z?f@r9JJ-iUNc%qLjWDEvtm$zZgF<Kq^aI7el+U@qFp9o{WB9}Qh&Vu-F6yTxOaW>^ zELLW0FzfjZzq>?P=iX*yE0k3l1vA2lvdYB;pNgW$W1$@+Mkw16VwOWk=T=Q}XLyfx zlBTTX^0Z9=2uOra&NO0@A}xJ3B6vXxZ0fFC#o`HSL@lt9)G%(OaV>QtTty%X4*X2k zN_ZRD+W6GF&)&59w7FlhZ0;8}6>4K}63reod-uiK-FdFi!gaMj|L$^=M6TC9F>8XL z-c#`YY=3u)UPved5r6}IXr+h98UWrb1HyZAvcMP~Rn6=|Eqi-mi|SpYo^9p$T56Z1 z&f3Pz0>)vMEI#m0e_D=l{6qw=JV3AGUfIN{6RjXq2R6b*Zb&MwtwX)!45n*8oK#_^ zGL0>+P}a@cPkC#yt7i!|<%tLkS$^ljb%Z#-GCJzQM{Z2e?^3YQeQ#lmJyD)&vNYYw z(Ja1CV=;7KDp}S^V$EW^Jw|Hv_o%?;Zg{msM$jE`vKl;#IyP}dJ!V>Q*_Jg4%&F^c z>9VHcBrl3PN%O@+b+EF%&G&x4<=Ogn>@c`Lr6Au0??>bDuV1N+q>z5?^4)a_{EG>C zWb%|;4AqQ<6I)Q?{Y8*cF=Z$C3<*a`@hi8A`}u^kGvYo5+Fmh0V&7q}26nz%Ax%G< z_+l^u=I5iiEOM1ETp0egqs&{<-6pT)PLSwB4eP-c@tO-K$^)j(c5mC3x$yxJP(#E8 z@^7`DZmIPwyW>TED+2n)14b~knMkB)DT&9oK(aB-P=FeYUBU-6VGB0*p{{@z@CtD! zy<<ysJUc49zTK8{n^e$*5%MhJnE>@Qr3$eN>I-<Sj0}g3WZr&P;^<JjQ&fa=r@?s` z4oA1U;<%HdR}!0CIEvO!A6x6ql+qG@VPJ!*lBtsGw^!c{cu(5PJ?A}|<2AzjQ~QXt ziEtM)quz%EK~u_h#>8%*Gm=!y<Uy=7rs7Q2k$G!WNRs$?*UjTv2*`^f+u-Qio5yoJ zB@T(B+L+!=Rd{acfU5b*C!?cK1k&;p^Gir$6Yib%aEv+vhL7IP42eVECSyx8*cKP_ zVsBL%YfR*jWO?2lDOYXbHJ;2hX;xUR_S)>Gf~A<{Y?m{?7&zHb(cw=v28pYy0gwf^ z`@+}cfM9B)<KidGNK2f?8iQ-+kXlquTHVX*Dv8zd9Zo&s>p;ubgqSO*Ke{2G+ns1z zK248EwP5O@z6)d*l-*x$OcLi)1gkJFUlMXJ)>T=~MvD8t!#3=m__FmuOI{Zt5lCz@ zu$9@z+d%FoXI=V1>wR^~V&fmI=6?5HJdco{-$$ANyrFS7vdLmoCdS};zCTfHT7=lO z;C!#y>ol8}<Wm!1xY1L-`XN1Ee1g9|l|4MMwaN9<fHXHmr0N6ARLI~8_<*@mw)%5% zD)hMA+4C&lTiu6A4fgV)e{oQroqly=xC5r=`?}~kbN!ADGLTMgo=n@0w2z5cq?{Z1 z!Jn1%(XN3?%}hMHE*S0Qb|Wbs)OU<EUP>kW_#L+7)|x&Q8_}%_oO*%cgCzKM6~;>n z9w4s#VDqC=$xCXw(_-|J?**|mJ}4a2wa|H;ar%h>f6?LVx+Rlwq8Q4N(OrX<)i|k+ zRujw5#Z_x}&uud~)f0nni5<_a<2TtlZ7R<Nmf=xpzMjIh?UAXRCGIG|XX@j%$YPJY z1W<Bcn3_uvjTNtB`3wTG+K32h5g=zCuV*oAhXL<fGYmpT<ys>ze{!@nxm7^LJU@x+ zabPuo33Eqqy;+5W_-d}z!Ki@EE@l>0v{N{yRAk@JU-G;b&b1Q%7iq8_?Rs*B<}L&S zk+m=|z5@Sm=7F~z7yJs}@Ze%e$8P|S=dxbRjC0s=Kf&8+-|?ux*4u&y=NPI<qLf1Y z@a2~+@%ZwP?^J*<_bx=52AS+3Hv8wILH+G3)c<t)sUc3k_Et~rhUe&_+FA!wd#W&B zi!CFRIpUv_r4UH#f6HxPc~~AoUJ|00DGJ`-o-M1c(h#RD>0~>>jZ57!I~I*P-v8g; zJnR1mx?CDBn6hqt%609Ot{Jt_qVu6-ziU@NG&rZuoEeGp#F=^&67fCFn&a<FdCwWL zy_^R+R^9G~<}u3a=PNn&MykAy5E9}4@`j;=jTeYr7dN5vzHeJ;A_(E%yL`dvY&{wZ zk*kBEHo2GHBYxUiJp-@SIK+*K1SgIET1`S?^%ky-X3tDG&p(z%iMtH*wtc<@L+|Dz z&I*Zmrfxt4R6ZLoJX}%#&|{<x%M*nF)$5{s^yJW)oUB;J*ZK=~!Y$f(eP{pSMq&V6 z4|Kpkm$YkP<|FdJ25q8D>X<_`J1>fjC+wnJ+a&UC%`*N<0|#`rQ9Kc2gx=#)go06G zkPJOT3BD(6$uwR$fF~$jz-D3khELdF-9TanU=36b5F>Pe5#qEy{_tx>`y;{&e5E*A z?t@X)>`JdnuXQyGTdL(#db#b+Gko>)51a8yn09#&qQl!%9r|9in#Q6#o&8<C5o<dC zl2|6Bb@n+V=q%rhaM0EJfzI0>79wJV93m;49V3yl8~p;}<}_RCP#NoSn@r6<79{bs zyGq=yT;4(s{J1NC@T9LqV|UyGy0et2Q+IH|5Qwr=|K#eIzap^ZskRLXZLNF^QFub4 zJ_@~x5F_umA9V!26YNV%u*7DUpHsVvAICsm4RIXd{v1BI%?n$UteP6Loz*4Z81lg0 zxI((+>AE9@K+5(-;?3`t!)iHN{yPK9x9GwW<+#BHxCO;hKUjaOD9v5kMTV}A#u6c< z!6@DZQmH<!U*D@u*{*QA_#YJ(T8{gKiXE;(9ivxygb+`a=_PrXb1J>3tC@UaQNE<^ zyQxP~^1vmBEwW?sLX0r>rFckkjq}@(mw!V;#sdOdOP&0)(A+$p>6@+X1&h1(VMv$K zi3oIc{wD1DdzUo9R92=YT<E!@lI2AZtzO@ce87RnA^t-<)`X1>J*!bx%JvLTp4aga zq|AYw71^B)=x~R>zEP99{^LT8*Dgf%Dv_Jz32`q+dv#VJcc-fSPI@owH~wSzSMd>w z;USVjhgn6*(h$~vSt`#5VvGTu(puAa=(grd6spx$9zBTml0*SBbq5(RyOHS%j9HwS zJjAN~{L(}A{rMlWxOO;UFp}o2yJZyqZYVYwKdB%0hz5J|(((=*Dn`^h-wW&Hx72uG zljN2?$-x(RQLW;gUsk%#1itDyZzDkvGva$@UV%;7{Thu>T$+=UQ$YXc9882id<E1p z^q(U;|9@AxYCzB8h>|uQgw3d1tkuit;0RmEOQxq|9nooPF}*}~{Ua6Z3e8bJju#EZ zIg9#`k65hS{k<2)K?|Mqq%C$Q^6=4vQGYL8RzX2QN$ro26h>E97g;)6sQqfGhUO)C z><1Ny#<h_S4n0}9m+>>?zkid5MzzkUlO^(SIAb9cr)wXTu_dtnyFe69R%+*IkkHTX zTi1_&2t=p6f9qu-R07xko0j*zODVHqw+>Vq2~sJ-nuDKk7jn(oP>hoxyoQ#b4G;1W z0Wd&T%CNX0k=9b87#toGq!E_@n~0*(sx_V07>vDy)oMME-dfFt*O>mHHUZj*ULQs~ zJ2a4~m`oiFI_pl{p?3Ka*(aQ4E_8m{%WTQ!vSr`(jqnjAWQkrrr?&<oq`T*oArM%_ zthvv`8r;=L7j6rQ_8P}L>kmGz!2VSrciZ!IY&fV>`-%`eKTccHV1?g5LsWP~JNa;# zd4BEE_7k7`+l7ix-wL7WWi)bUDjcwI{t3w?%{ApR?{MrfakzuUHmc9sbiyh={lR4? z2l)dRV-12`cUoktNpza!-QF;S!BM`KuxV&*>yGTx((V=;sn{0TD3~3d%C0;ZolRNR z=^&rhLy1TRvdln%?9K)fEDqstK*reFu+2IS;uHpQvwQ<k$1_nY2_8-k`r52Guw+1a z(<n&cigfLi5DsL)Cc*+WBw2=ncHLy%NNgYbbYPum{mXvNNnk8-3Bqac*x`U~Batvs z;<9(Lm`Z1TxoN5>J{}3~E(A~nM|k3VSMkY2s(8h0o7EfHHc~ivn9j_h16S-|@NGpC zcCA9~lZIo~2=PfV6?tjb=Z8tXe9W;V-eFy)k#c)bl{YBwP840(;&j^+UvXF_oV0LA zXB#MdW&C<wSt+rqxw#d8$!+*|1*Mlfoz4(a8NdE?EaORx-F~ZCTdK+n6^C`?#;_i( z^nnWqKf%UjqvzFM;_YfJMiNU2(qaW(`4O%2p}s90H_bTu-XQ8z(E=0W>1-MvWol9w z9C#%?%!`~Q?v{oCZuRgOe?A<J1O37oa3*4gXC{VcF=TtTezFve>bAb&oA$_QF1+?? zXTSiL$z{=d3=9|WA3^HR(V-`>=?VWT9|*#LySg^xLt%>(qJ|$&`5d8a=h-67mtIqF z&Nn%psZM^#%%+&VK^<mqaXmAQQ%ASJvxCy%>c3QqUy|{z(S3;b`Jsj|q}IXhTHpBS zR|j9ZNdLT!l&Agi)fPp#R-HU{1kv0i*NM-)-;Rr|j=k7q&KIqtwb;qEr7>Nx89%9K zNvNvpXzS%nua21>ORn2W-!eCgpTivN*lH(ViA#x7Z!*s5Qq9B;hQLfXRj!{05pwY; zp|!ISK-zR2Ogi<hL1gHZWxPsQx~~ggiLqr>AyiAVKvUM7mlO8o4Xp@d=x~n?V*%Tb zr&Z*Z3!@bY)Je%ZgziE=t`h15NAdGbP~v9XUQpH~*(g-fDJlib+Ga9|^T5Xmp+UiP zxuG*cIj0aPb{-n1dlK?!&77-Sjak`OxfGbm3;w825QLxd$y1K|HpPi0bjc&@tJiT6 zXM9<zHYzr}NTn+h<qvlp7^T)p)CrAMn$(cH%i3u?ys>nQWJ1SLpMwK7Y8LgSRT-yw zcw=&x=xi0Dx!a8+viG70k7rBF0HzY8E(lfZIW4@`od^Y$X9Jc}N<6o5+;1^yUvS}% zi`dwUL$QX>lo9}~W%F<NEP6bY-MyDE8{gP11YKAxg1WjNE!B#gt3?D1{ob~&xL*w{ z{Aw~K7%_g#IDEEv#dA^rwGHKFoWSQ~Ed|R$=Q{g%kW{N>KVAH~@=)N!I7wD#|GVO^ z4c3FFM=cYa11YcE%O<=blEfj64l)^(B(&+D8v@HbFco^KM^9HGbetVOTQBb$v=M!M zoTU2?KbT5gRi?T5a&X$gZq)KoRd3)#U)V3E>ek(?W!eVztY|J?m-AttJv?r36Aew# z%4l<Wwk>yEda|b>xqCQS&5nl1)qKJaLG_;h-A*<#J<iW<3;0i_v`_Nuu~$TcbJpO; zGgp_hCt;KZcH@wZ%a2@Rh1!gHURRrp465JmjRk5u(*sV{ejrqFn25WJKE2|eZ(pQv z4y38asX`i&f}P|0+c@D@ph38iZjPJU0EkrA5xX<~W-wJtwgypOJ%abByq9uh>2$Cy zP?>TQ7iVX}dCXNFW=X>F)}QagR<h`cOLq}&Vg*A7?Ciq5%k~GTe-hX}nd)e`Mz-7F z$AbfvYzx0(MAx>)^JpasM*y2t_jiZCSa%0sk6QR?a!AS$P#=an7JBixD%iZ{fAmxn zX$W10tK8sMD))A9X}i5YGfEZ>Md~iP*3&-O%jqElZk+b%gL3ROvx1k9T-%y!n6C{S zGs~5x%Xg~PLpXI?ZE+6dDXcE9dbBJXps-fyyi8n7-r>KRHXTcJ#s{Xn@^D#Pyv{~& zjA?uNI|Lj}wp_}N?LCGJUr(D{#-+11J``~#CUJ#BIBSJAI6~OSDhzJjM~?@TB(>A4 zo-_vCB`#Zq9K03!BwjvhePz*SA0c6+fqO7p)Wc6Y+~J0?^q2ZS?vzRkX3cA7k6O4d z4}5WWTr78piIxXGaHR25?A)wF0y(#nsC<|cboDlq=4c9pS_@~$BNj-_w}*bUS@t6Q zkjxp?cJJqk3S<qHWMZ69ah2tDB8YwWOoLJr#bWCzb?RDud)~7<W3UM*w$01rd2jGF z-wB9@HD>Ix*AKrlbV|!@CKwxoJyEx0AU|%ICG#4-l>!Qa?>;FKz`1Bk9t)iGHHv7$ zH%s<Dc5Q{R+*GN-nI>yn#?pR0Cx_#I_;Jh-;qLb0>-l!Z(fY^|>M`<}nE4!^&@th7 z`Y-i$sq|b!rB&4MuzjM1OT|?4S3?KAOR*XE>oFv@aaT6IX_l8|R0X45kIBu%C{u2Z z;+o>s=e{z;HUi}PT_|2uV90kza9wn5J?Y5T<|bF9Pyx)+v{X+)FXQPJjF4^b`bLq$ z6T4l&)|4I~fng*X9@XifybQ0AYvF&O0^)S;Hj}S0!ldoV|8t>1F}tX#ta6O%%;Wrv zfT9S94IBVJkAvfFfAq0$Y{^a#85<sBX!TkXlVdV&yIC&7OCWoRY&7sJc4xceVuOL> z>0-eiQDM6nX8Q$ny)<1B6Hlv373E3uC6b9s+Nc!>HyR7eTD>Aet%1bku8^Y`)?%KL z&7rEUk0IeLW{~m)6@Hbd6`Nc8)$8ypD&FR;L58Sg`n-&x2nmnNMI)@@Zod`Z_J%~2 zqpj_w9r{wGL%C^e#li*Hm-vmO1~g$O2hDGe2RMPg9w{vr4PYHweA;<<$|)}{{eE+r z0i`BJobP^Sq$w;$j8Aqnq5XQ0xX`BVLAx>^+SJEFr!ANO7J2o>zVhG3Dugz~zq-l? z0II4V-U}(~K3=ISz{G?(9B4RMs0?@<S8M<yI=r<6j8II7xRG;+z<}|-cSh^T%G_=a zckWc>S5fB$YfeBymN#wdH9ixk;9GI7@VKe8w6Dc{@F7qVyqY7ysEDWzi9j(<#SXy| zF-IC45V?!Z52uW|(6E;<PA+i&>()@G|HQ_hqz?HwAzReP<tH0C<Qkj;AU_1%rB?cU z>);IaD%sp@-|bz&O0!~5>u{-ZIT#)YN>h_`I~Qj`<zk3c-Ys0930P_l*LL5ymW45F z|E5hcBZXOt{Z*t7qDhSS(W5X)(N>pru*)&4cW*qJxT2;uqb;L!x8*-q;E<-zaFV+E zoZjhh&Cz*0yhCm|Fu?tN>ew~!+IFH(gYptD&C#3(ycstteX_<rHg#`n817OcgEUV6 zY<TeVnB*8#85{nYdd%SvvNUudUe{Ztwqv7?&U~N(zz<g&8^<qKruE9s+E+fE>fFp- z%aE=fDN_VVSHINgI8QP+7_Koc5GY;8*cn}}`i5y>NiTc!&^|LUws@DnRkJ1TNiZ_j zg18OEFt-cqPE2C)^XIYH*nLIL@(gjSJDvQwSaEVdzRYJ-&(lO=y~mAKI2$y}%N5g+ z!`icJx`HSBaD&RRN23oWvn}Z-Wvf>;Bg<3!NUv}AmXM{GTgS@8$)~bp>+!KM5Zw{L zfqXnNq!eG!0pLsl8t+tri>tGf>s}x2yW!kV)V}0x-sQFpr@|b`;pdw3q|x_y4w$T7 z6lHps`xiX=3G<h|kQK2y+$(ATTm9Cvx51`VPz}})Q&7WjY)nqtkJP(h$`+r(yA{EB zr|he{x4p}YMHY7I*1(<1UTnQhfcIv9trFU6dJCToE)$v`p0ZrKG>h!pL#2O*gR}QE zEzp7Mg>qv!=TIF(NO1W2$e#pup;h1R8pxaj6;zVJT@$=IA}SCrLVV<QH?b_@`7vO# zdvGx4vdoZwxRlcLTCj3P2ly5&s?$>CX!O%$vJvYvuVd}JU)o)T-Z8;}3M{U}Y!6pQ zre;x=R&1MGU`DAwN=!F5SAGy@Fayn3;v5>8WA;>O%=9u?ySXMvDAjW#*a*-Eaaj)3 zYg}+@NOmfe)1QpnNYdPT?b96dvW-1y62Tp+G&?c^QLXCk`{jpSOiCt0@f~X#RIZSH z>jyhW^6MbGt^n^~TCMwuMZZ}5sC-^-pOlRNc!w`>Uy&%GUY+%S$?Zc4)nMx#W?QO1 zQ{D^?{8A9q_^w~Hg-qXJsVrR&Q1?CAEJ`fNW7(NEU|I?F;xt)+1N6&<nQ3;8D&>ke z&)Hm+HHyfnywZMP8azfB=~(g<zRs;`*M{z|tyNp&3fE)K8Bs5YQb=R%@gl155R06H zVzZ4);Zk3~F^$4kcPFYP)%vE{e*N0<o`6T~$9XCXS4Am@HU(-@YSq*!)Re7fvZH_- zWReZpAk$grYaTCs5qS$!%RN1Y^^3`3sTw)_>J0$_2L^zS9tA?!WumR~yEapwt6iJk zDyCgKd-};`P4lJQy?-}+GPrl%;@09H?aK9%@R^X&({e#@SeS^nxI$B`jq%ERQg&lv zr<cpo!qWSkk3!{bkoddN6gJ0|aD<}I!m_~&<)Z3fL>syu2j(fELmF<)d-mgFqGjr> zxL};2*7x@T;zP*}2wOTWH%%e^AV%!G0^-h?TxZZ)<wV`?jMzGHyccIJXJr$ac?T{O zkN$%jE>aB&MFCFBiC~hcyIH0><pb!A&B`iYgN%iPP_^#fyB|(_L`8^u8tqGCe)&`{ zN}>p}PvDiQN!rfPLp!Imw`jc!G<RpaW4!}7j}lOToPYpT5Im9-zzqiv?Nt~v1AIp0 z1b&qJON)$05%y=u+;)pRrbnk<KR+$tqfgLSZRVnwtm9y&CSKYWcmyOk*1SBPv+tRY zvz?saNRl;kJ>bmVb~=b(pWQ+NwJ9!=GeB!0bNd>K?sx{Lah=NPmkL2t#;Xs*op*3z z>0DQtqxC)uRog3`ZCW80UMpOe=5=KT<*L?4GW-q91+ym)2hZ#TKLjrATJfN^`mtS_ zOeK8oVgp&c=9+d6jX(0Z)-E90PK-*O<?5{pH24%E;ZDs<^@OoLcYYF$@Md!UdJk+L z(Oxe!v-KJ8&w+G7ES-#_Ln=5b7pXna+M~~~F&fJ40@G|$_<}`^Il(bu&NR<YbV<B& z3ijvZK$`L*Avb&A#{4{uUEZnog#SE`Tuo=<s`|1fdBb0SB!T_iLmz8!-!d8Uys5MU z%`nF6HH)b2CJ$Q%3`ZuJx6x%rNA)F^hkcQFc2-|=rpV&9(wvYH<hTpq7%h~S#Z9h~ zO%|H6cu^?)!tN1mR_yU6XIzHWCS!85)_DxtOOJ1k!5SaIJvA|^#_y@g0Jg5EA#F_E zcOm=jY?%62FpIO4Ly=n+*n1kD9okC9I|_xS4ZEz6)sPcAXGwo|AZD1XnU(URo4kwe zZFhh#Pvbs@i6;L;qj}C~_eTEb&~5_|JwRW8^O5ku^(3h%X3lJq0jZKf;=>%ni`Ot~ zJ-+>uIysBiFXMsYVvU8o&Cn(Tphlx=H^a}n^?opWjCMJ(&M0Xb$kJM!d%PdNDf%L^ zq~0kX?<v946bP+2%-PCOm>|Vg9YAKW%p{S%GywvKq+KK6s(jA9LO{5TJAqoG*-7(0 zp5FdH?7ekRn^E^J8fXhOpg?hJgL`p@7J`-HR=l`taSK%(io1KUqQNQd?i$=e&|ra( zlYZxS&zvhWcg~%;f8Cp5@+M^a+IzpxyPmbzvi5%X-A}=LD&@Mwbp^`j9hh((oj%6> zIC;@ajr%VE@W<b&5Y9X$CA^k%EcnUQOg%XHUC@4;n`WxfD&MeP>NUYLVMrFAK!x)5 zYiBWKKTBa}G3db;0)htcK2uRpjiSgA%6diWFT!D*7G;cb7^9P%oca>LBvUmgN@9Cx zPj|fZ;*YaQNwp<9$2l3>vEt$+s3ROA3cnX9c}p?vyhlDIo<WKIV3cW_<pB;Jh4a(e zl$epXpJxtVN>(povxgB}P}iPSqNaMIvRBdYwQnh|S>MsFc3tm^y<Wcduom%j;`FV$ zL#aEXY$%km=(E-4kJVVIAD1wZ5GGa)E-dQUB<ug%123MDa!7pSv43D=>dfXrUmx_1 zs^E2jN1b*9W|m#dTOXuK%jo}|SdO%;lP%N3oAE04<jJYvS`QeU!Hpxj1bK3@V*@I& zcs!D?^_z=zb5=EsGn)b@zPi$Bp{J(y`bx}`jwsz<e%zWF&-ha@Q`vVMB&+V|2kwgH z45jF6OTLt63R^W1-EB_A0T5JHN$~J~9)l>MLnwtS2jc~eO@0}4ULx3WD+w+(RqZ|+ zo4nH27B8t(0{v>ne)o<G_C=D0J&D~K<W9XjW%3&rO!ES}^Upp5;5ylN$KTd&($vQr z+D0e|(5QKjjC_8kg%#un`rB5HJ7RRfHDM~rh9S|tpcb$#(}w10XYXlQ<)UzmqmO+N zC+pE}Pi}XD@VW?M9$y!`gNyVn26P}jjlILhF9T7)iy)!iRTH+D=4a`z?37<St9UC6 z^)EltdBL8Uef*>=*3@)=;~B>b2A-xrI8(20c0N~Pj`iw0E@*HI)n5=t$Ma0Su?YsX zKYUXtocSho(jrJFLS-#NI?`5D1E)qP%dcEt!J2ucPxI&2+0_pPJ!|uxj2=FEBQ7uh zcQ1M#+uX{wJT%rUKhZScxl#!%`xWC8YWT)o|6MIa$M47e`IA<@ANR&UI+g<j&<+nl zdXt#&MUW5UD!n3g#4NeJ&f$yBVyj!_Q7iUKARfT!!79t$*=luX!>_nrMlge+26q7I z-|Fwf>dsg}%k1f#8V^{8)SGcYq*huVUMKj?ppDr-ryiqE6FUU}a`X|*Sh_4ugEGsM znJa_eQVM@mg}1{NJFo9SxXz1};267AmPq48%xsGMGuGewmsBs`rCQ~Y&EDnj%-hDM za^r!Ii8(HKoGlgtba_X0RDzz%Ke_RbJ_vu*`iTF^?C+n&(agCKI+N9AH>JH<*_uS! zVH!`TaQiKm<+IIceT*jM=kfPC-S*Q}0|yTAqLcdhDML0BJd2ixf8Oe)+kY5t#iDNq z1Z5nYi3k*0IXi8scnoj!@Wg0aM_F3tKX3|0w|%5oOH9b5rBvquxaa~Bn3p({l>PZj z_WLwH4`xJutv%r1ce_~sribPF04T0}iia((O;YOnJ0B-}UNT`_;Bewd!~H70b4nH} zdG|qOyrX-hs}vvb_2tRoR(n8eqA|lngVVY)W>=9?pG)MvAa-7+Skf4;-&R6_&Tng8 z0mS=$oThrV$Z0Q}<BTVAI~ptu)f(1YJoJC)NM5<_-NsqT)5lY^5H@#0%{-l0NN*V= z`>E~)sf*Bo*a>BVx^pJ(*i&ipN?ZDP+ebO&+Q)Q3DlY;aIpVfWtB$84p_j88022GX zzxH<z%iF56j6P>q%4Uy5IN+p~TGfyzD&qovYC2q2wjYU{sI`Y;48N2Qea>er;|e)b zPwYM%K}-<E!n*p#H*dF-u}CtCx=keCEo6Rc=O`vMCNR2<5a48)ZKpF|CXPi6AVWVB zXQn6I44kE@cl@-r&a4(&u`IIRF82ngC40w(X`Rd2A|?foNNukriHRsQQ#!F<9w}ZI zIBA|xHMDj%UzViaer=k8GIk@-aqVL=>roj)rDScibyPxs*w@@X7}YYr#)_0c;|2-6 zvD9KP?8M^G|MQqdW)n_g$xN2(qAKxz=D**}%4f19+$#1>x|YCWXOCExKA%K~Ny}*+ zeHpSEyS3;n6Ote06l?s$vA+~HfA$NxeYP=t&<Y0Z+v?Ha;DwP({6$m_Wxw0s*TZLO zka{gkBiQeJ^5=x`+Y(-Ri!5<(L|!l-%4`Ia;}^>agzOw?rV#JJB4pyw2LJd7<abV) zQ*H8l><xGuyVYgr7UN3602Rix`sD>6w>)^v#WNAk_>oh^XsS#gaOBI^a=-9KO5LhC zO2N76lr~IA4Zdpp+6Bo=(j7Ds4PWu|*Sg5KMqgR*^1T+qUgv%BAch5pP=O}fkTj%P z4)V5izG6)$$4=I0yxyj{_xL_&<?G5*I3!#9#;!o0yEcgI@3w~0Q@lc^j$h;y()9E^ z<c}MFS;RJu9Y-rN#ihgz;1TuvNYIHd@@3r^u4eI>@3dG;?xshVGBVj7Ar0gS&b&oT z(P4j>Zzgi@I0${VPQ6gjj(kq<PKYZM1)(01WUE`CB1m8Q{OQ|*t|-HK+pY6{$45y5 zNq4{d3ICFj(M99L`T&{6<B$>2v&<e<!>A{hfeo*1G1easfM@;RxOLvU4R1A<$sULG zryf@tU9ER;c}|x9>TG985?@rh4MW^Z)VK@;aFfyyxjKofwe9}>SshaYYN|SFNvhP{ ziM=%$mKqO4<QdTg*zE+|96P;;DT7;<ED6o#uh2IcZ8#VRPkvjVxQG?CH(i*3@94)Q zZy6N2qZi9EDA;0s(BE*4hX=Wm{4U$QSKz7_mqt7c%622bv%hhE@`J0KxXmcCJRvj* z;$C@vAHlsI5D$(Ms^(M()oaM#7L~Hpq#Y5mzPZe4KbyYwyY}Km<hw%Znz+omm%Hn^ zp^>3T-i!&y^4VVZz|S*mMW*V@B`g{04l{|GDls-yi5XHJgG5=p%sqt{CTMvvcbl_r zHl-ZbW#LnAw&4PqI3`bt!(4hs^N88+TUrycp;P)sR-v>DlXoulmS@7BJCjd|2-S6+ zLaBTL=9*=7U7~did7-!Kaa9}27lH!5!pL?F@$>mw=HNDc%)m8%wgdv{HRH&vBx@SB z`I}*8mT;vp@v9AK`&HVSIytilo*KR^AD2N7M>?h)jO#j$$;sW)XXQS@!*$!a;R(|b z&9rH#@$Xz*_IvK#NBDD!!O@cE-9O7LSjX7uMAj>c5<igVLVpQp*$qZfYI0A}K1Sz$ zpF`PjpR!NhUJZBJ_R2)JSp=f+ssvLtt)*fTPSbFY5A+$5)-LpgE%$Pmjd|NAd698? zDO7YO+_Q3ouENyF(F*DFJsF6&F_rzu0{w<CAI5#?*s$?=zX+_6l8`W127%-nR#_Kl zvUlz6&0CVSu<PwS;y|Y?Uj$!qrhBekJg=H{@UJ^7FrfSwV0EN<Bhxx_<$hVr?FdxP zRX;0S!0soxXX<><zK2Tta|;$~LV5i?&WVH>8#c=iezs6JE0aHNZ@mad7SX0A3Lqk@ zjr{BkuHGJO{21eCv)DJ0mF>C?6~ZAYEG*F0nvS5zV&N6f{%GolsJ)@vP6YX=h~&we zNCj*t7;S&~W=WQz{*9h3IvJ&ljz@^>@9&p1`lze#@P>}-6ElxyB<4>$?#U3wB&S(h z(3OU8Nt9m9FB7Vd67KU^MVv@jrt^s15-TBgt!shxIjmEKURQDxd*2I%lmt}L(cZt- ziA<!ibSo7IopIYa4WFdK1&HN_4_(g}7Z+(Ea4&1ns0auocfg2<w#idy%-iPTEkSyQ z3!LkZ8Ju&A!{3L72!jSOu77gL6lay@&>!3v!Ct|z_kY_^n@|yJkR1)L26yjJBQ9on zX0)XmMO?bI04JBOK12%JsqpJlnKLuME~*634KP|L+}j+V*8e#67^~-6RXAUrL62K5 zW-}^rim%ywdqFOSH&_AY^xSrJ;4pqu1hLd7)WQz5H}Utn^e}40wz)?0OXHpeixylk z!cLnz(QJDKrGCb)8xr@GZ+%h0N=@fpdAML)r)IbywCfu#flgSwm_<mx$Lr&&)x$3* z2P;H*j$jEILP*FA=c#^)dwA7FV^n?V%ErsksrL~f%K0k$Qvt;~2w?qeGc%*jl5xo2 z3TZmz&7v>J9q78~S(&Gu-@!=;Jk<|v$``W+kn>t7aQnT&3eqnY!D{&G?m`G7ZIy%` z{hqtJEgF*-M<D2#2M0$52J=)$cvXgk5rb4zmx<vDXIqcjmk@b@fx!r0go+i}@6%t? z@#TU3elgl+8hlVc*0q=8fy*SiH>EC&k3RsAVx-UCwyFX?Vn572c6TSV&r&`%qM?H) zsX~vl+UR)v28rd*b;E_DorP05<PGNJidN6}%uz&R1uInR)@0oi^9{%fygE+nC(nKM zLgl#~-=G@kDpn`364uB7#gEznhEML=W7!WjC?l}Sj;~aq(eo_TR$%3cONSD1u2H#A zo&zR}W%OP=qdDS#lxn!J-T)iD*l>t{T|%MC;bZ05JT~>O(YKgJH^A#>+9JQ<3SCq% zzx{$t1T?BBSoD`S7@8<<37E38ka)JDl_<b(i<3&Ug_xG|K2_*5VEhl{X>6s-Py?%g z1HStQ)mNpUIqO}6q{;?SYTddw%v*rgx!Z?pY|Rx1g}TO1IhQZiVe9M;zNoy4OXzm0 z1Tp!6rCmV-E|=*Wz__1W46AQSVbYTaM|<rCHRsx!d*HQ{LgyP?!xW?-mP^J9TcRZN zX!y*A=xdFYwozTowW3n`scNV~iF8)t^0VD;4{5_)eRkm<kN1W}ApMFF|6No#HjEts z{as$j-CrO0_4egl=xk?p#b_uD)cj29)_O%!YkQ#HV@XuUru0v9DT?dqLYL`REQ}5L zQ=2(VDA&zivNDr>Ag)JUy;9&Ua%>ZB4Mo=6q(PHem6;`dk0E|%Y*c91Ps?@YvPmpJ zvM~oRx{Kh7PRtKkBV&%66;8>k2TCV%TV1#bZYRm2k!m>jw6HI$iDvvWCv-*4Q7)#5 zT#yY7QKn6(Wd=iQ8-7F3kiFv{bj+~!2pZR#5Qn8EtDR{uVazjT6Q3(^G&KhYw-6m= zl3FDdb&FQ7$>;O>tRlI&mYeo0B+|A_^d5OXc7}~yzB?Gx#1(Q{GEmd^Uu#mYYMSQ( zZaA=rULT=v-?Ud>Ze{f`;mzPvk_f}VTKqUae+w^+ECovHm|P(5f#{F#h@VI3R0T`i z-0FL(@6jF!C*S*`FBp@WeY`&qI9Ia(1=GsgtpNbQt8X|SHz&;x0<NFE&8PP2&nXsj z^7|ASawv*$ayko(z@6P<s+>=%>C@fr$y0%q!^p({6uMq6j)3pGb+32UquJW3&a#e7 zYIbuw;oH1zH6K7ncc!y=`=9+8k9EdU1JSAPQtVB{^$*!a7W8kx_$2b2hRthV1Uzcy zoFxyQ!$(YNx?h8Tr|rP3&to>EjMJ}F;kO*FLw+;+Xm@mKnDZTCBt4+5(<u1rWq!r5 z_a|lbgFz$t%SR)kELuGSiNaee;WgNOPcyQ!%m@OX`Za8R!gMQ}C?J4hyuj8xSg}=e zOW~#w-Bf^aH+MXz;(5QJJVXNox*fMh=lis~h)QMg>zu!ZaWbEc=}KL}^SzY=+!h<U z8arsBP6b2z@s50><@_O8tygJ6cvI79y?b=e8*OC+5L*;Gb*ypLX}uqA`WkS1rpTG5 z{glg5A$Nyq#KE=)&Q8!>ufqJu*=ZB-W=K)g?CpEEp)u4PTv4V#a+^xg{^{t-RNyRa z<wK0@^uTxbRnpA!IyK*D{a;?W$ai4+@RkuNibYOTa2jyB%5c^x2A)vN*WCKrY{{yU zyFDXCeS=`X?f=WYn*rpBp)67`i)X5pfx1?*yF4!MVg=Iv=voZEzmOk8U1;4^eB1vi z#hol>B*%?UW@lj_6&665*K$9f@1gOHUO*-0yMl7uWZ455?R1B|k2%EgqrNA)6s zPjN8qV4IkG^7bzwVomHA{K1->$*E}eqONjJ_cl7J!BMGKpvt#V4H<_186w);s&B1O zD-<v@^7`vY6h~&Wi$lrn#8rF4^-!zS%@`fmkr}4u#lv0qpD~_(bqenGdbKOM^X^>P zYK=a)aq!-&Q<{qxRs>$9U`)Nw#ZjIV<5inZbK7VrRcbY{>izGNZ&KG!?SDd>fcF7$ zo7r2(FDRJsM1Z{B$@}4BCS<o&v2no(x05O^v-f(3eWEmoIxqCcz>OLEwCIY6)tiKf zgYB0pf%h@<(HVDl7wd9yl@^G31JyvJUlkqu4dN=VZ<SIKGp#)BzpneKEq6&QIb&Kv z{swtX7F7R(MTvLEc~z|c+Q+z{!y6_A9)nO?E~Fn@v|j1AbfgL%XR^ka++Stk-|s%C zX%84`Z*A}@swzHditv+NqF&su_6xiVUjdIdj^6iGr#%RMJnytHK6<@BM$m3A?%%Nb z#%|RSO(-bc6S(L|hG*Qen*kXVU>#~}1$A=)m3Z4w8@JygvUat5$NcV=D1amHl(8`) zE8F-8XC{Ah`bUE0Xg%ud{t^VU{{fK7S*uUxb0bw<A?e&ytdseC@qP%I)+6;*tF$?G zpl{?(c*w`{IluC`#TPm3WL?5u-`?ewOh31K0mn0w$O%<+6?*7lKi;pWTq^^V^PzkY zeByj7gd=M+I+#tVy!E0IMrrGG<}DVcR+aS^PQop5iZnM+dH*53LEblw+L(|qL!n&q zAl)FT%tKDhq2kxhmmD?~9oMqII$tJ!9=~%X@OnAC?c-&n*MM<x4Il^jf|=JOl>xw| zEDy@pM6Wj-CB|k<`gC&%C+cVC!fZf>uO+T+WkKC5ZC}A+f5zvu$Fqs*LpLtNk}|z- zVxXX(?%Qec%%4gE)Q0cXNSK!<8orc&#m1kK*`viL9uAVn#*7J0&?++^py?sY-uz0Q zyY%n&D4|bFEAI%1>c1+Lyt(VBV0Vy$Lzr25iA77YMV$(Y?&9D!%Tb;9P#MU-n~L2w zsaJwc<m(?ZK;UBc?D6w}o_lGqVu4LCq;#r)2L^KJ_=bG?piX=5Ri;zKM+#o~gacS9 z0FPW1eXCmF!HEX|{GA!H8yFg5AG=<?!X8|{C|Jl!TLHS6r%DFiQA2qk<+*?UtVM(f z2KZ{k^B94aX9v@xpIUP?$Uw`@-AW7gLK;U4)BLQP>CbZ0zoxQ5Y%cC&BNCqup1Lbt zR?x$Di;Woo67Ctznc;g6070c0<<%_5{%#5JxTLdLtfTea1tVD%Bm<*24D^KzlD5?$ zTcnAyX-DH>Tcn3WAAfNHi=IA1*iJQhA-LUyo8MS1LNtgG@3s?^N2eo1c%JaQ+otK6 z;?zd9mR3^#Tb-pe@@N3y6M#k3Ih{v>wfN7xA&=|X^(jv*B|R~7G`AomA6HvB6Oo^+ zsK}$OOiSoGt@r-7`J|@&cbX2Sqw@_(XnlR3ksik30g+v7ZNfY44E$goIs54_w8^#i zqN{FLgF&Ag1d3m#!+i9f&>nnzecz2a1quKhBuM&vm(2fjV5W&27lzjJysl^{96-k# zQ<uw6A8mZiokldOyBRMpdRjla7WvKY_L)O~$0;WMAuL&s4<rTjgDh;u91@I7)^`^D znA)7)ch4!J_#WDKd~!rzh^Xqp9BYX7&_F(RRdNm07N1p&BihuozCHLjwv`$VD_3#U za5p+wrXWgS_zn6uwX%(U3#5w_KESFoi&@HR>I}(*s@rnamUF|YY|F*9k3I~K>$`bn z#e~$?U}GoHvj6GMkIs^0lJ0h>uo-0kkd~2B&yr_1mo-Uh$r1rWU@X+1DLK$W{3g4L zlcy=#0AgXx<03^bXPFtHG4Az)zKFfxiMg@&r;fXU-tu-z87(zkal2#WTpEV%y-3B= ztwuKGf9Mqhgz#-2B#uWYWn~(z4R9eMlvKGn_@Ul4C4c^Km@WEeu+l^R5-rXey1F8} z^W#}4h#9A*A_@}7Wc5ieA6A^$^7-qyejo5&y30A|i`HVAN!b1o&D@_~o6qB$lK67! zRcxR+%=0fJp>ukCIwhlduEph6KKH0Vi2mube`5N&w~Sw^Lq`vEN>c{9w@nW87Uw_W z1Az>TT|Op>n}eoLnZ~?g%|KhIyr<BiC5hM<Gj7RQFAD1XL@6%BC=@x{74|H@vocyA zS3N3O-*`e)NoLzBuC`VW4IyupBJar})XH@R|3jCAt{Fsgtb|1&e4myo^$nRpzn6q+ zLtx(<+76`Gb!lE^61mntd|~wp)2NwnTG5uA!cK^ht`T9<c)f;{I(w)YCkvaZkn$Og zF{~%YODtY2>`jBCN1HMP6W{82#&bj0kIS69Px};&;yhi7PTj+obXFoi;Z#VX9(_88 zaj#$yV{_wf#?e6!^aEjx(GA{4h4J0U%gyd!5GYl}zxL{i5s#j^HzTcm?OkY_F^DVO z-xBO3TOf8%+0`ifxlle@Z&`i4hi~bMhV_0h(`Gu;K-g<?%^t1%4}W^Xq1x~!tJ8?r zVDY>CO{qI&`3IN{sW_^+dgbRV3vj@8zd)8wIhvSIMB70{F^g_~!(Xq8kH_)DS7Q(` zcWLzLW4Pb{Nv-iSdYgOa+7>UEShF|0f%8#OFD9g6LU42uj6=4kBrc9oT364G)`1!d zZEk}iY_Zigeo4(Jr+J{K%}E5(uF3>ej8k0OOR{r!deBC#PPrld6*9+}3dU77z40rJ zeHkLhE3Qk?vRfF`huQCT9)-Gs>!zI~n>M9-736<#(|SZTc%Z(jyMj@DHyA*<0KPwg zg0@Dw=rZWgn_`8l*M03YtghgLaFFXivDFQ%I+7B`theDoEq$1ndZ?>Lq)ybULO{xy z;8vcs&O4_*o*J=$z@em~xwJxSum%fo)9M2OTwFpzK!}@d(2$8x-+rUJaq5nF1z-2M z)#M?9UL;ZYoWkq7q}@jP0xRd{&+wv=6P0>;IUOqH#OUFTTEXsu(c}y^yP3INz_NXl zZF1o%zZ^Qdf2>W!HM#J9hX;vkFt#nM5qQ+@WJ`X4yseANX!o9S3l0gHmRHR*HBRI8 zska@D2S@m+iAU0qtoj|(+pcn_kB%`%&WMjMTHoIs;6YX1PfrsFt!QZwIsK=jr$&*? z<pDW54D<p!{)5lU70hlu5KiTi0UZwLo96o(Y@&ptM~THrH#KnwD~iC_Y{%w}@$?>w zunq=U#f`goQLnIyfMC-N!U9PW$nLVpTyeqyL!2gq3Oi4(aX<#(d8oUvZ1*N%%<IK^ z$1J88velb#6<`LCY?;{q2LTEeop}o@xi-R`!UG$>@oI`NURF2#pD?H9({$hy4Cd?? zn21@&#cY3SROWp`r!+Z;c)@%{v-u@}d?@IL)?+>!t-i6S$6{)q*n1qIa%Mu#`r@xH zJh0dHKQ+(%@8P74r^V^=4|AoJ=r(jukI4~g0DSM_D*vN>5$xXWXuw+$Iy3ZRQa95M zu4xU?g*^|&!z=0{!0c~;=ia)r0f649W}_rD*x6=KMf|3;li+@h-5<Upm6+vyvAC1R zp63<FnAiDo_IbO9?A<L>-@5_mYu*o(ZXk=3KZ+*)_lfh-G-yQL$%9aZ+o6a5@Y4fj zIyCm1*LRn(5jSa9_`HFcy0&jtkz-I|*U%8pUR7}5wbAB!*TqlubEjJZ6XhO^Pm8v= zi>m9Q(x<zd}&p4HPVTokcKwpVUau(s1l(K4ERX>u(~7woU#5vY3L=l?Miqyu(yQ z{)gYV64Do``cHLaYBL8js6AypLcUpw0V<2iG|Ed&!)Ui1>wQ{*ye!h6b#P{EfWh8I za|)m1in^p*<<4b6WwWr>S$oHj@q}>G^yZH264tqhs!&6FDb#qW6efBM)SdrVNWAT) zra@jOV9KE~<&BwDblTkP?B&&SOam<Xf4y!!%uxknHH;b^KW&B+g}N;|zi8I&o<%y; z^oe~){Tc2po7zb#+Oqo6>sw{{Dx91fKdJxA71;Sb9k1`!*4-VNM%*FFUHn(b@{1QF zm@?m-U^a}kgU)*S{jE<B4d<{Q_Z2PWOD2VAo3R`(;uZO!yj_V}m$ndz;kVSN2N)3X z35LN+7p?LdKo#`bZDeYHjDDY5@W{k1Ek+(erL%uk0jc7v6O;Lbrwu>yz{MjeIJ?i7 zsZ9iwl!c%u%hr#0NtDoYDGtkvicRR`Rf7lsV3adqgYXRibtia83`_Ez5Cir<RlRt# z7NB>0r{2~zi$VjCr+X$K%t;KS*)aexJqWvKT5)P#ae6~Oo${a<h=p;7x~;LRjln~} zZ#Z~Ohs`*EY%}A^xy@5yYJ5zL$I*vxBR}J4ZG6y#q#<r6qyT`VG)%BPyE;2#?EFdF z2X<<X$E!w?!bn^|u{;R$@Cg8bQH;<5ve_sjG3gLqFHw2APl5!28u`0IL^#L@U2z;o zcd)$c_68;u;9_q^@$ad67ZuziCMLZqm_1|3GFpHElTEjn9lmE$2kpZ^{baekQ{S0u zBhSh}EOH95*-ek8Wx>i$WsfiHUv<T~bZh!x)D&X%?dFX{Mz;R|+nO6}h8sXRVVGqj zYArFf)nN141O1i$@3wVFM3ewSL<B`1VVf>~@4x=AO)uR7Z1@R#=i~1)9|bx6YdyeY zL+(=$rO|*qIvpdrJu1xmTh5BDJTL&@(inq5XPy7aib37aKjJvLJo#5?&_m2jcY1Gg zMJN34>$Oj-u}3E0RXXMj<|p=E7~NRSlA&?q@2Go`C**)}++`=BCxD<YOd>kBrOu!` zXv<(rjgD?!o^?h<=!~Gy<(nYB$Ri9bwIXzj3&>V+f-L=$iNu`+H9*Vvls>!J&ffl3 z?B5PS@gJq(8a3u4;H|8}zYBom^}j_9(E9!_0YHrqV|Dg_`y<eAVHI{E2sYZU7Hoze zv}W*DSm=L~<h2^lR+o#En}Swh%0Ng(&cWb5_LY!Pe>Q2V*D-|DM(cxH7rs5)rwtNM zZ0D4?R}1Ru>QEB@R>^;F+TILNcH!VTQO?9(Ej4O0tYE^1U$h)#lgc)B<;8(XhN{HO zk<tmuoT<yJmqDYld$kpE_F#ET7sk=P34jJTe%o!I_Pe|Zm(-`2fp#Hzg~{|*`+uRU z`C~+YB4MR&AJOb=jdaEh4gwYt&e7P}RK|cNDs1`ZG)=f2EQ0&KQeT?4pU$Zl>rTAH zR56_&O$3l{jlaA8F-4VimE@0FJboW|C*3n!ejkhZ5BJUKv$j-5slXiWE9te69GR<E z<ULGA$Gbz&`wH$NC>6~QUlL{0pwC-%cQDsSj}kV7xuV2f)73B}1PwMIsEv3*sA~@w zM)}i7*W@(XK8=lWk!4a#9g(1!zYg+<J<r|4QPT9Vl&!Iv_ds?u`GWbZOF~rK=Wr0y z45O7Gko#N+$V=nsw%16=IK4;~CzPwP&aF<ET^8gn7Xu<JA=qPa5o_qyn_Nr_InpOI zviE6JXjNzdhal^(aUYT4^o~=$6&sz>CfV&3RRR&oTE8TWdGD$d&ZXWx-+_NQ!h#91 z_P+e(=CO^&AYnb7!s}^TRjj0*gGYL8k=B?Xo3IO0HV0AfKkPJuv}pJjXiJ(dD}E8V z`BuplKF-DX3O*L#EgdZH;oBD8!yRWGn(MwEV%cxXa!dP~Dug2}aaS;GSP3zY(5Q{D zIs>rF>7MztzV;8v-TttcEO3Su+AfPZK?nqn4lW91ig`(c-03TvDUsib^a*4VhLkXp z0Od#AM3vliY5wd-R;ezNnWpcHUKr1a;T{}B0!P2+%+Md-I&}*`!c>@5tc&7=V=klz zA<8C!AL%O&s-P+q{JVsNuKxErJz}!TBcb1b?3H@Fm^uT&cZoElty)nxS7P*)DN_}B z$k<AgYa^pb9#fm`Vz9~U)6EB2cN-9}m!P8JY{xoeggV9+p+$#ALMrFxs5Up*<xwuS z-(BroK3)_g7?@N@SVvH5W%xrQ`eDZ}343(HPT5J><jHx})QTmtu({H5N7+9d=>)4* z`ph|8I5LsxnP)!T&zT~`0_c)M8cJnBwV}YpATw}Id%i|(*V4?s#+3(9aDtKq^E_U< zM(U;QLR=NvY}`%1_%NoJR=JipUp3*NIW8zzIfDZ@(-#KHueeSQ!5lhl25MZ{ehJYc zBMa^SQ(}9M+^wytW4~ARs7YTA?ALV*+!fm~A0dRIQ!a0%#Pqg)`|oC)Y+nF9xJ1aV zIN?`djfGc<aJsPmP%`|Fql%q;V<5Eqx9z*FxFr|}lsEOr|9mB<$?E2;^Dw5}u*j%t zw54WScy~)B81@BEvE6vr@XUnSc<4g+{`XNKCdC|rTk6K__DgnPo4>jBOt*YQyRojo zX-rtgF|LHzS&`I>n5|v3>K)Bz(AE(ASXb4^^6sK3wWPFd`QFq<i{!ZFbKnNsX62m7 z(UOaswb9Uve-l=hLo4Eqdv>;(pZFt0Lh7uC7(RI7CtS%Ny{PS;{z5)ep&+ET;&OnP z&~>Yh7B!T|Et!1L8;kGvc;`i*RCf$>)Fv<z)k3wLkW{8f(1abt9^Tx>FXrWJdbHY! zoWwlunUs|0zVUKaIa)O|uryVYu-{&9{ekZ#6n$TwnES0U*b6rcM=xIU7s^=u(y0b* zax3Sv&>U48T|Im@(bm=cjNq87%D+~%%-Z+OOt$1q8Rp*hLQ#R1qsi2R(IiB;H2gh- zZ@lZquc;=}8Ae9MjWTu-)+W;@15Y+CuMeU#lgp-j#=`mQxiW6pAX=b`G~xH|Ztu1n zI&3!s)&~P(i;VI-1|P*dEBf6R%HQ-e)G%b_d}=;Li0OXJF~(IWWQC+;sxh~jKit(z zCG3o!NrgOq(~h<AayOc>LDkQJ`KL<630YWw@&a+Lc%*BM{4Tmmv^efFGh2IA%fzQ! zze9idQ@*0OMJXzKXVRFCk;pcv^l!<^yIy*8yrbUar9RT5@)kjc{IJ|XXL0`7H7Dx8 zy!xZUzV6kRh1xcEVL!qMf8xJ<X%}4-B)L{B?!ML-DPk2G8FPE2N>$?>7h()rZ7j0v z8Lgcq5lgtu3f!H!JJV0e;CMDCdAc0eUQ$9r=;L|ZQDl&G6{0YjXD_>z_zhRa@3BtY z=ewC*{B6A<drO-Lj&xGK?NDn5Pkk^v?9fP_x9zG`X_CPYBC@H{_5s_4q*O{X-7!=t zP0ENpHsf4T?t`NLqy^ysCr7y8N)E{Y=X_GtD<hB!3F+Qc;eNBv9r%CK8hxG1))5rZ z<lE_H=>9HPrA@k>p;{5^sY^UCQeIuKoGQv>3>s!km}$&P-ih8nvM5D*=$fb_xv*Y9 zn4Mxv*5?D4N|up>g&m)rNQ#(8E$sSNoW(ry8}&Av1aG46WkE$=O1GQuo0UKe(sLS4 zULG2&lhJeVTQ_LZWYpcn;^)fNTfHM!Wv7m{{;%=P%tPt&KpfR5n**CCYRzr|-={W7 zT<d#muMr8=UQbg~BQq~Y5Z}5t6Z#b*h4SSgAwKXddeAOmRWs8=2^ikBiHT)~&gN;D zaj7f&(cJ7)+9Dy9)D}~NAH9_yi^)y*-oDGZ^nSYcpk43Q%+n_|M6WCsm3tGpCDCge z&S=r2GIA<G;4pmEx*t9`b(VSO80a{p>D%gDr>gV}J(#63d&i&o5&d`ZFcFG3*=;vE zTF-^qiu0hYuaOnhqC#Qa#*0Q1-w1-DQu8?n8)~bt-qNuP>V8NU7n|{-mh|y=RUAFc z9{_61Y~846M1-_}r|E%FqDqP$!(S=rJ3V&{a_Ms;o%M1zE6S=xcA2I_biS%!yNgoy zk~>Cdh^o7<3Y#NCR!r*ITLSMRK#oI;dF%UKQp=V?Kk5<XYEKOt^IK|5RJxfKg$aKk zWEhceuwGC|2IzNHp-kZZs-T~$DL`OXQNGaDk<=!8%IZB;$N1*^l{c=&FYN33&~N-3 zqtA2u_K655@JM4$=d_K^!%GD4&^mf*nh?}LEL>J|xBvUhR4XN#CC@N{F{U@PO+KnJ zN(td%nv3*@L33#XJA_}W&}(0m>f8=V%npXw<n`$<+*?>?bqur{QV>cQrbj)Vo6CUL z?<H1nv3W8Aze$h{(Qm}bcEdPGR<2#jTi(;KykwIr7FN@B7ky;t$*gfaw%BqVse74p zyut!>J`_EfuI<U0F$P;lAMb%JcH#&my>Cmok75tWP-9N>&8+qvj`#42i00h{U4MCW z$(2Kc^*}AWayP!U+4ESWar>{BCh2`~TyJFGxiORvUS%yx$7G{ty(Z&T7oy4VzV-<` zZQA1!>l2BWjEl^b&qS2XzNS6@`+|O#A3uIO4q4D_R1gzRFkJ__VFj_jpXn(?<hZsu znoAqHD#xK&TZQ$>9yW$Q3)7g|l^gJJwO`60S=%kH=pU(??rxCPASyGr8hL>VIb5-d zmamrL4_6pJE>MZqESh3Xw|W&T=>yu!8Y0BPJrT9H{BCMv^ElXxj;A1+lgrM<uPkm- zKExnQscfT4B{iNrOLR%M&zEV=(9qe#E-n|Qu{-*!m_fZjvXyZD7gelm{z0h~Aw{~N z90;eVAWY#xmy3|XP1Egq=iBZwJrJ))tgO%Tn(im-RTZhf4d?1>;I~Pukp3i02rR^J zG==&_uTbwlt=0rFXe*pqFe9*K+s5j;9aX$RAXebk&QEjYe^JC&*(zaoBV(Fd9i0L0 z8owf@BCwO3$2_zDHb_h|8Wv$uz9IX(`sTyqQFV;#C>yEki?ss>nbAr+!M2?75~r_4 zn1Z&$`?CkmxoPh*__yb1?p82gWMI9?N5wZMUX$_8V)q*R-1<86UW;tvJ&#FnpFXea z(|k+keb5$RV76Vt$O*<ek4j?I8In?;)dyd4%4~<;@?vLY6gopB%AeuZHdh-2zV6qb z_YRljws#%c$8Emc^_r}98*`=u^KyGgFL}s*yMOdpe|8^iQ@8c<aAaiFNTY#!X`(4Y z8&qcP_Utmi&D%?H;Y)y7sT%o;j^5=&M_04b)5`!evGdS&Ve2asN0LWbhwS~UMjKT9 z>$5wDqa^ZwwcDsKg1vS{m-StzwYR8;7YveXAPu~`pN7cH0WOTLVcoS{u+XqcWRk?* zhTN>~OU&QFhMYdTYJwQCW^Ll~O5+#nM-SN~bkvCAGTr;`;>C8-h(GMKNZX=P_#M^d z_Av9Ns828RcA%|ux%JU(b=Mc>B9F6$jSBWrPKC^}lLvqQqlu1eGjH=;yvy_1{((0z z&<5|Uxfk`Z4rU%6`_O3KCSs~T!Q6vty}eb=y2s9*YxXD!Pq##m7evj38-Q{VT<~PE zW$U)-0^=ew^x3b!+B}X+b0~XX)2T6)BjG*5iP7r?543MaL%Qi;09)Dl!DRqT7pajS z8c3MrHxO-aETVr6Qx#}pqws*%5sVR?&f-S!2F|X<ono{e;A8n&^oWR!_jImxWfsx4 zqaJPEi+PVLF3I{+l9lY<jw@~oGvR<cGTb6@A$j*WZl)E~3>clG7Z;1%YAuI_=%*U` zne2p)e8WM(k4Glx<xwXlGVNbfjcS^%b)7-NV=BI$2X$8~9&S_F@4&Zy=YM>Nb;bxJ zE!*la`1WpvHiQ2x*z3j@mYuK>rOl!hq2`Kl*6|N(eR*R3Gfd%km8FQXBd*fwXkF%} zSO+;fP_y?rTpGF_5AnQS4xmC{f!CswGM+(QW;Sm}>SB>;4@yn6?tcbO`8l>z;BZcy zO5L#>A0``+8PSnhmekU+a-@Lem3&qg)(6h5pOdk2iJGJGz0a1{oP&lR{jiR;Dkz9> z!LU3Dp|y7}17=x|!oKG}*Nm;OeATK`)?52DT*UUy-6Z2__=44kDf@!5?7u|T?*%Ai z^NVXIb-X!x;wOesPXI~L^>Bp`y#=ac_xWm|US$lIa5oew1XWLl2>GTSmj!)m!_XTk z>|CQpzv5po0*SJ$#9OXxQbW|)Cz0(PKgZaj6sQ9X;zwBJpAK0m7)!&F5bMHhBl42A z3IoY;M3vWf7-qq{m4UJ6kSN9DAG6T8OU29>eey^|gw^i~+U)hZ1uI{b7;rk6k8T($ ziJWd+F>}65_;5ewXQ*F33McX#a$V1dN^k-vr^#!}y+o|V(-+rT)#-^!tNiqJ;a*xt zahK&=y+2g<TAf<Ec24{2^0re=EIt~cIWRnWML$z;--^@A=q^6f+`^kAsJ*8xp0R2~ z-;ta5BDTHV^F>-g(aw{*Xnteo^wI^NDG<yE`pXKIpQJ<JDPYoa)8~5%5=oOd@>JgN zxGX_Kr39LsL(hD18XcT;PXc+FL~+n=jRyQ?_LM~C%{O2tXE)A}NOxN*$JJlkqW7!M zjaA+4ox}bMp#P6agVibwLLh@GKXN&uR8kl@PwZ*zt>;!+1I|f5&pPuR$7~tU!cMb2 zyZX1zqKPUoz6B|bGWb_aR`+p(ZXCKCr-;lEK;RQ%&HJ-$9<-({ah!ausv=WiBp=;s z2LCEUE{SW}$TsmV7g0>?S!%=*^=Z?4LW;}-Nw+_2Jq!Ss9}|r<I^~jbpk=`{P_5xh z*J>U%+m7di6NzNhvy5ZpgdQ#MGQf}aHP2`UP#yI?GsqU6sUn9`k<%EG|7t9ktl@S^ zYw&APFJEVfdEp0M$!Ff)J}-ARw-)1kk5=%1u{r&t+yE(;3rFl%M3#^nuH^%%$JARx z53%2Gq*9^?9zbNfr?$dKl0qJ~R*JHb5k{}j(CawEG@T$qxgE6Jo+c350(C=`%2C_% z)_2$hqnoLet*@78Awu;FY(S@&$4Pv~>Bcb)R;30Eqqca@2cX@sgb=yDPp%;$8;Vu5 z5Kv>90T7{J@h#xbd@Bv-n(l#eRf5?+Bp$#<@bblfkodUw4(KqMHPTw8Ry>NL#86cT zlwJp%{HRB2pRV?K$D6xv22asrHZin+5k9tO9=YKXve}?ewkIZXVV9#GD<oCFo6yn& zx$;M(?T$%kcuOASam&F*Y=w&YL)=Y#is%4e+C!P^qxpH5uIKji9|pYppb=oH*W%i8 z(b7X17ayNZM%XNWhMzfUR|ni6wROQi-X47zq{QXBck(ke?BS+2VM%F4h?0##Nmen5 ztAP|7n`+iACzP%`s0LdaM7~@v>ZtWK1Vd~QneJJvg>{*wb1kwEhQ>89!Pis{mPU8| zwQQ7zlKCWa(#U{zeU7EGa*Un={a;E|$FN=yI>Xvkl%yeIZ2JxVU!9f1AvJ@mT+=bX zm}nkRU$@f;JmDkUmtLw+ZdW?>66&OF2T~)iDi4J+<5Fcrma@(zKBVy~Rq3C7PxKHF zaTaG52(E@+D|7c{@WQyDKLh6$ZKGrcd|+NHaS5ouo7*rGc#C71_-S5+31{tg-&06A zytBDPeJ0$Bd9~$}+)5<Gl1^ls`)Y3g`oY^>&)PC$w~tFk1G=Z*to;`wcXG{K=hDK% z`-)cPH7E%KP&9o0;U>(1_M_>t`>o3<0G9#AqJkvSlpcMy*-6cwo%ql=>?{crox=|w zsN%B8VnX&XT&?siMXGq!pax46pIMDovJ^!sKhIqQn5R!SOO!(}e14GQk&pS5b*;p1 zg+t>|7+9wJPBC-DW>}$WKj6pF`<P5ay>SgKj(T3#^b!t~#h)rz5+8*P5=j=+_Ojs* zu396MR&@nD_H*{Otb4f)bkk<^ENS`5Y~nTHZtsI_KYRxkDiNhE!#VjU7i%(*UAmE^ z#Y2o?we6BneE3J%?*ABbyBGNARsw!g8JZ+gWu>#Jlom9=cMKoVk>nTjM7$|v=+<iE zcD;8~Qg=PrvIrg5PD~|{0&K`dmEHoGc^H+u^^6Ty_pdi&H=x`K<S|}b;XfOW8S2VD z(4>m<{1*2Dz5gA8VeQAXddc~k{&bQ6kmKF?$@KL%xRPw7F~tMtl|ndod;6Z$e9cq4 zCdYp6ttA&_K@?Lmw~DH&BO~Eqyh)1RXH$h;kNDAz+JjPoDybQP41Gk_lABTE^2+Ia zVg-)NvuR)Pt{ktq=(PN~m_$20w;YyGomR_<FG&0;Ce||?<Ri)iQ#t5TdTbp-lrngl zr?llC%)V6td?mdE{N~pKfr`Lpn|xG4hcVUE6tUtL9k*mE<ck&3r9Y-3f@uQ=?vPYw zj{HTVfk5_6A%fL{anpuaPlC$uggS1C^X2~w>uMz*<>9KSo%@1phKlQWF}Bw{0Zm$@ zwc<RkM;)E94dz7-O$}93y!ua@Pq5zDBDd&+%{PWgAzVy>ll&z%@Hf|SW!pK%77mN~ zEt^@)s*2~T!xrxc2ExNc)tG3#jNAwF_YY9{SS~%2VHWwl>8dF?7v(ok)@Bc;$c8Vo zI$=`muhjRG#zC#aSs7Z#Dnv049hX>5K9gFrM5VoC3_aI8SY~bdg>O(nGu;+wBh~cl z4K|F$X{_;cg*y9;B2$q<x=xQ5){6;mKiBtGaO<6Z@(Zr4&Y2#|I)X;l^1cy!dwaj- zdb;hp%x*Dd?gZdAekjQk@k{)&S3sb^MzP3*jblW{ud=zm*}KgOKUz%q-Q;h$P|e?T zhD7@BK-54>eA|~3;S8_>ND`@r#x7}^LcGFP9kvxmvW&+ZSEmvN@Wc~3fKCh!<XST2 zjt1wF8ZpkKv77j?{CG#mk+|}6xco&HKOjiS=0D_<=_@og;MEDsGK<-CaOo>xaOS9} zx{hasI&FYmqN{#y&YZy!c8s`)OjV#w=*9>Z0$vj}^!g<K&tG%IcwCSF7?Y<bkzPay z8e*BJgYha9to}Z!X$sQrgR!~M#l~p&9jlAPUHQRvA?MdW^9I~%J<2T)B%&|x^wTkP zNZ2Gq7t1Ztz3xx=m~o*bR-Lci!1n>w`**Q)bq7`{met)B2Zc`FCo>}u6R(u^zqkNE zK!GZ8P%K^hcuyynq+bg1p%%N2#S~lydcCp{d0f8q$7^awO7f!5x`>ma>mM2NKt78L z>-QBZt47P>*Iw)rNxir>mj*Wx^j@z>ST#IkuYzRa;$2qIAZsQkMzxOfvrQ8Bug(ec z5PrBZTi@MnM$Fvs6aT@}8v~N#mjVLJ_+e!&Rs%0l@wWlnBaM|w?IxS9+R-S_!EBLe zgmM<9h`&M8b6(j0M>S%R%8`2m?ffqU%wv=h?Xgj32);=&8Kb=)@>nE+4U2^%%TzI$ zKfOJGnE-l+Ghb}mMx;rIqN8WtsT$p$_Yo}@Nz@a|Fw1Q<EDrXqh_DV$B@3IXeOli> zBF5w+|Anzy948=()&<fF<Ur{7{E_b$#2zV+$f>HuJud2F-#{QNv;O{FJN2f<mv=t8 z!Ug>OoA=*oI*>`_k49+(h9Iuekpodl%)XD=%Px|HA|b`WCT~<irWCYMzh@j(-97i* zM34`00MUKskR^J0`a1n`xxD>j7XY9E=-p}zS#pFd;o*D}{T$S$0^r)ArsnnQ>`9mT z`J^zr=+Jyul>!+E+U#F!zmu^@)}o8)7717^ssXtZlhl7Hja!08g@v63biKn6+d<KD zunUy*kz3<*3IG95_xSgyU~~uVQ=xfJ(TupCoqU4vhk3Nx(<i7+1FksS=w_554Mbma zhhb;oEwmv55-n)7mT@XH2nh*&TQe)sSb)d*6E?N_<*ArxLB2J@4VQeMEh2JY7gV@C z&oKyc8h<jJd2r#-H9Ul0uCG^6AWY%A&Qx~vtaqzxg_X5MzII-;eLXS@ugoU}Sw{Dg z3R?Cj@=M46w5o6Ya8`CMeDiX1|B;Tb;^$y>3l6%QMO(jK%lIzHWHA9K2`fXKh5VMt zkPwvW4Lkd63w3~}C~1Wq+Xn!MfsO5Vy9{PcJhiM@K#G0O+zY@SFWLooKe!hv{*wof z%542lYK*8|>R_<AAS?t$q}*qL`|2lvx6pAL-#XHrgMvv-I!pq92Zlh!y#5EvHi`wn z;lR8BUOoT!{*NWbkcF5R+hpm(SJI{0o0UurPcg(``8z079nn?x9|F&%XI~pTTPfs9 z)DR`{DEqT<kr=OFVSC<QbZ8ugea!BLUHrb(tkz}5lBbe4EGxYdT_K|AX#Cm0iz%sc zijy`}Flz7kBhvJUHkz3?_A?42gdNXjMSw3TFI2U;qVX(!Xz{Rm;nt5U2-`9K9T}Za zzp#c@O5P&evvQ7#kT7S)?pBNx0H}EUUo2zPJ$^nEaasB<QjS<+a2{F%7=JB*{(@;t zPQ%j|nEqq~8UA%EDD2n23xG}fpN$xx_%Vk5{r`Xb|IQ$cGwPSu|65G}J1<3i1qDD5 z7Z3S!6o%Ras5L9Oy~Rum_t1_{Yx0;B<I%PHoKFDbMP}ya1DM6}wtd{LuBxgkDWClx zqkOy%&?UwgCP0=}oV>vQjBd0#u6odnhLIosYi=n8VM_UbL~Q>r@WlTseEI)N#R6}| z0H0n}(~)$Qc~TiUPx_3+nKk5m+Z_#C0mja^b?Q|abpHbKivA(1BKsauJa5?PVJWqE z<g?BC-F@jor^D2sJ5c9&o~%X_rKv$_wlq4Eh1Aw2;En!sR=B=Llh8{x{*cxNRQ}6m zyBB^XA;!<+M8g>lVMNH$(}aictu-U~vw>GXPl2x305#(Oh=x4qi&f8b3HR<Uu9JJK zVo`lrgWt@Mn9LA7aYanm8ENk^cr85CWq%ySS58D|%d*;dFyJs$91&l6yjrcdp&#{X z?8v0~C`IB6J)00g{`5>(1PSMuC|Ahl&^RlL=aMaZPZebt#L?jP(t0M(>3uDSNwc`q z<XJ^+b=C^{^0)P~-<n@9gP?^ZSBa$Idz&DJ&+0oXrN^X%&6c}Mr4aw+)78f{%@`^U zQR?A*%RKW=mn^En=+x8GFt?-HZ6w#UM#qa<k-1W7PpnUOvObRL8N=+>lE28UC84cw zYTf6liLVDQTRW<3?iL~h>@7da>8|<#g0MQDWrsV67*~$i4_z$|!?T3pb=%&pMW|?H zCe87mm^-I0drLiaB_uZ>%c_!7D&I=&M|wS>qio9g2V;Y%IZx5zjnsl?Nv%4ym8;EX z-=+wx>k;+ls6orh?ZeV5$vgc~Tq<4UQ`kB5ZlE_kn~)?8SL2YaZ}!Z2(_YoO!k@D? z!3>g7uR(3U-I>BJB^*%vpJLd_Mjg;i?(=r2>S4>Y^Q#%ZBu7a^2Qne2oRr(Jq04YP ze7ClId!UHSn#-?dPp#E!8~?m3g-?e5(A#UK(y*Sx1<K}`&~A>JjJ&<n_5oK{nk`IT zm;(0^9!~;xuixK^Em-j0Kw6ERweQnX_{h*(YN$5f<1~`hAFy*FNmL;jAe)H+@K(1x z-S+o9<eoWYXx4hPjC*mNy;hsr*YUI^;XJXm-a8YHkTl7W##T!>-<kAb-{tiCyf5yo z9jIh*9(9p&9vItLb}(+$^Dvvu8rAzFg<#B}Uh*@>EwO-cr5CCTrpz?ebxwP~R!8ua zP3rEQcEZ0AhdEx{uO?cJ^6P40?tbU{zYCu2-aHj*)6=4JTPvOy|7E7jc`y>b%Q;-B zF>kxx1aC;#_{bDjvZ_P3ID;t;ANso!10Py%cBYgb;BTYKd3Q(3eiNvy)2`~8(0Mw$ z^H)v<8yhqR$~T|HH|aO>^Fa;Q>$aC1c5-LU1GW`J{ftE414MlrcGiE`du~BmAAi9F zE|~rj7xbk9IsbYrX>@S8s@#1)(OSsyf<zL1nD~H#iu7nTF{5hz#v0-|?K#w>?DxT* z>}a*Vuhw&^vi|yMR)D9${v=+CSiNIi@=F7W#*!-JzEIN9s!prh(x#pt$YNrLgHW#? zy{)K3_DDO>XX1}35U7DVo$XE|MLtz3rO6`>4(;Dl?|R?vgdmahKh7VQg@%nhVD;Rt z@q?Y`k(Kk~X(mf2J9X7+P_v&F7Fb_dD9U(Ve5ng9w7ef2x@@Nwlt$Tzumkg+;}y(A zjqBh=Mm;FiscZ^>)i)p4WvxJoF5#}Oz{y_$o~k-)A2UXV+ALv9LrIXdLNnb*1v6EN zkeasE?VIEKPc4?#4gZFziM@FZwten&CKUm@c7F=^`?g2%?^_`b1JU!J!YS@o%Fuwe zMcwM#O>T(en}Y5EydmWwXN*HKTs*J9yY2cSI4d$wh@-9&d1O5#3)=c?ZE`$sMoGgg z#K8~uHO`s&4G~O!PFj^TI{a$^V|l<t0RmZ3h(?S%`Pjo3^Vm%ShfIj9ZEm57MEh=^ zp`rQZ)=@t(#F?2?vxnDy@5+B`@7jZ!KJqwdZEX<&&&aD(<b_F$D|=cTj;yF)9T$ zAw&`o0;G8fB|HR4p~oZiqyjY_<t3MfmWBX<gkUHHjYxPulvhH+$fH0^f<TQtLhO&3 z&duB(H*+(c{&RDG?e6S;cfPyxo!#$e_p{#>zVi*A$hNxc%hCCEg{|?IRt~>!B_PPh zS6_WQE?ceaXtR)=T&eEM;-ahP5noNq{xm_ya7s!M_kzMayeTi3>L&DH44G&`*wDz^ z$LMX5az*%5c&v%;n<xElw~;BSS)znIefu*vYL`kV1l3~h37&IXB?13z*q!!cumk=d zRj;=Jp9^@<@Ui<8w9ozsYj&T3T4W0knb~)w2vA+!63LRv(xzc~4<W0-G457It~3rO z-@jk_<Pd3MRh>DKb1*lNu|0?R+Q*R8BO5=YFdwRFJG(FbI(6~v8c6sC>yI6%09A8l z)VmqgeYU$A^Y0_`gR`68V>qVNs%gZodSy~_OwRxbp%cwFDSNc%Id_SbSb=I|C2hY0 zBpk9DANQ3XCM+S-7TK@Yf=AKDLEvdIdBM2XP&@C)=J_rNXuV7};xMI~t`30D=uzwM zYCfA(%u@4;1I<d?x3^TLksk(UpuLpw<$tLU;^RCBR!M%AB7it|!P$71=%F&g!XizA zE}R%^oM1jOVSe%GQ$}wxDHJgF++?cqr{!bZ?3+LX3m(p+X5#0SW65ZwHnb&5K4NF< zX{LQN+=U|9z50bnbd@1T7XxmKUkc#<kaRM`j&?b@^pyNfBfaKAK)A;HPI*a*#l&TR zs!IW3_5f=tiZGj#&9IJd{IhF3iV$Uq0o%NqBzht1HY1)&99th3gjlKP9H%?o1G>iz zsG&v;mWPw(72h_w+Z9qaUIE;hHfihI^|75A@$}0%ZGmXySb@7+sDCuS3^bg}_>N^~ z1=a9OnaxfaSdS7g?>TmnSDkuz`Q2-r7|T{T;4|&GM}7|n$RiEnh}f|oN?p>AM#U<_ z8^8z~9bLaw%X9U*=H!y09BC0&md#I87HvmAEEcbV918~5NwG{f^_!GIc|Lcb0QVDY zUL(f~4I1td)|~p1g+*I8Wzx}f>&uf=v~ZxJkT-Vaq>gpnN44dc67ytaFo{}}vt6lC zM)zEkg$UTb9p~QZkF}ODdyXd`4S89DXA;sQ95T5FTd$HppTs+FAHV!6)0rUkPP0dx z>nCv(o_jix=+_iR?|{o`HAK<2RNV*cJ{fmtx;aeHd5Pg`VciE_O?dop{_Ycds6Ho5 zCz*dm-(>R+E(p#n%-_uoE2_kA;jsLVIIOyu7>JYdL7<J!lGJa57kOQ9u+w}j?i(#_ z<|-VR<dHjMp9f1DwXv2yZLq$yb!9G!EZdyS-sXH4DK1kGCX<$%YY`2NdyQ^@o_hnE z(#3L5+RCQcdAgwH$^jG=d+W97+ZNs4PDB(LQ3GlCd&PsuwYH|5jnC?&gY+{uW*7H# z-%N<jKPo@quF?uP$dVcVIqpmjH;58gs0s|K&+vLNsb^ub&P|0+HPA+7k6S#RK6OHv zcyp8w*0^dgwVc14noz79ZXv(P(LLu{vF{CYryc9*#O;P*$t9R{mXlP_7)`(B_j7Nl zCELnB?34sIbi6vWaEvH%f|;ptJSU5i)5Ojy)~RGZjLo7*gn)Ts;w8<s<P)Zq03#%< zJ#u4p%(Vm+UHkIlS>9-l+Jt^fw-KyUsn7@<*0om*gql?CD2>KkwmA=GEpQd-^~-6x z@<Ut9QR??s=p=@%I9(#Cipri2H;lKj>YS6%E9=_eV`iZTE(TH2H@D*a0typ1MHBEb zynESHBe+h)_oO^qobPp?R%o67))A3D_5oR{<h!y(9g%sQ_7iJM-@AHl(u|Fu_5jEY zKTT6T)9dxSS|8`X1$ok(S0+H@S7~5P0U9vyO|`rKTy0(_grSjF@DZ%M?xDJv`@32f z;f~gGS)UMy<;6+y{0eht<1gQKv3_h0rF@!_sjoT-Gdn1|I`qCD?HPF;X?J^GJ_@+C z`!qRwW!-1F`I;GXYieAw?(+yvaZ=5pd0rN_z5@m8)4um@`E^vgWg@>y0Z;M$aH;3T z$gp`N)*g4uPf9U1`oS20Ay?bqx-Vt{fMO8@Ky?uicoG5>HZ8@#P)3)21jwsjI34~C z$pH%$Q1>sC|KD(F{~&De|89R5!})(``V91rSm3f^e_sP&npTPM(8MSznT)3-0#T=L zoJz0<+xx{OP{{-u8RJXaG2f#*ZK8p%;XR`g@IYeZ0{zGZ40Q*)xL<*~c|y;4o`!*U kGSF07n&ICB$kb>;OzM9Y*n3>!3kVnm!Y}#P`9@^@3Ik%-k^lez literal 0 HcmV?d00001 diff --git a/doc/design/assistant/blog/day_45__long_polling/phone.png b/doc/design/assistant/blog/day_45__long_polling/phone.png new file mode 100644 index 0000000000000000000000000000000000000000..389334d95a8f616818fdb63dd26c273331a689d1 GIT binary patch literal 41602 zcmc$_WmH^2*DlytAV>lPcY<3WK!BhL!QI^w+zIZDgy0gK;2vmPgF^_x-L(nUc;nVU z&&m6K_pUYf$IM#uXMpaas?MpitIn2Z@7fiqrXq`nO@R#pf$-$zq%=Sv)I#7RiG>QZ z_-*Tx0R_7Cd*$~aP;ETU{YMO-j^d^vD+#I^quK*1bmnpz${>(0GYAy)1q8YSnu2yg zAP*i8Xx|J35>5w!NL{j8)kT4hC!Z8$r9jAkzj+;{NkGd}7dd@5pp^U1M`qAo9Jn1M zFZEu_d+Bi1%U^T*5%XkxaL{gA%qBln5~pFLPIl4oy)+eFR1{s@fybtH`{T-HYcPik zG1ZR&8T4d&jVsndHEc^F1;zYgKg;Y(1OrpisQmY5Sh3LSVbUB?pRsfQTv*oDGG8K3 z=&>KR$2TeUWGQ)kM)_pMva!1@c;rX2uj)LU5Hq3}$-l=gSoB{&K~p|Esf_Z3(!qjm zRt(Mpk)qsDA#LW&&8%S|+N>!GjWWe^bqa3^)p&3>kMpqTx8N#!_qOsxZ|f(Es&{kA zBt*-+KEb@XEB~y%PBPR=SxZR#-sA!6F)yv>U+ZLVO#P_ug(;0i5B3`A_RDp@$YP8V zwdU1Hg?b^@Wm#15G2R!|U;lnO==w~~=%>Z(oLHFwtwgcHhtkuh^uIf@sHdX~x-)Pe z2t`DNeM0E4P{*e|d^K3)6HAm^83e1>-LJGUAQo)XFC-%j-};lLN~y2EP0F|P)^JwG zN6#UZ4xSSIjM2-3=I8N-yc|6zNosQSFTUge^n0(luR4)XQmtw8&0`0lw0c6(0ersp zGc}Wn1>HM(ROa2`eC;0B(wva6Z=ub!dBHytx_Q~9cUqE;X_#AlfMsM)K|^?|u6f<8 zY!m8~)zQqITfMLrP`GR<OH!|?&?wfjCw6xV!k46w5}#H~WIf3;6NsS|`|av&x@lv= z&0|2q8O0vu(J4GO-iEquFHrG>=kvW-r=0{bkv4I0PiKBiUQo{QEOPlHnM|=p9K{NY z`CxU348%<Tt2$_1>CQxqu%n~h*m=l|pNJ&I!qS>U+o1US@e`&m3BF0=7X_?mS!|t- z7S+GUP{-%RZMkdl>1)((o)|qzV>aTnjDc<3gB*yf(dC$o7d(SIQBb?1f~34mkw-kZ zy>$*y8sos#cE0M7f$|wnNCM;FS+HN>;-Rl5C&YoAhJ<V#%*mB)O;)UMblgKADaXeE zmeC^eUbD#ZMqtSkS-u*tPrzk1AuKl&H*noYK<Dmj_L^6%r#*9(5g(_Wp~$8ko53>n zbRT)(vIVBQqW8ViDn){`AY2SmLd>=I&Cgfth_Eq++54Xz^=HNuboZWh2v?N<ENU=0 zib(v86Jk(#oIVjOn7JaxDT!qpXc4!^1iZ{=FQHw!1&96nKZn>;a?=un1(P38MPyc} zjaZY9L~AI!*E`WZ=pk9Z_`J`z(39zP-PRU#2Z<zlJ);m_xI*YNPX1=y<%h?9;{P5M z9c|cXXUo;%%EZmes#aL`8iw0jQ&9jOuQKI+P+k`*))-|aQb=k2@l!}h=tpOERASNj z)iWHtSDb9RwhhNQXaHR*0A14R_(GbwPEWBh7$SKyOo$6YWqMEpndwoZ)~uj^iGx4j zxC4K^9H@So0StL3d`~$+v693E^~Tq?x;v&^tS#Vuk!)YFCigy5&>bFGyYqG%AL8P8 zw)S90kU1kN-e0K1bpFe+sR|XNt1g%QB_)qHLU&wL*kLEAb9(;KJccpZkWxuy?X~-W znPPS}w4KLoVihfX-2J-3w{Bx&<06TLPbIfjRMhL$xs<Q3t!+kta;oL5owlSyLw5$J zY2^UBcCn?U=(u2>se0nemj<U+p=~SxTYt}3$}p*0iLn+?&T+|Pl&_<O@bR!hrg}Nq znebkb7#nqjDvD=VU@P!qd>&-su38I@mR68QtJl*h7M!^kp5c}VY?ZcIkD^6#KTI@h z9@9Fp`McHcBR#2ae3AJu!Bl1NdUT+o*P-xd@7VFYStwUy)y?2ux->YT!wtFNyfCTQ zb@M~mV6w&yTGkWlt4|Z?{nBnM?oC@F*yZ2kbSe#Gq@}mFwu}ab>h4KNNhwL@eswbU z0_rb|$CK4sAX4&jm4*|-{))|3Z=SulPTGbwyO#wJpIQ+=Zh6#kTkWW4M@s`M(bi?C zth4Mj3hB2~iayJNNH*<V?RHR*W?f9RmzulMJ3XOf1*Xj@%o9^TSN|dzf--fMOT~zT z8B4vIC*3my#?NRZ{GpA)+~PbMgP`u==W%xqSM|?3aY1{S*A2TXf?9?F+}&L?RNKXQ z+y-5LH$)odZDwF&mZ)+O@$oS+36+0%Vl)Ps8|(`;<WR@iv?+LSAsVEl#LZZEj_<k( z7#r=#P1L*-oqn-=!JnTU17!ciYWfF?7?*?-L*|}-(8rVlR@UUGptaQ!>GpCgyf;~I zIj}<XiO6DQ=3nA+qRCOD3=Pab^sx~H&N{CMzoGnF-O*IRlU|*>6N`IQ$0>#3XUslh zn3|O2g-0ncU{I<JGVbYE%mR-X=c@riVV!mru41BP+pY(gjB<AN;Y;6+W-l>ud+Xv^ zyMO=>nK<(lcCY8z0Mmq1I8P@sJ{29$RNj<%M#3cT?((kcTXzIup#=uh++)k%6z84o z?~0uZEsrVNrsMZ;aOXlz`ESD>h?*sDP0({gkr(`j*P{w<<2u|%;t-rN@rVYKA{N2v z7Pkyw#h8Ehd+jg0e%KmROmn54ZSapC`_c2@T|ej>C090QG&t<6H($UQ)`+#;;_I&x zk1zSSbI8}RXb6dMe8Cm@k}B7iRA`bj;w{GQV7O*Mo7Wur*IKR*PgL5?yN#Pk6?RYy zO+b*#Gb_duqa&I2`(Nc}@w0*xv&c+_@2?_vR<=z8_)nS;D9Oe{0~?a9jgA98W>aRm zRa^R1qp~tG4R*7<^x}_NGBO`Oesi!K#ynVVjMU+vKe4he;bv#&&7erHL_<Yo3@+rh zV*Y|pIy-WK%I&g4Am5Rl)rv`nHDQ-R)lUo~O@@(*yTX&F3fj#YO>35%cf_9ef0Z?T z3;q_2mDg@mtu-qiLM!&L+HYd;=BMJkDOi8UH*ZK}ZBOi`<2OyxGmNf_JDemGM)-m} z=7pfCnwr`CE90f#zx8NjWMte`l`hWDJ+w^o)mT#;;8jmity91355HDuoKI<Q|B8`k zmY&!B?i*}H?8O)SDN&;?6>j-Nx|6IyZ#Z?Kv^<e?c)yZN{o=CWQQ<85{=I%j9w%SJ z>9feTbCeTNsiu2Lrwnj<2qxr<MrGom%ItWni09m@eZ})@_^PdO&iQuf+&0^DrSE6m zj0e589UsI+YbKhqw~j<)L`4;ws9iU0_`e%?ErowU7b$aoTanA-IdI&|GHW6nrqRa} zqfp4j%J~c%*Zqtogn<yBkkBYGqi^bZn?N!Gr;2vkFfdkpV7yJ*riL*ps8^}_QpZr7 zfO?g;Kp8T?WD2%s<qYq^4SnmgO1tCw0bUiU5QZ9*mbU-rAwgdqE{J&v-#>oJ=uu-- z{@j^hf3tYwZPI1wQL^3W;)qg5Cw*@G_4Rd{RF29z07f{<<M){43BBV4$>E(|oQ%WQ z+d}@7+8|t<_X&EjuD{c3Av)DJHfyB1)h5K!lk@XlHv<HdM;qPi`?J3$NazKRF$Ypb zC)ZZ%WsQCT;$KYlx@P|C5nISov^pz*KFVj>8H;m;iHQja@bU9z=Qcy#o`kB~?N(-g z!9Vlr#cjWq2Nlqz<EG?`@B7fUm+P?ktSwTjep9FBr<gO_ctcVAJ8#PD=BU}!P+HoR zYQ9kuMncb}#9W`K{$o}_M$)qQwFJDqEnI#j26nrVShq+Upxwj9Zz7J}bjN|unY&Nq zUDYXJ3DL6Gvb$4bqW?0Z9JzmfWmTVFZkQWq5WD2_9n*yk=3beIBG#%;g3A;}s))TR z#_Bq(&PvqT*?Q$za78WB%Rb94)5}T(BEr_GbR57ucuN1}ryNQUY{cq=Wq5k(3nyB( zsIlWdhN6GK6{7Xx&$DO;0y6=vGpc|>F8VJkj0*MYrt1E0Uh=P3z5ejhpb6i5Y_P-o z3qNiz4|dqgCgmB&-a9VS=EkC;ZWg-VtM3T_?1wu2datQ7ds!vhU$w2N5+j%tJ=n>X zSunzKUfAbuCCU^j<SV@VUz~{QcC6IeW={770FAM(o8suQ0BFX)E>uzlN^f4v%}hGM z_tMgRlf9TL)EGch^064=?rsht(vnF%bTQfsbhKU{9vrh`(f=-_67x4ZnfP`bxAC=5 z37W-tm1hBrqrBtnT9sTi4RuLmBuOEPo{B|O(n<o?=YO@hJBz}OOAEZS%*c2_d1Yu( zmB4to*gS4V=ykj{y_I`1Pl>A=9p!pnZ8S1EI5O6no~fy3WWhthB+pBRYdvnAGu*0H zJTKVEkOLdHwua0soiCF5+{t?Y!wVXB@CDfFXBZSJiltsHL6B>89vqN%^)7-=`|%tR zcsuO=_B@GM>}K`3;uq$-IFrypZ#H;ch_>g^RKU9~`rhz3a<Pr8_wv1)pEi}Lz*qiO zR##!~(ZZR2dv&H~P7id(Fi$U5oCo+`!gCfN&ebU7urczOKa~8&z-mTR+!>d0vvHiC zohhqI_&@`$D@{7=c1BpBKJX**cyWJ*mj|;DXdJbOQ`=FK#N*9otl*mOc_mmiS0GlK ze?MFSM=^@&>)yO|f<dJ~rm{?7k84(?M%lx|LmSK0hEHIBRhPRkZT+H_fx%pQCp$ZP zU9}PU8~+A_N;Yop%gakjv9qR8!^eoYh?DE<HUd5wEc(&7MTa%76S<bPA3r_U*&<Ia zr*3@eEiEx>I=2-QqqIHt=LG5K^2P*^*Q-ODEaRR>3&)YR*DZej&0l;i?h@;GE9Y3m z9=61;SL$82quSs(KfO;2*pir`c>|tsg`E5D4_yyUPAfl8GX<Rk5tY{_$ZH6n^@v&> zUVC$1QN_sea<f}$l~sLNLxWVA1u-BLb3C{VQ3X9__|iSY!+!6&-lyKhzFjm?)6&u~ z@m=2ij2jvi#ha?Fqm_Jna}(G0FeV}3$e)h;m+RMem#P?<&Bq6XrlzK%q9PX)3JOYO zWaPu$<+R;isqs_#<|=cRDX93Q${r;nwkSwG1T<%)F4Vkg|H04{y&ojXNJEH8+~osH zGC$7x+uoD4avyV^7Vr?tJ7zjII2s>i^IdRR%<r03Rb=p76r@h1tzg*|*x~06pKGZ9 z{8w^rNZUS+O5T!;SxCrcBCqIl(`kCoJ=S4vwnAUSpk#7aB}dd!`CNkYHXn?9%(|5^ zE~S0@=>{zRXm)c#Kq=rrCgyvwGnxqn!wWHxi0`BnuJ(p0Ce?xzB3}D;JiD<ng))U@ zKPrS$Q(LW}V-m=v#6aH4igu;SIRMzyFR}t|e$FN(iI3+oQ{f`N)z(n~tB#J&k6DVs z!5=#I>>M0Y>SSIB>J;A(J7GA=Z`Aem^-TkBw@twh#I&?fh;B8&dn)NX^y1=y$j1ku z%Th;Y4sTHuFndJokaF*@ZzyB41}&QIt@%$TZhRuwW7d_|V`h<0W$N?m#-7CIib7^> zM1D6;+VR6)@n5~H=tFi~K6XB^b#`_>K0XEp238t2cLuBoCF$#(O>--YP!bRjsH;!@ z=Ubg3)^oXO%L|J5QC?pDZL~FcPf=l*-(a;&^Uaihb&lBEv2{2c+OXM9lM&)`I4LV} zbF%ukH{3AkA)NLe2Eo7)GWnsanaF57(lJx5nz-n&BUG<3SVAS9;A+zqWohuW(T0F9 z(dX|<s)XQ?NR4W~8i<vf8>9R5@*jY-$`U!)q~x)fz)Bjl;NPFMQ~tA;)a7_{X(7|9 zQC$9mbDr{|P$p*f_O2vH?nU39wS?T1l*@-}sGpzTb1I>U{(cr--a7mFs&C)EnfJ$K zzjd>E_pbXI3RWG=!FL_j;E7qx6Qsnm3hi;2$i($6?CCy$2qitudcT27Xbmb2*XK?q z_bEHZ`N_gpCnX1{eS9V=QUAJA0vc73zc3i!|C>~g4-E~Cj*595uY7-F-(cYA;$mZB z68K{5s}98HZjS{CA4NtxQB&jN;{(g8T?}pTv1iDvL>vZuwk?w>6!F=g>9}4o%-#Xt zbXt$+h+1Pk!?ycHuw+g=vN>Jab-gB1-SznA?((2Np0>+!cqd-`ersEwTO2VWp`|d_ z=UI+>H?dBlP+ZsEu2nf#L?iKumqNJTt3fpL^WCAN`7zeXa}XU?2-9eE!N5G<v>TPz zONK&4Sk=*T-@#>yC^u`$&;#Z*F|qLx6mlIIqshd?1Zc|FyBu%p%fQfJ78M$3nrn^M zHI1DI8r+VbB6c{HD?0w)4>uRrw$GYt)tW0c2P-S<>({62J)uCa-{URpNOjY`acOF5 zN+xHmS>P9sQYaYX^=0;2By#P!^by{7QDpR{WfZ&oq`v0sjbQb)N?$Zqc|<@jEz5a& zM9$jVP}<Cbi>TyEeQnDd|Kq9suTq7qTI~V|Q#&SxHsK(?{^wR(<j%AUr`^}l*V^cQ z(P7td`zr<WH@<j`&i(U$LuoO4LEZ<I&1=2~T%@{0xZAQ|y`RleACqU$P-7oxGAb_O zQn}C*yll?PyIv*NPjcUzC#UIHLJdx9V<`o)e~w5=%e~!nJ|JAU^gPgH@v1g$IT~oN zoh~RWM3GC}Te))<D5X?7p_o`|MkdRGIQ44sYQCTpqVl+U=RO9s2`!Pla{bIs<;c6} zy#<3>Sv62h2HIHba4mvgAwuNS#RGgTEQ%fs>dx6j6qSWee2>_#DAk)Lj6AQ#;d4cq zg~Il(GAeDl+oT6SYR3L9CuPelO0u*Sa3%HRt)r_GF}+J>G|>v;Q?Pm=gy#MAn~?l^ zc}z$Tqr4=wGjCX5aoTzGQoju5lbb(MU$e(XUU9y{dy4H6;Cu8?YYR~*?nFK!!g0x6 zw}(>n>#ev<+R3{8;2mkn$;rNlHw!1~v9{1u)+naFFfK_{+ALnn;}svkx(Nw+U*|kr zD`icjTOABsr1FE=8F~dquXiUutj7Xsy~}xRr3>0E=I6O8;K>hB!z%b0xCwtiFdZ#6 zAB=t8Os-JO_*qw{ad6bO)lW;~>ry_cw+GuaG*Qpj@C&%^ZJws_8F84Bxc$8eZ%6EO znS!TXM+1jbM|1t}7o)kwkiXo<Thk8}6%<|wdlI0V<eT9{W1m+U?JbohUFriSR$HGf zGK5h+kufrnH4^w1)r~*6u&TeEsGT9`m1)Fv)>l^_<1r(1SZxYJY4zIs!=n^mwK_GW z>h$P#UPIrjWTp8yJDg3}dUJd8&}qAwP*n7_czI?<3-p3nNyvRSp_q}ITeVE<PhTI( zx=#-57EsLwul`;i%vTd224iOrvJ3w#CQcorYaU)$hui6aGN)g0>et>4!u&E7s{Ahx zBFnhjCzfO{bq&Vuh`UxF2Bz!YcnDVunq)fJ!Y0O)S*jK6m^N)ZK;-1)rw`5?1or_Y zoi}yW`|jTYCv|h%=iG36e_pIvpLT6=IO8S~DRsapD~URA;Ql*%scW2}w9Q3CRg1iT z^U3SNK!K_q-u)lE8l7e}n%LymADfRSzLc7(U`=MX8??CmwXXK0=&NA|mHet-9>+!z z0O!G1YtC5bw`;+8S2{ef*m>0yvB!lkCnqkj<$^&kv_<6|RvP^#zIy8i)vFJ~v~O&8 zsfQB7kRA=GoU-*>B>x!LWqZnlppf?a?CY0rAEx##IatR1d(=N>_cpVL#9oD|cuE@* zn(>m671KqAu)a_3j*g+Dkgi9`%K1w!zr~LC$+q~1puDK2$TY2r*zK&~FxhZ)T(Cj$ z<i7jUBSSPf8|dB0?V;dWrt^+c0_a_05m;2b#rjjf?`Vq-WLv1y<6sWtE}U(N^3L1) zr$X@(n9lMroq6D5`EkiaP0hRiX4ykHd(eWDjcrS4Y<O4^GMk!~CRq2`I-|3pLaFjh z+~c1%Ub9v{Uv2XuMc0&5oA|1nN&Efm<ao7>*8k)$lSH7`{LSYBK?nbvzx`LotB8S_ z{!WC`WJlElUcu?vV!ao%4eoyen4rspdD0+-qed_?SoQJzcB3!)?&_$}f>>4Jc54}a z4@GvIUfo@G#Zn3aEY6h+zS=$?e>g8D&DAa27w1yf(x4(Dvk=JCPaSPZUVX`*T<gOf z=L`*;PK_l_Nl6t2i$UjMSeL*0qRnO2NC*ivOicdNRZLpknNR;Aq3`+ZXwF4U_H}Qm zWjezR7HE8Zu<+U(7;9`WDkg%0-{qusvn;?*a4UfC&6_u`U#mlA4OAs;8kfehML1Fv zK%(QA=;&HHI!!i{zkEu%ZVtL~{5MK_m5^nvU2AKPp{f_upffM<#eR{h09N4=z4_pL zb^odl^gh^l$HYe0s>=WM&cgYih*s;3!O<ad{dmvxbf~-+LL$0!9Q@qEkfa4-8mn}# zDpR09%>RacGdm!hS=p36N<*$K9whB_$LSnPj!oSA14YWV9GPg(k|TVu{N$bIdrOxe zs`j+RL7kt2bF0{X_Uh%&+%3&F&{Mxn6kZ>*RnbY4(zJ5Ay%|u$2vq~Ulk1beX{e); zE#b`R>f&EuOh;gDU1kEnJ&Y{&&s(>h`vX%XDqYkD0^WuEL+M;$l=f_0!p#e9WEe>X zTA!-2Ja`s`eZDQf*@o#s{?|hD?jYIRW7h91i0o(w2U|8wQI~qWMdS3GTekOCwGy~S zcDA^~P?t)Gp~)#Wx>@ybd)X6TFJ<cm@y9WcuZ&A6Ba{`8xWwO;hV^?_h}?yfO(dsd zl+kQlVMctH(4b)t$OhtZ<yC)(t7{2gYjqtbe=UH8@d8doHItw8V5D!CgFNq#?f0NK z-U!$fe&R{PAOfk&93emiFOQ8hAVdb9IVN<K=!i7#OpCM2)>}w;A_y0Q+YA6LI^-y| z_^Uh-0#hu;Bzy_NJtn(-bZ*bDkR!rC{Ax6Gvp-a+a#TauCUd*ja2WVzoJ@699fc?M zSfH{*B(g>&vIf5(d%wY$kL{mgqoYOfJ5iymL4)^m;;tqFbU3x`@0?v7AFnDkj1R&s z1WhpIS8hXJl)eHbFcQ2wPWc63B*nDzgUmg0z#sn97e!p%el}FD4S8ksQ%zf&3G3JC zX8#L9LZYaWJ5=GmRIcU6JNy2DZ@pw+0g39$t)>NqNq+QEbjGzl;LtV!J0Z?*VJ3RD zpKe#ZR99*~e)#n1`d3K%)zJnBcQ>uU@A|mbyuZr0tpwb~2ns+vTWIrwFVvdPSLm-+ zLqVhrHy;O|!@I8k?$1I>m3&U1&h1w-BmJb{wwrp@F1-%l%MZ_$voD9DxkVAGDTx95 zkt`<ux3|uu0bQT^&Q3Ss3k^Qgirihi;2v<U-_D+J+mDJVjuiHePKC-j3z&tMyj)Gd z9CRGK+x<Q^tDoccmdl{w#}8Ir_LSn{V#-H7T4+^(1w^N@yfHp{+O82YUqK_{Sy3Gi zzpYRLcJ3fyVR#4p+}zHG3$>sMmZL_4N&s(d>sRVf0)nomx6tIc3@9iOJE>eh(bN3g zd8-^sik-_PZUmg%>w2ew<4=gDalgN~;N`v7(Y?>p7AutQT?x(HxjIk@xaA^AP(1tL zw!lESGBzV6M`Zmvra&aT>Fs4VW*rx@(+Ree+WYG0hP>Od9?R@@1EGuLDLy%bq;~l1 zO{IMP{5jz6qPC%Br}PbJ9rsD_N{lQG>N+WnrjFVtc9nT_k0C|qD|wC2wwBQ@rikx4 zy4+cuiKrrtcy4uf#Up$KwMUh-fB8+65w?quA|>NBM8Cz)w49mH%vK*8I>1NN{5vX( z8SU^Y73b2byZL&w%IbSf6nUgK+rC5o$2~7o(P>Ncpj^@iBP~5G`@T|BUjy5RP;Ek0 z+69v7+8xr*%S0+I%?HTGW_VSb@0aj!oIe}V9Ptt-BlRz44lN67Y{t^YyJnKqeI@wC z_PU~VZ(R`_GsT*;ZS%ZQn}Y`)*|LpKe+HKQ$g9yRJ7-fgY4}_8R!{xSMU{BqQ8{Au zrZ>Kw^#WVl)9*yQSl52hvF88>hWvTmRGO2EUqry96_J?KB23A@p3D7bXZN<cD+{5K zNuyx=BT2t;)uQfn;Mt0&)minHFogkEll|ZyZV|;R^R#R{L~!Uwqq09W6^E&f(1<$2 zrkV!c2~+FETw+|*2X|@9ln}ZF(xqozCX_S8xMp1(27a|VI4ARL>{ZwbVEJ`vf&x}~ zLdai^C<ULjVfV&FuIfaE@*?a|3!ZnB6b6vAIrYk9_SlRU=F3uR;&oj|nmzAP#z%hk z*WDv>5w9#vwafV{3k~vf80CO?6#(>hMl$;P`V1;P&$b3rDRWUS4wg$h@rL%HT~J!E zgO$D~Y)lMv|M1Y!-VTyW+^U>5Zckrr^>7cR^h(`(n-sW^@Db{Nepwi=V%Xx^m(2FO z%BZDIIWzrN!A8P*-m0JH3K*JfIUKk*T?+q-cfhRj(+$41`dsv6VyajXkl%;pyT+vB zj{X#^5^;Wyo?o}mRRgxBRV4zq{>q{#`MEEFks|O(+0uZE+~?LxU@A~Q&Uxo|<mE4E zN-)$LakM#CjdTPY_-Z6#R@ZvewHW6s%J?~MVFIIkvDR7ycM0Az+@TKF#rb}ggHJlH zXH6zzzF*NXhv#DAVrJ~#9Dof4>DbtW%P%vgOG8o7C>Q;VjEsP|G=SRQj2aS=kf8pk zaQAH9rxnrgi{BODAHnHvOG5Z4&!>?ZtzE(L$9gf9?O@N}4dyj|#V|8)>904X8nO^3 z$%yq?wdf>VA4MS0eu|0T<S3}~WLg+LJMdc0=!dQfysbLN3FvJDKba9{THdQdglNwr zWpZvNq@FG$d~f?anHY||t>%%?t{z0*Z?qYAP7w&u%fqr?@hB{QH!G)n>w01HDV`?P z0cLX<6BF}{x(Zp+U2f|2tQCIzDt|Uj>q~Mm_;8rZO7arbl-wl#fb)ZhG^!2hM&k;n zd`NfAVJIJsd+S&Ct!wA;vQ`Pc8aLxGkjs@(oW5zJ$0P6X2R_MY1*M+%8+RBGS&4i9 zYMs{PVeKxi^z(}fYdnm%gBeqN)Am_k|4M~*7HnuiBB%c}zcq2VgX@}(_*OxNs{0oD zt^U~PsU!w2<^);|e#gx5e((8p+-j%EX1dia;Ym<Pu*9%X287;t85D7*BlBCv(rVjd zmuTNY$5D_Rgz&b&q#@ilhE43RSX`+O3V0lEq!^e>FbPs#p^-{Yrr0GiE<K+x{Atrg zaOqQeh=WmsZ3Ir!e23qS9Te~}cC}0#5THag+b)i!t55l#h;vOBcM4D5M7J|4B(k!< z%_mz)b<LFsG0ceN`7WKLzBTHf@-4%{>rA3nG29m0b8o-$K=4RGQQ~2|pT*B_K0>ov za13FkuQR4CApvE(j@g@It1>AB<xTz=wR-FhMgzh)9_s4fSfldu^Pym5fRWKk7!E0C z?yQ}tDebD*^;*5pv{kl>_1m~+8a@}R^U~aLpN-SKY>|1m!<UqLC0a5vH7$*)dh2oL zF2jpmhWLk@&F9a>E>4D0I6i&)gdH9AXVr6=dpK|(%5B^G)fC=tE*jK!Ooaqw<pQ4D z;Iz8$$Gmp*37z@FY(h^c5?%?GxY{+(S_D-ptjC06KKH$BOtV(XWjkSx(+zms&f*r& zt@k-E=?M+5fYt>5J|U>L?z-FWvMQT>W&A<AwqnrXlYSVZytr^~R1|i0TC;;PUw?6N z?m&nC+X;yp!{%3k;#H5|KeqjB!n`^f9PD7k3K^5d6l&8L=Ec@2Q(CKik+>ktUalK| zjJNEqLr+hCdV0#Dk`)mht;wDuE-s$BxtX4xJ~X5NGv!yu$mTBRMrG^q`(WC4qr=;Y z!dhGD=?a5~cJa}Ox-sbtKep`6$BREy2WYO%SC!X+SQP5GuH$B?TYWELHTy&)L?}9o zd#|El#QPLrLXYX$wGvzxzh)hHCEo$Z<yxmW!}4vczbzHWt#9`Ea|Sx0-|EVsm%4$R zVh58jX8nVK%2(NMy=*6rt_==|+=467%8^#=KfSM(3-3p)tufd$&SAWsaIpw`Yb-9t z!M_Ja9!H!gXjq9w=&AnaZuzUPA0$iz4T?2THTL1rUa5T#o54MYm#eZ(HQ(hmWMvRy zJdJ-$pQpLG#uzwO>j;B74EH?k8g;9ZO$MrXO*<}T!8@p|d?}T8wzH02D|2;@RJ}Y5 zB4H@I6h({Ezu=!t^s`K(1t>^@zJEMEp1+GW-cDrHul8IVtI3$OQQs7ywS)~x;_>BS z<OL7nHYR<)${Z1=Sqxr2dy4gqnj$MPR-uUvQM;Tr@XW}9F|Ay_-~n`fINAV>=p*Je z6cFNVEw4aN#F9agui)gkJbg|gHQ70Fi=XAdtZUR_^a+rmYYiQvm8NnzCgP_BAoVSb zZ!d&mBUhgtD`0S^a0rDCkfX2B$+xHLy3TeMI%RLXH2nJNKJaMqJk2Ei;S@$YGUel^ zpHn_XX_EC2NyoO-5a)k3*%lf~arUt`?&)d&v`QT(VoH(w0g8Oct*(ZTOCbHP4i_UL zus~=@cY=A!ej(lQG;e<O_ghbwj9Mkh<D(Bl@!3-pN~b?lUEh+r(fZn)oqYU2IpIxh zjSNLY!-<aeyV`BMS(c7h&V1~B4i!5aXdvd$X>g)8HZt<R&h`SO3;nIyZ_>MZ^kYFy z_Xmr0rVfmclXml|ilcxGh(Qt(5+EQHAqt8k6-RCib9bh<*-n?d4}DT;id>E$U;qT( zwEFSDlwy8L6clS<sIGntJLo?*DpfIVc6j)36>Tr2zEW#HpU~5L+~%d=Io78PcA$Fe zpB`;&^JdA(SQut9Mh)&?Wn$`M3%`!15kIs0`1jjPp>8#aUeyEUlP6aP(=43){66zz z01##8<P>thQA2j(A$?j;PEG)wpPo(z0>lasrLr<0z)0}U$S7+Yzss~MFjK(M)m2b) zBVpMj!2j#xkN`ZD;p*Yc8UB-i>w`ZcruC?APc<#uWFPtwo3Y-k)qQSVkf(xGXBc&% zV;?8)creXz(dctcnC`N3>sLAGmF=>DsM{nF^cg#x&Lp?`A{u1&3R<id&e3=zRb{lr z&C#)evbP@@s{nV2jeid6NguQ`XPT_>I*+>Q`0C9@F8c<>f=Ut3X8QFA+_&KhLTVy> zFkN0b$NX(9t6~~mD_4hWgMU)|?i~{v9b!v72qSOq2ZlTY8Mc0P0wg26f}@U|`x`{V zhUzi+=43N2G0EM1vw+(2Gt%2EV*gH=u`X<0`gaqw#>rg!7{yr16tq)E)ChKVR8#yA z)}!aGK{++)@@7=+<IIz<EYdQ}c)OPR_G|4vUaKBy+s}^jevE}#U(0&XjHOtonsQy) zP8txhOXnwR%SsYfQ!W0$u^r|)<D(*9b~<mxD=FYtb|IAuVN4z#OX&;S9IO@lb9Q%_ zHL~(?lZDiz<?x49r7|;R{9(7FHS@dDI$DElzY2%@I%N#I1q1WuTs#?a8wnSgo}U_c zxaJbwMJOE>f&~urFD9-u?&1c<dR?cIQhJU;9y+Lq4QA~_TO~bpV{n@?P(YwUwbTsh zl;7#ngPd40!Gcl#DXdx~x}OQTb%F$=veY+}3mD}TFmvm0o}Gao`ebwc_sqejm2XDT zCVc!b(9x5%$xOkglfD?v2luy}AndST<Kyr?Qqu+^&)tb0jXKMNCcu8ouK#h=PENam zFZ*5Ws*{tKl7D^r^yy+vU~e!QCO?I;nHk-1onl&*8JX3>1pTFB%kjZI{rmS}(tRDi zR|X9?nf)corWZ$o)1{+&wXQx|7BjOUzew`wUtLVSqvH0zyCpRZeC;(|qKt<5Y^COJ zGXaCl=;Jk{{vc@w<x3;hYQ6LL&GPY&3eM+vPaPN8HzvLniV?QWwkJsnyX>j~f&Jy? z_%4^%ny@2HJ)_^}AyeDqXDF=fY;lp1PqDG@9eagAh%0z5zpX;_#C{k1SdK`C?K!Pi zETyiR78U98*z&U9s`CK_p9HWoH8?o<A^cgRQE79>8~93#TUb~a&?-~-`pp}U-HH4- ziam<I4<}RRwW~RYk%NBzw2y2)#6iz`zUwwo#gYryV<E@+luDaP!C=_W;PLT{TPFu1 z*sA07y6nS=TlU|<ru*TNym{p9g4v<`i-Lku=NRXC?Ct?_=rgD3E=cPQWaNI9(sg5l zKj1D;3*P85i6L?B`#z+n`Pz7zwsC8NR%csxyW)-H!K%;5W^*6PGka7a-z~ZLqNh#j zi`6;bJ}<d;jM}X=TbHOD+20=gFm|{oK@;;Dxi!)X%XQ5DAx!~#vitTbKex*uWt}P8 zN$^kWr{$a%oeyW3E^|D`ExP-SY}Gra#%YO^Rbz%{lTILEQ|REhD7T?an@)tFi2u^G zTN;b(IjwF_8+#2DC!RsB^ziN9J#JFxm|xCsBlg8k_vo^F({7EE;0AZAaXMXKe~iDz z$B(k!L9IWDaJt?Sbt4@T_1xZdMLxgw;P34*ahU2=4LDs*B|E*AWOiRL_Udm=%HW6& zV4{8o7T^w_c5iXBicldZJE#GqNJk^TDPGod-QyWvcN{cOEG<XpBMBJsSA+}VeK<Ss zsA~(OV_z(>i|x?#o2!ztT6g6b(uKGMjjg`j?#%5()X)Bj=e8GyA{N9{uq%zAd3Dn^ zrn@$}4Hswo!}Ahc`c9~H`xt9<C(Pdjv5mr5$)iSmgVV~%);Q0Y)p?>5v3gFebDx*y z5TSSa&3l8ieS5tmDl@Joq_UfJud7a%J!yoqeCs*|H}s8%It~vGIOH|7v}RH`bUAZb zb=ZL%sJpwnoGzEzkE2876`a)-oX!M<SV6FuB<59)s80$CQ8I<6*Voo$J87mmIl>-y zd!<%$5dEE%40qjqViMw0RJZl@;Jx_Kn>`q<wfN)jv+ZGqmj-+7Gd(?mTbh@m-2P{` z)~11{P~}WPJSB>spEvKmG02Vw0%ob}%AjMaz0Xv{D~{sz()hS)^6$Lv^#IH(YDF<Z zQcB9Xf-qKWAkD5{CCg^MX?3A?v(D|6+&dqAAkaOy=}c)@ZPJN2?QedB13~kR@veJ^ zJBE1w^Hnc+=R=^ndOqDrD&h_{@^H47!G~-+0n-MYd>$)~K7SOsUMxN6EX3~~+mdLz zJ~TYI-iwvlOfwB6fANCP$Mw>SkXG1zz*k$Gk+H}PHU`8)hlhp|A4J7!^)8^?$JwV2 zK}~`E9A6TcYpwgM>bV0r<O)o9DAC7QU73UVB0d>ZuV~~#3W5nn5(nf_SrocoG<V#s zOmh!6)t|JbV8#Qk#$AU&>{&hX(Tv~KpmM+1n&$QQ8{{jK*;2o7mhDb7WSjHOGaBJ3 zd2d><a6b?l#{ZI#kO1f*PUBXsd^Nemna%(N5F9NnEvh#9Sw~mhJ$#HOz{<ZnxX9;= ztK_hCkNza={%jaqv98(wGh!B^+vag_w)KL~$ocoI-}Q%(P#kO=zstkRQ9;x3^wXP= zFjKMH-_xex^RDC7?>C0vN`d=Fgmv!NV#8iM3R>cv^Nr)oz-0Ak;5M}0T99rOZFj16 zGqp1FxXZcD#QA5USBq)x<5Oy3tE|C=T5IQb@7_UDxoCZCzUSte9;YbE6si|%AX}Y| zPUtViKm0mxXOtHmH|#Wxhxy2dWbg%?Zl{eup6d^5g1mE*=uT1RgR1}5Tee_a{0oI% z&YSkfQA1|!{4V!__;q06<PR-&1_lQ3!{t1HFl1>1lBe2V@a6dQtkUD3UH2(&Xq)s! zx0|SuVf<n3W|SP4CoX1Y;Es@y*^>H}CWT_QzU3z!Uy^+~XZLEy$mH^XBt>Sq(h!kE zo&g89?yfy8>}dR6XlqSDlC%Bc2-uV^l#SPc%)SRKNLU!Kk5lkt(ncqsquj9Bsq#;w z24wc5`bY6V@kQ(Uw|toE8(|gIYe?vZ1PQ-uph6T5t@nB$DAfYKy-iF);(4fN;Col5 zl1*sjP(+hEg@gCB#XxNV@TY)nRcH)(JogP$_qnpq%_1zv2R155@s?0OGO{BvDG3vg zqTOkANxkq7u<w{6Xaer|XuC$}uV&VLmNMKQPsttiX(x;?7^MfWMAz_TReY%&7zg`M zT&~>Z)!Cd~hfbBzWTP7_Lg(_4=Sly0(C>4q@z3WZoXK?Z3Env{pEy!)AbmX!={`m! zm&kM=cmuht1Ux#LfQw1X;Z#ct3r1$<CTHl{*=n<0qwn8eVIZJOeK^ct5~~HnR_nV4 zO~`=OQ=YR#b)wObAFxqkOYL^X2xb`~M)?FO0$emE4)BCVu^<^9Rq3x*3C~;1C(13> zBi(_ko^XjK_sbm*@S#SHLhxo42}v_n*){p@Vs+<5Z@eN7Hg?)8<DohSvmj&*JsJ}o z3vB8u9wl})Nsh9ZpM&oHm;U3NyA3T+|1~Z6c+46F9UU{7SYRJhy%Jb_c)Od?SaH^U zyFU=L)PV#91XP+z?PBZlbuh{UTgxT}j#gH_K(y8enGNh<Ki=+H(@Ka3$N*tQ07GaZ z;TUdG_~>z)o`(zKj!PG&^Oe-%4!?)1+l3DLNYBsD3>vVs%d{%&p`E&l*G`cve7vcg zw}C4+A|auY>_fv<CZl|AR$o67VTUDZKf!onZEcNg3@}u3cW-`Wyg&PMTU9h?lSzI9 z<FUg_T#a2j=!<>$jp(?1;>9E;QoU?u&NT;y@m`IUC^n-5@Iqm^;I%VpZ^Sjcndk{R z`o+O~eBf{#zH9VB;==aX;cGxu#{32)q61m`LGNh8bh34m`-4!VBK`%LbYdyp!W|fd zovY_2xwv6z4RN@+0+vSZ7D7S653SO&Ujv%m&BwMw26hvk6#0N~dqwYRMq(Q}{4PN? z9;YOQYk6kGUgEAW+OGRrkJ;35UGQXy`SQqxTVGh8vXG*vweN9@HEbj!GdGPpYU73K z2rf1@5xQ<XvGM2yF>#7rEHmPhXJ)zp<};eZ<<jvH7Aw)W=Y#k6!+^gH^rsr`W`3cI z2$PoHbfQJ{k><vdyDekVwqIYoP_@b#c7S#oe^ghGo*=;+zF<x&(;iNJ$z5U6!OO$? z6L6HYEZoiBB@EhBOz8qLb|g_#Ro7l%F6j?BN%ir$HQ=sH(}7Id7}**TNq3mguEW7E z#YV@+1+Ryg<SQOKJ4Vg{_LuOxa!^tl35(81)O+}Si$i*U?~nH+G%ZcHSH=R!*bRS1 zy}#8Y0&x4AJ@?i~O{2RrV%VC`QDh9C{^^mq15P1BFVx?%HNfWuAw6nDRJ1{}#cFM6 zKS=72be6L7dLL?dM?`_T>FJ8wxJgSQDIsBj2Jc;YD|l{vXjTahg8_y){Miwt{Gw1c zmXm|S4}n};7pn4bhse+*E@?uv2`UXTMt4ecyxS`(4*OuamF4C8lZ9=Jk-@<zcn8C- zIo%Edh}+xCy~Vb?ymcvqC15u=hWQ1WOqtm%g@=uci;|>lrH(m2Ir&%h8f>Ovz%A9C zs$q?KQdq03G%~ITX6LR>s6r_MA%m_ye>QA>)Ys9mV*AD@mq<i}ztG`VFlkfJ>jWh5 zi^}fZ|0(tXrB;8^w4ce!;L98Z>CNKZ1_~(F0pMZaoVlYcP&e@4b9T;0vQ$g1{$mpp zgM%(X)Lx#{(7lNXe9+pONvuPHr9Le!ZKaO=nZRBQGgzW)ZgP@pJUYZ|kr7)a-%LM6 zqfDc0#;)<-tK+W%FV{%spG?^;|M@K?EhU$5`|F-&^@V*rK}>OB$%9BFkcg<vAonup zEYa0j!a4VyDaew^@)zE~1xQMrKO+WDueKJN32g_C?i6d3P49hgw@kGJv_U{X<{{w| z`Y#EFxpYrK8lELFonG!znOOCUS)M}52`l%R;f?&W@hA8|W+0dwm&|0#`x^p|IM-tm z*{C9*?YRH=@qKV{LQkb@=M~)JKk1MB#9&%vNFwTc!m(^Iuj`<vO{%rH%j^|vw6mS> zjUM7eH%y3$iDjSDx_A+N!QW5^@*tPfAyuVuS&tjBK7G2D;%cO1gf|<AapsHN^<#R} z<UJt&6MtN0{y(LvOhyhs&8fu@8m8t7H5$+*=|ofl<mw#91^*-Svc?al1ENIU@JV!a zt7q5LOnh#RMGqK?13GQvIv*a>`e_2XQ-mELcSr$_f48r&a<<PFA&$%I4X%H`0`Amg zlTXBPBm@TA()qhp)DfWEdi~#r^3Lx8Y3$pj*Z=Z8H%#mrmzI~?UUSWemk4GkCGP-) zCK!HMbP&i;s+zgKLYP_%6Kg0x3GG=8efcj})Z<BLzD`|JwYmIx-C#}?a6So0FU)id zX;!`Z&ny$HM#LNE+4G&p{?YZlR=7(dJnny{4bA!hJalEBBB^38{lC<>XLp*QXIeIW zj;(o>Cg^i7*nk5JC>UC(I=)<}Wcr->GYG_k{e(H}Hbz4mHLUz&tPK&S5vTLnjk68u zzjcc{ZH}+wo;kQ|RCrWa`;gH|qhq9p{Z75J3pXE}6>EtIWz$3CEn3fdONHh0r6 z^2{&(R#saZWM(+6e*2~_e6vo>z#e;kKRO7#aXw0O?iE1ez3~LK&n0jij;9hH>iFSw zdx|@E@#N;qYZg3MAR6c!tc6FN8qbDkr(Qu@oJawSYCJr8|0>9WtAYO|HdXa58rkf| z=NfkV&6ndR4%|;H+4n{oyXd8QDu}hRK{ZCg5CI()k3|}kB%z>>N}Rd$tZk5t0DO!% zTb3TEq0pP|)faMD^hF<c<JvRrO39(Hja9)%Qq1<VeF@GmrHkaj%x913ciZu$omuUB zbT0w~LCV#-H1gs%=KISMC6BOgqnH_<(-pA|?VFXzlEAm{-6vgtofibw{?^8mP#d58 zd8~}ujZ7spArLcLdz6;#GIn?Gsd0`wQxahjL)H8IaZeDTdmVULn5$umnupc)kV0)p zN^OjfT#!A^c?-NCr*|2h!2(pH=q~d$Lc_hcrdM~Wum|#Kr>^_0BjjF;Dk&I!y+1d{ zhvgaOaU1LxgZWzIa_x;oWhF$_QsAswDPuienpVtd`S2m7%LT6N*N(AvQ*-AW(FVP7 z*+U2Kbl9%=O?Og40@g#HXJ25Mfq0rQn28_id`~(+Cb#!})&<=if=7=9@KrJEfBYY` zH&>Z?v<XCzy~5oOhDJuv@eKpA4M#@W%>vSY@cVIWG#7?FSsKxd=GxB45D6OaOHIo* zs_lRk6ZbJ;s^TOTf9r{?-DWPzX<f@}T(S5SteIi?E`C7|G`N?cZg8O-6ZRBS#d3%2 zbwg4wjpLI1KqU{FP-4d3^9$vOS(_OVP1VKUK+1E`;>qP@V}Ov`j#4WF{Hx}^0ZPzm z`S#!2BGueSo2lu?w1yJJIbld{J0iy`*Hp|l;`7v(fIm;2J6oPY%HwC;sPEsW7}6V% z+*hYa*`nl~7_@BX7XlA_z1*Z}^JGNEYn&VqEJ3xI+YjEq<3Qiy_uim(4`x$xNprwd zecLg3nW0T)H`8-=+)kG?eBPt|3}3e&t#5d^bRMi7vX!IPxKh^sc3*bUo3*3AyLi^6 z6F4Xz@2Z@Ng0BxQ_EPj3rvwzh6Fa5467xG>K6$jsm-}VSP!wL$z_Z$79u-5-mrh-G z)p(I7ptK;ldaK{lQ1LafS}4vn*WKfIND@*q`s~3&V9oMEf{`Bm-A?d+7yVWB?N4ZO zOSWt~hU4W27O`^W!A6Ra#je-o(Bz-XP~4L$_v;Y?NvzLktqj#BS7->`V)1&*gN3KW z$j9THQ_6AOTt?{WF;RMx!y?Z*d3B57qZr;cB}sLc*hvyg|4wI{hj!Z~1e5N3HNI5L z*70{!&%tmBHD7Pw?G^QtG?KtG84nro=4$LVWeKo#e}3*z;@{gKxVE}mB-<wN`a0H2 zy~ce{#3bJP0rjvZAnM;SN|fnFd)?*!loa<Z*o4{T<+c)^t7DD^+UhLGWd;{SJqt>( zlR?LaRH;L!22|?r&jR^cA?hF_#0ylAfAt&hshFr%-v-C&m+$c;)_;&c9OeMpbBgok z=4L_Me<P9wkZj6d@^SoVm<~D09Zgv{Ti>Y#UbgvnSEXUMNXm*WVfqZ6Y66@sN)sSU z1H5rpNFjWH0ceO29lH2eu>7x7{r^=JIRg||f}yeI+BezAT)<Sc6!Y`GnIF4QU<&y4 zPusSH{kKjL`_)okxDGf}CAp%K$e3#RhC<n#;@d6X`@%{7I(0z2zpT96jS~g_`JFUb zdI;3<|F_NhuPOWARrmi8w=uZ;Kl=Rt?9TqLn!oT9z@tMY?B>6Vi2#Aj97+C>$}E%7 znS-9Rc*tEF9ApxP8fLIq<IkNgWnzaBCRy0|iC-3VqP+U2pToapz_+~f#mA6eyjpwT zYu?+ai>on=#=;TZj2x(A&Sbxmg*9Ow&rO3QA+^&8cN{gc>MFyZ7d@~iAiWN=#zxwA z1?B<3e3V0Y1H`<gnN`|ENJu@8R(yXtYxLWS$yA#kx7L_rfZh=)t!KD^6xecSyAx+( z|LDYo=+^2A(WCO%FQC@g6}~+Sc0vIOJl5cJuVJ)RU(;h-t(k_TDSQrl!N5ph;Mm#L zuM8*w@<Nfb{f`6P#|G=o57xYpqJjtV=f7oe&%^>u5<w>guUzjL#LQ8!`d``A1tQ*; zabliyL!Ogy)CM5__7rX~-Z(G2s0}Qhuh*k-;&}!Xjb~siKA3oey1#RGg6Q@?g{yqW z&#PSWqbmirrYoCTv;F}Cvb$tsv4&VIkV{z})jN}xli_*8)XFX!ANIh71x#UEVv#uo zk-4?`_lrIwdWt^wd7;mJe~il+>Ud0T<kX6Riu^l<&MGYP-%Q*YkoNw0cK8Bh+rM=D zr;xf~e)u0O_?lmTeVK;=O8>GS?h|73plPc%KL={E+zFNqf4vKR{nC8-l6ac;TuD?I zg+N>ZL|WZwW?ZwsAdLRb)hd|KLC`Bc4Pac%JS9_ZnRgt#3SqxL5DAF~Sw<1F69<8q zK)cEX#U}4YeYgZ$mV&qApLRS2!H#<X5Oa#|e$`16<;sh)8}bq*=kgitT|7B`A#HhJ z95)(W-5TzJW55EP4Cp1qLNB{5ToGX07yk^ni$ApLqk64zqSJEi<M{6$G{j9_aeAFb zB511!9=9*>>c=S7u=R%Pl-IIK#lf)U+tP=^R*XjSLbJ;&kAEzBR{%`e<sz|jyR}dL zLtB$iohHXt3iWM(n`_Q?nM9JRMBeLFiE<7cGQPR{j4ThwVyet1`zCAGFjI4Q+A-~R zQj#m7ocnbIuzvi0N`MElLj8g71=dYH4=M(#1N_G{D4!EVgjHjb7XJ~2PSM39WAk28 zFSdHawR7uoJS_(!CKoIYU1b1{&AHn9TrFDnL&b+WjjHG8*>5>~o>NcH8$MNgIgp$g zr0BV=FZqxfu0;M~f!FSVTNV|y0TlJB=%?RLKz_ap4qY^p^i@HHV~!{u-xVd2-ryWG zJ>={iM*#EWcXpRutF)Xa-mHZ`ds2&e`&}31-}Jxco8K9#yj6R}-$@Qg4|?ACfAC&T zEUy@#6E+4}|67eY{*Pu7C8z$M`v1}WKh^)OQeOYx@BTlo{(l+lzmPL0=6^tC$(GOB z>T7`i>9=ImkD*;%<>d<a=w7lw!<Pi%8cxXc-dvUO!5zCowo0i+*?%c+7XNn?*rP*7 zecxS}o143p8#pqF)pGe7w@_^cP9wrJT*o=wD&qQYkQID)`2Qol{|EX1KUb5T4h@rC zs($JHI!$TcJ@)x`z{_Z(Pz$|0`E#cM#^$k_(PonpH;NxNyE}GRwIulu*K7WN%UAU` z*tNc<H1Crc4%F(~!K&w#c>T(cPh_+h2V?cvz$kKJY$y^KkWc9&u7z#ppCgxf177zd zI9P`P7r-|4o_Od}oR=5TtIvid)$7tt`dOF%9(`DY%l>^(+3Nq(8h%$Tf#KL8tqqTV zbRKXCI*w8(;Tb^6e4V2LA)k3sPPSd&sLTGX9PyNjrHUvl*`FW4%Xzn)rZMfg`i1YQ z5%l2@&6D@b6HI>w&z&a?J|CJNFMS~P>z6j=kxdx38l%k9;0w(iSqaO)3&$Z@Xo+4b zWVlQDc6XUb_R`q7#nyglNKS-<^5ervNa43Nn|a}F-mBxs!_w)-9OK)5^|tSCbgPju zEony)6mRimm1l=z*LMFe_TDloj<#zPZJgi)3l0hHf#6PpdvJFN4Z)oT5-dT3y9bBH zU4sUP;10pHahFp(@ArN)YtEcm-<oySnLp=G*Q&0nyQ=mrwfA*xnZ6XgrS2J5!(4Zu zBmDzV^P`uwM&8+uf(sGL$rf7fBBZ=7`+Dm|&Z|&fi+0uDWm$7Rl!p+m7*GqZpRm8* zs0=*F5ab|yb}Z=+KhUvvtF|y#T83hT1d=0PHE7-po~pU;DaI&k)h|J6Gu}@gEMRpl zX3ny7M;41aJkpik1oizYcZ)>QdPr>egWYgRD((Z9<<I%b2N%Q;00-w&bU4JPKLaP< zZV`0z#BXxl_deaGSF@_1a8INSbo}+t_B)3%K`~-bg<Gs9{INf>Tzg77>S|c|D7F!z z#qk9$V*sem%hZlOl--{b<nt*a+5KH?f}2e*GN=&I-v1B!aV2H+{dE0O9CrdZa>P+> zhNndKGn0+2J3|2Yv-_MZYHM910%%fLs__tgwdI1BVWatTRkD!X(tyeoSz8yYb@QDL zZ}+Y)=Jc|Zlei`}YgX^0o81}r_{c$p#PF2Cd>hvGfbUb$gOgY~d&!=M{;P)l_a%+0 zh{t&|f~^$60haxk6SkZX6vM(=+dJ2;plv1SVmkJ#e2j>bs9jX!slN!INA5GXht2S% z=8*zo7ysFw84g>SuS`E9>;^Flzk~fM+jO1h+JZ)THZpn6Kq9w{XH(MPmTHGQB6oXv z(T{6L;s?0KBz!p~OjK3Vg^i(u?NH@b)9G+|jN%hSql`MUr%N)zj*0|{L|laI^STdz z4}%yV7NCm|q_1mj)Z=M7+MX3ENU^S#9a{N^v(3UNAi)aS8MAIsh`k2SmR$qlYB|BS zxA1(Y?sXSsqlKjpFi1PPe}DNd0)nQAJnoAl(7!s`#~Z6MQy%=OV_AB9z7~NpSdN-v z?YbE#9=)teUUnFlT(MISmq<a3mdESyut<p|<ZX9TP5IGM=v}W7!|Z9_cnw-6TU> z{r(G>@p00f+Q3fWkBEZnL<-EHWvGN==0hB3p7LOP2xi6ih?3t6r*|h90m>~}n>%mQ zHQ>q)q|KWz%2JoBmh2J_rMG_;Ri)vPx^G&fw(3>I;~@v#^tqI@E}^rtJ*>MB`%n;@ zS1)b$Ue75rMx93iuRp-K4br6G;it^aRV+OVbC`9F9r?M5)a+tZB+3M9E(>s%0ZZq` zE<Kczc4k~K-cX^lLl>QjRgRm>qh|grX&I&%=0@kwCzqfwX#Hwx+F#IegPLDv>awHE z7;2XI@*S5a*Ee%I%!F9Vk5-G8%0TuW9~0c^L8}+&nq+<(k0#5*bY~vlES)bi>SYgo zhTmaR>ENz$+jNL?Z5<9&#hHVMLH?spd{6SkO-o!^7Y6Tr88OqF7gS0%ktY!ynzoF} z3&?AX`3b&&w`puyW!UsS;*+`0{76_wVQ1{jVWmHiZsoi=fW;qEEV@TQ%j|BBmgq%B zH(F7yG_a2DZX_Rn|H7M=i6r?^YQ6h>Tevefb9;^M>nIYBv2f4ks*;%{_rGTfhWrhg zSF3GjY@rM8gXdt_7h+k^Q4xP=w7Y9925YunT%Ngx<A<lBfEH=Yw0iaxflq|6!{1jV zqQ}rr0dg_HK5gZ_$QWZ4iSS)q)u(XgmInMx44l<a(C^<(PK+EvVqH)Lkw#ul$Bi0s z?>Bh7M}n9jIWlgu60L=W0!(-+wd{O6%TlJWS0B0R;+vHUx-ZE1?Nn^^N8_7E1|omE z?d#DKyA59EI{%q$f%r@vQ@bmYswclYKC^4Q9Dl61yU**+c%P4@t3_y9&GkF{B#^j0 zuD)jIX1n>!k1?#+IXtq(%ZNzYfcH=VUR#TR(|j*W{(EcUfe6gprK;HonXF2LmUIKV zdDLiU%=`DGcsqU#AN8bReUY0bJwa(na~s5BTh8*S=*Fp{@XR89?X<&yGKDq$C2jN} z*GO7@!q0R*4Pv~4+;@Hxp1<RwB2KSNDiMB{rl&_UdcXzOh1A#Y;>?3>NGa_&$nI&r z>~oV>+Ed@p7k$HOQQ3c3ZTtS+JxA!5cJ~dc-j{&9ziMunM~xqmR-<`D=)`B+9=vXf zhdzR$KB#kwp;a9DI7Y#7R!6fMYohp3zUUXr&-UWjAHhdRB0i+AoJF|L&=Ih;UV2}h zCSAlGYOPv>AF6PnF8qg=<&^}CVfeip?5D+Ywk&b8nSk`wcQnBT9^B50{&@c{>2I#m zMDa*xEJx><aqSk4_`PX)*mySY<G-Y@(^B1hoRaPeq+%<#(^^Z<%Ug$*UCV@I8OyGc zX;oN!FH2Ok^=8w6yrbigc{xvm+~(F`6T0|K-&|CHUQzg7EDEt`(Uwgyycb_QzcxS% z)431jR^nSE_PlRa)7To#c>~XO2Ps?lc(mqM2ELu9eyh`r>mMqp<S*|tm#iE_1n8SH zoiD{HT5PV*BRh;yS-pbu(n}56f&S5Angrj?kH+Ud^xgi`J5&B&nmOHO5sy`1-;8{P z305i*vfzzw<ZZ@dW1HlucvC~ny+jGf4u!k=u<!TFxnLQM#RAT>8Lg+rPaL!9QN{L( z4U0s6Wk`4K44G%r?gs+~mY09E*`+b};6OIWBo+~ax)$)D`|ZRte|Xdp9{w~;QRI)q zD;O;JAhEpClM1DlMFzy?PEb%cT$Su;(cP_YMfGnO;3>a1B#11TqY;6Z5uh6aso4MB z<+J%EZNN_??VWvpW5~@w7k_+pNC<okMN;+s*OzD%4EWH@8O$+;1~4A29-NZd1j1wK zR|I(NpyglxAzCC0@+aS!P1|bh?JRDrV@)PLDsAV7($p?l<MOD%__qSD`Hlc-a?0dZ zxNZ2jRD3EhT<8&zk@q0OVRS!gc;UV!!2I9K&*`zsrlZ4vxVfxuIW)8*iFtdZE_~l( zqx+Mjxq_ZOl5){w{@D)&*v9dGzr#d2cCCQvP7UkCk2?3ekmj@YgW1^>9=?%o?$RLa z`b|Szj-xi}^!valB70XA`4`78?K#o8@i_O9emRUz`r71$5<n&X@TFiTC!4fVy`qWD zs1~UybTk4|9DNfX$T3;J=L*ay86_3DH(OYk04pfUM|20)@i`m^3JA4?5#?gN5Op|4 z#3Nb$$oK-3)o5j-T-!_fwF52QX{leUkeMg1U%lwhb<%nKg%2w#XfPS-4v3)Er;4_@ z=eO#cH?=l9qJ}Ms(9llvKPB&$=~@p_ruNbT>4<Y}XB35Er{Wds;`f)oUc4qUzZhd0 zkSCd!s1@LKHz3%ngdA=Uj6a%DIvB8*cwsNbS1$aeRoJ6!c9`0#*9(FQq&*$CevjK) z%9+zIu&*E>Rc6s?v3Ka{k9y69z@Uc0+eQb9cc=32ES;FsnRBhp0(Hb27EW~%h$9$t zI;*;#@~t9)@>_IWbw7Ln{T>lYPWD``YjKu90X=R<N^Rwr>A0*OZ+ZD#7dT76`wx|> z%_SF<Vy|7Fg}NFCH2zUYVw=%9**8+w7xJu$csvbTwyHk-3{T|$<z!r52_HK=YJ&zt z;oJS@hm($LnZY~N)H*x$5G=RCffoaO9@o6dr09F4RLnW93Q~KjNo)mq6cN_s>wDj{ z%R5WgISiBpeI87U?{~=FX}p@h&1_3<RUpcHPwY>`#5P@wgYz=OlZhaI@RJo3#-qqD z#dqIO4aid@mbie^q$$mD&m-*Hac?-(5MDypJVO9$Vl%gBdlUR_d_><W$ji>?uCdtp zsq)|B(3@2leztS0FwgJjt4=-l7g>5oOSyC86DWeL(K<Zz7yMPM+fx@>8ny)Rg2F<a z1FGn3lP#aG#|%@S6rPl;iljfL4d{*T@=LRRaM?{ybvs(R$b%`AjY~xRdWbscPr3j* zT3=m4LMl-%(~|G@r>y9M7N(Qm0b${_*FKqVv)#cR#t-1Tlb_$_ED!tc*a`!SJCC7V z!O{(Uq#z1q8~%kw`{g!tvMlfl?Bu7h%uD|Xhx0_m3jKg7%f*$er3-p>i5pTiJ^r0a zFY&qhmDFaX5ZDNl)*S}rl#!*}Lhxr9Eb>VK)Q+q=YEri#EPFjj<ViMlW#$7E?TMCG zd0p7aT>8#~Ouf)d)YDq#zGWqDt-$H*KF6pjH^RaT94RBU@(Z#eFG4W1C4CM<tlcqp ziA+g(%kh}E^6_DEEAl;_SE1aK{Y8&Eg`J(A$=?dLGamE60)tPyKk>AyC*Dq1_E_|N zBgv#fg;wv=Wytcp6E5s3XZ~}xD*7-Id9m{KLbst!$XBJ_Gxbl`#OVUYUZ5K1RSNgo z$U&BbLu-BcqCWqu--c1UlA-3b2B0OEystJ|r4bqvv^=>@qd)rGHxAdD$`P}X(YTUe zM3MJ##=VS%0G%or&s^R-vGtXDVY2NPIGkZQ5zBst{(2p&;ZH_SSgXy+^$5qBRC?JQ z@NZ*0aM6^0@!5zMnU08O6XYGI)I+Vc^^Ni2ap=E;oQRR=vn|R5FrZBM1Q_!&e|3W3 zjahQlKyn1mhNeSeH4>+PX$IvBN9HOF65-}KUXIG<1T@x;MAhQnS=C~&G2>fO>EqZj z&z5hNby!HLc5{fw;4^;La4SG1=<tkxoq&hrkHo1FT9;;Bl!u66L#Jo{m9{4C!{BgG z-BQ2i5AvYHs!;KwlzzM<Yt2(m*_NemHg=G~{F#d1=J+{*h~IX@Uk4MBM~tYdksv3R zN-$<e&}cFw*>c$3kPy^hoZ^Q%Q5n8eW-4wjbbhH%`KEw9`9^KtoeO2bUULqb>PA-` z7aEz9^o!x%pF{PX?8O4mBNYbIOy_gqQMlG%mdx9w5!itU!E~TtwQbOTbVD0tb4$+c zDH`G_;HNX!yY90J#a48~+ej0=IWk%2jrEebXz9C|PV7pS4xD;m+$1%5yuVqur?fDF z&djt?Z<lWf53@|@DTyCr$&s-#Lk;q9Hrd1*wPQ;fIL;E){I{Bu->}fKbbx#eSUEuG zGBbceGFiJ>ngAi6Gb|mRMw^NUM6K0v;eB<mJ*_)3qhAp<_9xB`X|9&VEIJ)+Rs%Yf zZeeOSQ&#<znN@GPxVG`I9!bl~WGi%HWtdD44BaD3&mAsq(VVDaJ)oa<Yn}<69;ay# z>1FMwKh={~wp*uf*0E^*T%243&8taeCaO1XCA3YfFJD<;9%rtQoc+~h<u`<WYide# zXPDw(Rab7@-W0Yl;|o2wqRd+tBs7?lO~YQi$euFf*mRV<dAeC2@OOM45&~XxOp(vG zx3q$J7SKi}NETcrHE5qbX>JE#!WQdWYd<)YA@!dykJT-X-v!ySN2a)1@aXGk)h((b z&7oS%6rb_<(Z5|#woNC{|D@x_ddK$!o9VnnK%T8v+1??;oNLO-UFzy-Eit+CTdaWQ z66EAz-z}3LIw^9-PS+lgx;vszgMYd4mw3Zm7nD)Z=lGXZl_SA#7Uc1chAs)rwcIW4 z1UzfyBKLn^?px~=mV6C+Us8K~#Lge2B8f>MR28pz-hgmx`7_zVi`UCXDu(c*p6t7( z%gT3uWhpYp>(gn_GOBhL<a4N2VQ$0c$<|Xh(#@Kj3Vh7S$+QzIcK1gd7E(r(S?M$h z-UHx*<QxT9@ns9BW9NwDn_kVfq_S6mO$QOOhd&c;85O7h@2<(~t#9Z8$2o}adXxoX zq_TnY+qYBSRA!aIh=q1XYc0PR^3|h`J_$YJTBq*+rlW_2CIqiD*c($^ioQK_AgX60 z=TJZI{Q=R)CP8fgBI?FW(a7H({6#cNkv?-z02aRf3Ko5`EHVN)tfF@$9xxWe8-X6@ zVN%DmwJFbRvCzlr#;Z1#?e1O!&pAt2f-PX5nmoQ;vJom{|6kakKaATsxd6M{+1PZW z<3ncWL<lbhOZ#i<oGHMxl=PCGdI)oU2Bf&AY$JEK57$eAu^YkjSpz@6WZDmwT^tN- z!~({Qv=V6zVA-s<O@OkxRk`ZCYFi=mS%Bq)<ggO{Gw`!2Xn7$T#_hXmFo7ITgL&ga z3Bdqb{YDSw={v_39eX3r#G5LQm;1KoNUgFzu~>wJ4$;xmt{Dx+!b<L5b{~x;{wsz` z4m9?K=mYX=l`Zm=xJto%XP3;vifTJN>aoOk&&ahlfHI-{r!q)?Rr=rQkWYV1{iRIG z?1er2_S)Jg4_Hp`xJyC=&LYL5ttG8s0A}n_Y8ksLIv2BKx=|P%t;>B*$-ZoP)v}dQ zBs@i8j|$JMt}Aa5HI2d;794RlisJ<pvA;f!va?q%cy?syHsem+KM%?-d)iH%8+1_> zh=cRU{+n}HZ8u-1N-i*)%|y?zzPh%e^t*Hv**Pzn!vOjCqMV*BLug*g??w_<J$Kw_ z*mt44{SV3ip_)HG^MC#U!&J{K^s|;Zuxc;q^y?p<@Q5M<NR@V962IOD$cllV1Z`aV z+uHal`*vRUbgY$h4d^AYNO61Z2!Oq{-C7qmqsTp@(6mx9i)RZF3#Ws*>NYd`;8*5V zXnBD=G1}S2RljOBdsqlayIz3e{KbdO!xSn46Jo4!;5u$uK&%0SXhFoNL?7&t*tkMp z2fv8<DI;6j<Q6Kb*57-2j`s@aR{fagb@iq(Z~x|OJE|QL2Wd1cFV{HLI?b?jR<Mu3 z=?Z&k3{uaTq<D$l?f7+5M37=EDG%!h3js^%C_IN8D!~U3d=?Qd##_W6{!FQC0>|)> z4ZtDeTgWG#WC|YMQTdq!JG^RZ_a}q08dg4SH}z)<?gTWv^$(F2_zq;@^*n`QRr8;T zHzDHx<!<r<XKRYdPM_&BZ=m)Sk<#LfPuEQ^j<vQ}F1pPt0T}$%>a;I@6>ps!I)5HK zuk_UoV9@+_j#LA*oq|WfK!g;)(0lu7i9Aex@$w24fhOqIQu9?9e|C(oR`B!GS<5vK zn6$+<B40m}(cc*1!bU?rOzEfm09+5uE1@I0XY^L4OXa`vwEydO`QJLqxHMZ&^Zh2C z=wiz$Hp~4==ozAB8?RViwrS_coW__CicDBa*rk=RLc^{uP0=WBjnj1>eRie!`|^b; zt(KvtM+3x~9XY(Yt0)yfs(m*lgH;)H22TEw4>B5U34x?Y`>APzGH?c*KW4i<K-&9Q z#~i+|xA1ChRLDDZ(}F!qz^qVx*~>Y(Ik%AK@lrJbsnu}HreOj4HpxTy{S^W*!#`!b zVo>loYv><Jci#Y5Z0esUpU11OfNN1dy{zAv^9KG3TtsyFmuHc^%jJJKzWlSjxy$+I ze~&85=w1Hff(|PK_SLgrnecx7`84SFjQ-BE$bM+|i~w@H#~V-bHm!`973J{&GyQ}6 zm|*Jrg<;2u-<KL@(gK@%y3qQSxD%tMHSm;K1twZBj?)BpfPztepH&zkn^E(aZq?x^ zrHEdQ!^Bq4bj&80$hXegBzYaiacw)^IZDV{W0cV6>^f5<y1?W2c;;eqiM6j5G$-i$ zcy>OVGM@V0&uf(4IkD88leCubGyGiJ^nF{mXV7SZt#d6T5zG^ASIBG4I>Rg7^%Zzs zpJA#A6ps?N>)uBVbALukP}WLXyf^af4>gQ7GLV9#9|19N4B4ZEg`gu7$&auh<7O0O zwUGc`X9uD+zf_mJnV`E?n?m_}KSxqPrvEK_^!SDR6-8Mj<tFnL#Ua<dNb1zHm`=gx zw9Wc&u34JZ$RnqjiVY?_sYCa6enTrtkGr=&^~lB^IpPN&Zv7C=Q@yJRu`pOTL#zV$ zz_7!ZJV^54h}9u`P1@^$a@=r57#>AiZe*pAb89~B@BPEc&(*j1_<qw+#yQ3E`n2gP zOby?Pnbg+l#0Ooaf|4!#x#5afV;ehDdNcQi!@cEl{n>%EA*f-=8;M8DlwYk^FUOec zM%yNbCiv+Ex`PO|tP<dgJ2Le9*U|=wRmUMC+i9RNW*%Ai4kLlehju~dI1qCEU%{v} zB#VkLaz_H`>8H#08U60IS8m)Ht7po#Po`E_piO_x;O=O4G2$1i)spC~Ee?Kve$)z1 z`2W2N!920&!c{Ug*1#!VId}=UZm|KWhs$;rA-%h~%(HA0FDH@P1j5%Bc-Vw<vB9u( zQPZJ^;tq<0HbXC`NI)<aC7lytJh0JWy!+SOH|`jF>*T`YYr419f;_Aunk0nzj7?_R zlrT+q0XCspyLIec0+V!~GwJYDESOuQKoz_Gu^yT~`QX#e%`BHIa{0D~DErgei7dPR zinh-<?_i<`->#zlKE;69V@%K+0XkcePac<*h;y?8Rf+cV@oxS2WFuQql#4y>!vUa% zPGM#qDEs@_fB>^Y-rLdkg1F?9xfr{L<}2bcVGOb5-OL#n`&wYmcZgZ1;4rA-^Y}Kq z2!G%Btep;c#GuMS?qg={UAgW&T*a0OlI?uj-BKrG7jo&W^BiU35ryEmAd9T;#6q|L zAI%>g^|@cbCC86#OEY9lm6sNxV$5@dwsoOP7=l>6Zmj}+%SjId{hEf=o{G4X{FO$l zq3P0@5TD50NYoor8|1!o&~2|PvI8F%W=BzJF6fAy1Gl4pC>Mlfl@1!?g(CR3HfxRy zzVpEJl;q!t_tXiVL|`_6Sqxt)rZTT`Z^S<|Rn~2KUqO=+KdE4O_JDsgqgP#%Hy1Am zA&_wyC-QZG&-X)yv@4vIT_GrM3$+Q1`S(E-Npsu>Gc2NPe!~MS?a2mR9^hAkykwCO z%N;X&iYSQXFjR56t<+pu=HALX#qC~iox;2N-R?u9H$OetZobh;Ym)0drFXT<@g4eQ z96zIeHRSNIkUm)Catqk-9L}x&d~?@%N8yLrVGuRyM(gp6sa~atKprNqzSq>om%%3I z9;u7F-*VM~`y#y#6s0R!X9qPf{rncq>^13Hxvxe85;`;8KMx*04t0dAEUHZRx9w-U z3&R_Cu2&1vU{%GHvXYE#ukp4@wbvTkr{r~e=}5XA)Rl5i3~TGmFZ>x<H2B0k5R6ee zXW8U$6!sED<lgf0m6q>vb^ls^J+W(<iUmsQ=id1$xH`xj_Ly89QfgwrKYgZ|Ze~B^ zyJ^mBWc$<!+*{wV*1HKrPmX)aJBbmw3r7=p`vp^Wv<>9INTejO<m3TvH=6zNo}a$Y zUw%{sfro~A5<8~hQlHQt<xLgwDn|wNnXPF|N$Wv-8uscho-dZatU?rTf+w~?3Sn6B z+6O2+nS&&p2e;L47Cu~8{9#*_xOmG?*0WlsKDR8>f!cZ4Mc3YZkcme(YKACY6&xM= zG?Mg<Dz48Z%Hz!8k!I#A`_<7r`+8XtR8}~*IUOuWZkm^yl3IPbLQISsc=}kDtX7s; zH5tdc7!O=p5lZzamI_^z7PX3SU5tj9pk$MYp=77IQ+vEfT5R4ft{oI~A;I<t7&Y=d zUp(*UqWxBDBZ9LcfVi0!Fq^O7$!RDs>PX*QV@c6`>E^d%GfwX=b^Ufz^~BEosC>z_ z=4X93Bj;4Q;_d=}AR~;pEQ4(ldT>jFko4zFSFoe~)(y>Mz<bj64Ep(`Ea}vZTyJPz z@5pCDPl{Ep0#n1SV*0ua=#XPCMHE);-y;>d#(UhCy$4!Kb*CuqQixoe*}_1~%gkFu ziO0_=()l4Yy|qV<NB0SxgDA?0Bm#68M3QgW>iQbF^w8L0jiyri3lu*-fHncQs<v}w zu@^KONi;Kpl|M})B*vI*()Ji$g2c*R+EVJ?lmzNR_(H`umn1EkGOlT|jIz!}fgke( zo4~blb3Q7u{)R^`S*|0$$5?W!hiO~I$$S3K4wN-1JB9hR5T&^JoEUfA>#3@CbrmPE z>>tk)KtdiJ`qMM4ZrRjx^;?T`YUes#etwzNYw4N`!b2_WNzSzO*{{`vPc{2Hv})SJ z%G_cFz>TyAXRnxNdx(Fh@Pl$7kHvj72&n3Y_R@934rS&M!#DZ$k@L^1&ioay)&Oyf z+^_D4-GIznz5iNhuv9q7a6BKpqPl=k821SUPT{d~gHh-0dfUZn3b7R)1JHTcuGi5} zg3(oJy^x+k6y_HdzO}VP4LSP+WrX|viSN8wiPuimDraTShZvGW`S#zFa=!Q_jxoAC zRWdD@s}ocDG#_ljxmohggbpIIYNs{=$23CYZbb0orvj-^+XeAjk?Z!L$ny1H(kNw@ zmV|a$KiN(47yjF$5_2Q6Yk?t|nx7=799aB%WThj$-5EVVLJp(;(P5e*PcY3FVC+1_ zM*AjP!pda3<XMrGminGT&-ZU2lMF)D*3-2qOtD2Wc`tZ&4Q|zwcCHzTf*DsLZBwNN zHF*f;Y%OjS*_)dJehGxF^bn>ERfHYRa9>ItYK_!8N%jN@goyoKQ9Nr<!lru53E#2& z8o@s@IvOM(Sqt~$V>g0~ExAe2bmjUI=$?y6%HYxWA!k&L_vy%sC>!?yv|$bv_Jj6X z<q5d8P<Gsu*75@|2&KRpLvSXMU!%`SqHFMY@x}3kw4eX3%<VX(ZY_nO!9Xy+;Wcso zo86EN(fZ4!c>?|d!uq!dkY4W#+8UQC&HXyFkJzkVc4gLrBv(r34_Z`QcLuR;H&!Py z3mz|HV<R`b>x-E^!YICk=8TCC^0K`P#D<Y+_hm4W>N)Nl)89{DytD7g)(}Hwx&$3# z?|MFNyiAJxnYqlkLYUeSfB#}4T7XxPysNZeg1-Kj%f@*>ZT6aQx}6tF_5fC$A%e^D z*8>b*+hzSZHz-UCtIjF$j6Si`Wn*^SZbT6N^N|)GjuW~yV9`D@{Sx)@(J{>T^KkK( z!1;nh03+v=GD<q6q}VUVVF|&Si1BLsgm&#Sn#q)1!QeBWwFZI119e<3rr&$Ecn2>x zJFspYG476e^Qo9TsEpP8WV27PWSu>uNAal7<Yp~mHFo=xpZiK_@Jg@Q;dD%psPqg? zG&yFQcVkX41RfdGirjvmc{ms_hgXKI5Tv^W5XV;o-hwm1utgo{Cw}wEk_3slS~_g< zx9+(!b(w0R?{EX86)V!dx_*4+%So$@C*rdK0ZxfDM=yKtjN>CwhNKj8bjan?Z{M81 z0uiL|H*{+h(W<Hx=G=kKwfk-t6opc97Nws4ZDy`-JJJ4=-bJBb;plpOGTD%=)<JSW z3NinKPFeOO+hgQ=5lw+r_v!0|NoPNkQbN=nkORv06Bgdt@AOz!?{5eB^#(o9Q+D7| z!`Yt)!F?VOx*%Hb2^(wm;_nAJo`VHs(K_P^_O(9c8j5oqrMAB=sMogrb%_+Yu{Rs` zfzdy`^!q<c6hM#8{vb|)<4t=@^s`U#Zm5cGUvFsy)n};Qe%Jq@{(uDq;mcVhZ1lk4 zqE$z7>HKje+()63Vkob*mB-ZA@X+G4#W>$y#pFm3nC2nQ;x@zaG<2EIXMU?~QR!PN zr!MwgH<i6GM|)(!wx)%@2tO1(Tq*9S$Br^*)2r+p&0|BfEzXuuVvDS9>CP-7T4^vN zT&rB{n_>jo?09nyxsT~V;xS{Vy4kkURYB9){lO-XX*XoHbiKRrwa{`p(bvs-^V4w= zio+b+1R|w0wb8{)_{C(_^JoMl!Tn|}OdW1wQ;dy86C4dg9;w;ZjGFUqCY0F+92Rfl z?E2hpz6Xu6dU`E?+VP<dl=T{nAgM}Sc5__-KIF^`iHEw}ZXN}!|9mmX?C9n;rH-D5 zvm+Ls9pZcv+mQDC@>53Idf^*Ta;Z`2(qQHfWR9dzJl%75`I)or(fY^Y2-Z8J2EZ#$ z*?Hg`fI<J%riPo#g8(QLgkuNA)g3W7b{nh$eq2lK(EK+fQeAsNsS<ZG`2IOtO?4&A z>BvT49`l*18l#f@{h%uHIimSXYf7m@qzOkT!{J$k^ljvmv9)}}0hS7QwW^Y_JYJgz z&c0rUTru5ZeL6I`eqYP&z@aJh;1mx%^KK>9ISz}iW%{!jX*D-6as>8f+{$#}1V8=q z4NgaV)0|Ak%4^vkgX!I8Z*;DJfq}a3wKGO3U+!{!z3iP1qk*n4%YDNerk&tTt-ku< zof!kEkKZutZ3(cD#+)uzTjAL+g|(=}HAj7SZwk$w`(Yqo2bn>)5UgU4OQ)1Zr+jEB zM{WA{3x;jKNh^2i4w)ipIMb<GLX6~LPSgC6E&w-jth7+nm_|h!^^j#Vg}aeag*C0( z9@*)(EYbS42;AZd`@(jlRb^tN;N#nMS^KMVnG8nF)f?5|HVlnS5B$;oeJgJFJ4!R` zBoRW@BX=t|ev#UjS~>H0g0_R`G~vl9<!CbhK0cf?oEs%M!qUC({cqMFPT@vc7aS&< ztf~`CZahaQqyWb;+AvO6d=!)ek~<5Wlt|84eEInK6AZ?)oGNDRgBR#gXnE%O44wQx zLMV-_6V+&W!--?h7{Ty&MAa@Y-nR7A4!h)KWzvB&DR=B=DCQID7hX^B-i33~XTSlD za%)02j?a)o?&3OG5xA^-nC6?1Jq|6~P(kfK&TS&fqyC?W7P;D)^z7NVPH%g8frt#i zjwi{hkD{YeAR6{}bZ236+~(cp2!Fju-@C*m1|0X`{CAkm|KJGy|Jkk_?<K2j%$gj9 zkp+%|<-Z{j&0NjBmKNP$E}+(tw*KEX1$J2rVk?4Dc)6gD1&;rLu0+#(FE3>p<Risd z!5XHXYd$<^6@f9~W8|8q4z4@{L#Uu&lUD@jNV%iUd(X|(DU51qGOCw0hX7z>;JZMH zp3``ZqsY!$m8GdlW6p_jA;1UIGSnmqz;K9{yq{0<;QY6{`oD0G|Ml)asEEVvD%&jn z#us^%L^CxfIQ`q&lwDq4fmDja=FegrRV59}k%u*lf60P$%c<WPH|?bjk&e>=>Goy0 zexGkS{cJy;3Q~Rovo-=@ue<C%@pl(9(=q6okGu~-<t*G2M%R0m!Bz{okQq!=DK~<d zg+{)og;f6gUI%=e*5EP!-C}1>`wyuAuEYjl8YK@J1k{e6jmSG^K-sLt^~8ZMX=;+I z10XS@xI}Ov>UXufl7TNygEouFBn5CFG3+CZ1}^`$qtm@Nu2_r7DIrOcGZ{=(LT$^r z!|(_4(0VuIRa=39B3Iu|x<|6#_4?+dVwj6TUl)CVw?2guYyxk6x~igjh(}We<aUEu ztDNFaAIQ*624iF&?Z#x9%vIPM|MPH1_fxuBvZ%Y`^~QsZRcd_?-od2oX`7&Y3+3H` zwc_dm7xFueGyyECpM7F7Q{Y$F<wJ&UWDKF6)=5nZ5KzZv{Qb4;BO|Do@bFxG!cv@I z^QRCXA$++HD^pzCSJfmIp8MPROr3XUR(`D7b$K;HWUKIBLp$@AOTLj|#iQvj!43*6 z{Ro_`M#I{P0@!UJR^c;Q^l(YaY{Ld_`u3=oAGaixj`EK#E4Uv^HFRt?B%jQ_ayqF* z1P@G<`&`(4a`X^WF&y+0f@{C5Q_jfr^PhMFxttzTeb5WXA_|K%NN)exBD6TlUcR}G z&CuyRg;jE|usrj`+>bruMIfnoSYXQw=YODEbuvgeAZ<OPTBbrOf><!IX&sDtm$*^N zOla5Db^?UNebajvVCDs)Zf$~R5O5+B`!tUWdV95mo^`%s0+RgH2N!rAT0cE%6+27+ zXkgy4ySczhtEI(0$Y-h|bk2U6?UybxvdyZu)zU)7uo(^W7Q7n^^CbAK`zYwIW@Oht zAl<QF?%jSWK0O63NKAw`R%a5^*v65=Y|u`^zdTtuz_Yh175U64)H**TdMVybWbYii z!hf;k3*MB^OYai#)$>~j+fKAEni}b$)FN{6;=B*5M;8!IZuT-Lv+6QTMyA?pf4U?U zMD6I=+z<77-~x_^c|V-}JzY7>9Wbanuqp5h_B*Nb+(RkQO4M|xu1^5+!UR>}&bzBK zPa<Rgx^dx8SqsyOkpKrn@aAa(aq6upl0~QnD2spmIX?qwxd@Rjvvvt0Nf3OD%fNET z+bzgOd+`meV%mO+k%?ynU2L;f4VrkF35PRNWMONH>OUC5&c|N=ZI7IIp@`PMvsx0w zbb|vDAvOHY_S7`!Csmsa5e4PR^?1yr@50rjkI`zE9{gCf*eH>oZ@F@j&=>!4A|_E_ zE9}>5>GDycLYp{qviMr!Q0@Gt;Pj=GIx;CXO?csusOJ7DqK^VH=rLHX%o<t6fs@@t zVc$5rsw-(4$;x8HcblRdI#%>%;dZ!yH7IhrD$1x%g-7Bp(k5trm6|V;O`3~EFoAUG zd2Nt%=JUoD!+|uPm-1E3dARv`W-R-SIXL9lk7f|u@sf@nalTqz$fZXd*EPr^EVVji zRS*I(s84OuwMCxpxzYS`YG4C_Iy3y3pPFmwFDcC~DKE7sA{z^sk%fznVZ~#D0^UZs z`emyhUaUg<iujutoaanhsr5@6Q|8fg5c6W94|MVU!|NZ_#c1K_M6#!=V}{!k2AC3X zX$y6vex%QU2|g&D1{pdvB|!eizDqM{tX$mT0jkKcrpV@_NZg%6`KoUI>>0rYy6q!V z)##b_JPyw##E7(lC+qyYHG}+_KWIc-Lv~sgzcS<TQ-IVTLGyhCAABcE8vg!j>FUWF zG*UA1ZJD8>X_=I+dc1`e(`F_@F<|DN=4~z*%Z^Gp0yh_*4~NP-@qCE!<DSlF!HwGS z1;<!KC8r?!=ICo_$bERHAby(8FQX#xd`n3xQ!JoiwQDEj9*4nGIa+1ez-(D%p>W9( z039pnB$@u+fyW@yQrnk>w*mP0I)-gIUQ&n|hcJMU5-~vc>$z~(eSPo@P2C8n2V|Q* zu215zAoZVR#R63Ww_~!6l2dCdC4V&GjzeKUu7)%tw)-<tRy5y(WnW&<h#*|Y&9+GM z@qtysZ8o+@=G}zNhF$PulE){DOZWB~AD7_RLWMGE7gSv${l@qkI|7`qIR*)*Rl<7N zqUv?q(uxwJx+ObakrsY;o$U-d)!S!(mHpyAsmD`o0nOlm%As!t>U_~3vj3E=c)60B z7-`Ko+n&HyB>aAR*sdi<6_<aVX-sgg!X0okC$$L(S@mfm8+J%fDOFq;otv;adO>|O z2C$Y>HsS={D2bj*1Pi*DaQ>RZ)#GMC2VupteB7m0Zg$GnMn;j%qHi^x$|p+dLO}~K zBgd=0FWYHxdK;RUj7#T&5=Yi&$K)V(1>bCs@#RVONX}yTnzVV#Esz*f{chd^=xM^& zp8UZwy~>Aoo1nOLy~}N>=Htb#esag(d<CJ?-PiG2c~4!j2;4-Gkeb>B`hcuGT|&pv zJa<1%j<=QU%8hO>vb^GX)TA?0_BU(q{C^3SZmwS~P|EbS-F%$i7G-J}G!QwMvfNuL z5IsAchjid@(yZm-`d4aN$b+?(g^W)lQN8a!%Y(6|W74(%)%8`FwZGmwh!~u59T?L$ z;@ahpF3<1ADqRi&(Jd3tz9`O-wDg>D0*bAgZ$H(Lm8ie?+G}1B_lnz4Xs{U3(5zSq z6u&G2@;Q&MO@L!)i6@8&hVyw9Ywb)QZ+p{bm4W=@eE5lpK)05ra9BzeagZ~uzA01- zevHvGZ<z({W0_$bQ*YMPD-X>#-v!3IQzgO1(*n~LNQ3Hyt;DjYo0w@Ib$SXRm>Thh z0)ERXy<SDsHv9n$liEQhR6CRLU*(v;8@8yfg6&0+&;thKLF;yt%=jGp@4O6mb2sMX zVjuGB>hhyMz`$kwP+HP<+icswQ}VgMf2}?@#0ltk$hA60o9k9Tbm#&-Ky3r~v;1u* zhwnOodNltL*HeBG^!EB+Cd_on+D8N0m?ciKI6kI&^V`R#^wHU=at)n2#W^S~%3vLw zJkL|-FD51AzYG%F3$x=md*PWyR)Ltyufr#P2|TZN2R}FIY^z7w0JT`lx&M54>p+-n zrQoozJN`Cu5KrH>yJumNCNa^%Ud}ylB3Q%C5w+^AJao$4QI~`#P@q8GNmr-om)-On z5uo{64>L}zC>XRsFhS=o(0G6vJCjN_%qVYr>4F24nE82=tH2)R1ZaFXqhq!r%FoK) z59F->xt0fTY)FHD4D6rDI3Q46J7RuGwV~S%C?mK^pS<hd^2~b5zoch?xB%KDEx>Os zudz}|{6%z!kh23f_yYn`xL8uWZt2o%5F|`&fSsLVtP@dM{T|#d!Dt!Z_>ZWUP8)6} zQKRx>4i1HNz2+B-H^clGT^{uq?pGMkmO@7OQR{z!iv8cBFaJv<@BbSuGcJ*X6zG6j zCNB|xE&Y=`z|~ksGZ)CWK;n+_5&LKesCfbuhxr%@yy+i()UR1H`-*h2K<;OWaiNj0 zW-d9v=mI+7jW`ZaH)e@EsAMr=cQ+jH3;D4nkAoQ7zj4H%|93<Ic2xQ71AsZB{}Q04 zg~`XBV}7Pn<X?j+-0_};`P1azv0(p)<DdTj$9Nvv3cE)jU;^TNv?ujl*)vuA$LNwd zn<$fSVV;W2vl#n_mj1svBaFM=BL5EHr{q8oQK4@Td<8VsO+0XZq2_7(n7|KKJ2l?I zfp(P|8MIzR1HJBu4jen1PX%)ovxKSkmAF(dl4Ap*m&w%l0hslSxK#LXAX1D9o}Ot5 zuq?&w7>TPsbsT(eitxOff$>#bfXCjrSw_H-%mk3>fpRMj{E0%DHHl(JZJj@f>x*0m z${s^UpYLW9)8YqAj|hI<AVX;2yV{(g$(lDrA<OP7weZ>Z3a9-TaAJKPwMKX12^%&; zii*N%K*S2<b<Ns$P+)P3@WRKt2+|U$)@j**KpS)JWFd(Vwf<2*P?&@))tIbTjlCc2 zHf0;TC>FQ7zn14%T{h^Q;f3B&QKko%<uO``lxZtlG*BY(11q<=$V-$LUAzlgu45IH zS^`)8R=R|yeDsyT7huRMN;8P2sp?y*sbr)lq-~Ol=3t}K!1(#p6OV|-2|6Ap6<`@= zI>t|Hitqbq;rUX%w8>YReLqpmCZ`qeL%ePM=N}o(mQUhJRFQsHvbx|ax8gT=r#xxy zEZ=$YMMCQar?8nvTc0-c*y*+GiaH&;>9tHQ4UdNVM8r;t_KICK3*TGBV*mW-p}JSz z*7SG1*?_SK9)9B~4zrWhmHJ!&)aTj9DR~cUCpe4GK7TP(2p@C(K1Q%33EKKodj8tL z)E2#9n3P&S$bo=ElL*xlNeXHu=7^YTWpsBvb?ggyZ9^asT7XQAjRU=)oz$-@(?p}j zE`)E4W|)}iLLn8cHmDO?Y%zCqdI1WI@b$c$_f*X_LawMsBTZnboGh*W$`#-Dack6( zk&k+G?R_??1V!M-W{o|c2#x+y2L0A$IvlLQ{kbFI&Qk#t&{?fk!ws@6o`g`SaZ5^y zg~EaQn?}O8-L3#1*1<KnHl!Y}eKnh;sjr*yv_Hv3C{mLOd#3i7cP@t{8wKkRbTaFl zA-Zm-gh}P_GKQJdp)!xcZ#*Hv4<z3W^sEoj(!0%SogbjZrCoQt`G-2~?Ly3XLR=P6 z7W~fbwMrV7k6o!)NBWr=jTU&}jYk>YK)ib!g;xofMUMiiC}PRz39<RZK{=F?V(!^s zY47TpPCz!W!0|MfsAh_1tQ7q;Ds`G-P=#GmbxF3|AnFP6+RHb0HY~1{SSo*OX1G;X zCOA_-x$H8Q1R2w9v3kHVJ6a1!#iB1)u6HpfoE6@`>eBax7&zaIT-*)AqdR{($|&>Z z$v>J)N~pJD4s^niAQSYymT~aOF&dtLk!3ZzNg0+{G=evoRw_;xCr=mE<L$LImgmUW z_=1P$+kKxNBkm%2*xgFFq_GP2U%u&${6;MJ`c0OVlpGT@Jt3^!tnlE5KN;^fa=kKs zl)6?ZXKEJL7KZDs=Jb&{Cx>OQD6!1-BU=b^_$zWQw+~WcuyvG)Md7QAaOecDrlstK zF9qq5*#nW-NbRWrGvDc`6|YqsmD@-{BH@lXv(F{ie&4CAdVe}(;Uk+gc6)AmIS+HW zjh4;rx5}wa#>DrzQs?MMe<H24$QAYl8ZKWng?AOr;UfGs({<>0Tu<(hl)tgSlK3pv zJ(hu6ycapiQrx-jT+R7<{;G1ae|Uf+xUWRVoI)gRbAhYQiqC)D>NLDa+SCin^@{M# z2B8JpupGNe_~G_JFVXbYf%`(YNI!}iT+Lx@Qp&AXABCBk8jsgioqpqrO{0@N^P76x z<A!e_R?u}%2yC%|mjc!53;2l#q_=O|62W$Y>udAj!_G7aLBLRtuv}|rmUh6Yx1${V z;q(^aqHR)H9~dhAg(k?8HhtTL`=u&_NsVWmmZOxyFI2lSK0Bz>DQc^a)UCQz;^LNt zzP{BS-1mvF(1*U764Wk0_V-tM>t`Tj3SnwfQx8k=^L7cfPpx!@e7MU1p`#KL^QR-P zz)=Yoc<eA#XEI@nS(jFT!Qu*|r0ukTBhnwN0;%r4ogZ51!a+h}aCJyoFNZWrby37P zNU~LQ_S`XNq{8=6{D=8l)Ci`^gD#T{TbLzKjF$|P5njZ81KGLCVUJbOjmKx1_xGuV zWs)?wskI$eX`rXilPHk)3IB9tnBYxd;z(fbM^s5p+{MdKNrMdN9+@IZ_lCT&Ihr6P z%u^tnI6n3Yf7QZ#QS7#Gqq!G;P4U(`+M2QajN8)tD_eu5A@=l?NFEVxmPlzB!|32S zy1kJrcZnPkE^ZdG@yqC{3zoqu5MtI>^j2BDpdXeyK92tOpFTNB6>XZF-eQ#1*RAXj zE(7l7J&kZ{hj4L(o43gNqC41@aM?BsCu!Zk>h%nvHc8|Zmdx+IR>n;sgK)z0RIEt| z3t~O?BsmBx=U1hW-|LGfw^e#!r`Nb2qJS>%uOE{N@?j5-m9>jKXi6?;;s<A~`=xFX zb51&n9ER<b^qPA3vH1ElHNStC$t_>p?RdXr-DGR&g+9%Fh88;pL>+jxU7nD0McN<Y zkz_<COpEw>xE6IbFU|VelwpAo;Y@pm7dQgn@dnUg)v^(l>Ja<&sSHM_tDbzfinQNf zM+aF=aGJi9o`t${b48#>Mq#NSsCb0LZ|6(+5AY7PJ!BOsA?XyY*)2%mJ9CX7O1cya z((Mn|B_Q#%jCklLx(WfMAMo*uTeyfH*AAEXFES!IA!dpYkJ;soRtDKe7x~9vR!a4i zRuVq1y{<0(($%z*m5SU`_R&Qc5dk`siTUt0{WzqaJThvg7B%X{*k)Nkd2P$cOp?9! z!k;tmuV#PY*yvdcMjjWWuFC|;#$H>@+@P&AzrJS)5?4*H;lI=C?uKU={xTlY1Oib@ z%YG177l=(SK&MP`QRBs?9+n;s+svL0Nq_Cq9R8-xRvsbiP$0*kVOW;umk-T*8M5(_ z(?Ww$u-4JtMWwyy+qZ6hp_-}DFOc*I7C$-I?=SIVDc2b^Q;SYk8Q+{@Se?vv8}(Ja zE@f!3ny$le&>(25e2CfO>ysr3h^FahB?sz`HFzIjzO|W@PY5d0EBE{RS^2GqjzcMv z1wwIXHu?;0gfGOaep%e1Rbridh}%#k?TA?ub>4rq`}*t-dxe+!MaP=HnUYNtyOxRi zO|aYUB)u-W@#bE7nfFzxOm$1|>s#8M-~~tw-ORVR^yIc%eet}r{g;`sPS<VT$Ozhv zoHuQE!MY`LB0?Tpdp&0KxlKJ+U?T`mxq3%NoY3Kv!Z(Q`caKDo%0mPauWf8<KYC9I zpoke1&6u@d-wstwd^klC-dJmR05uMvuR09d%a_~O7dUL^G-D&Ad3@(A1|_0FSjQIB zelw2FIImvqB=~NRX0ANzcid5V7ApDWnQ`Fyi3_M_QPa!cZ}r;t2rF%pqw*(pvQOlY zUcs^AbWD4EnoH1YxF#uqXF@FWH?9NnfDc?|<1!H7baY;hB6F!QiP>(kTS}ltPqA<c zr?-}8E@OSH!Tz!O&U*%E#x^R!F1GSPwPtf}wJ8$n>K|FQWL(z%U`J`QDN>S)tUG1` zSc47N5NE7sx6J=c7V%#)5O&VaFJcXTL0kuX`u$C{{Gy?{mi#NLN@fovZOMf|9ynO# zg8eZsJ<ea9=K{J@Xh`Iq%M8ytoGJg+J$1Ee;Z<n8#BH{(y>7d1SzR_O?rHrSpq?`- zU94>GxJp&K__NmXG~y7qRkR{-cX4`Z;{Xo4Uy_NT3C#g&N_u8+K43~r=wi>^dX+ov z|D@cz(%etPf%kvThqrt1fGNqPhb@_Z`#_@NtROlG8{SRCF_q6&QOR$2w6?U5+e-2U zo^pbn`X?d4nFKq!<5PqIEsm2-U|)DU-_i#DNCmQHfW3y_KB%-S&a#uI09GwVm(0fp z=#Q5~<8L8&%@)9^`<K4YI3KX?=KW`jfeq*uw{#Q#*%A(K&i=V#E`L7ojK~-AK#sXj zpe7~1^)a9kYr@@-TUYsZK>luVyQC%moV0ZgBuJ@;2Xyx=6L8|YzVr7F%W1%UHVA=L zkwO4vG70*hH~VQwBbyU;&Wp7at%a>zqa~VZ%6a-S#p+qIO6||te=cZI;Vo`SLx99O zA8sl#-L-s@V-lSjL(AXsmPT7sPOHpyfU21HpK==~VTv#!>#5bL7dOqgh`&xtYLBp< zO_1_T9=Lh_TvMRVaATf^hDM_xB9M$D^52O*{!8QK|CHGmcZB7?i0H|&jbI7bD~L&I z#bHyeaFf0=pWj7g9;XU*&>f82$ggXXCicN(e(tK|Upd70ZP_PR^Uz{jVyy`b-Ma3} zuUqP6+}iGIf@&#ZNQb-V7j4`65o|k;(%RpBzHVSizSEtDRtsXUM3b;#Z;^piLg2=a zu(mYClb5?%FSq8ynFdWKPneciR{5IdHTjN?P@g^vd3O%;Li`nHmrmxf?U$MJIK4+x zCsw{H0xdP`uHj}?d7P#84@MPiz>%4Darm0rUUy^rQ@NvT`2ypFj&#eXV>~m$^1s<( zTf~Decqt3<{QrXeyn78x)G(asvg#Ns?YKx89FI#8{+s!R0HS2cJQzs9YA!KD)tr_` z{-V;i6i4jPrkdtVt$W6w)xD+gDWL9K^$Yu15wkKkw8B6EG}MrrSH{SDu7>p{3xjP} zUTr1wnO_rx84v&NuuNqIH|dcFu@&CMe<c5I;Zz((aw%X?=kd#NVQq#YWoSqcwft@Q zS1DK^6uTV`hA>s4U6;GrvE;VpXfsDY%2qdIO6C9lhIWw1+*jq^7e<^p<xKHULMhH| z3wBRWc_&{>5s(Xd*I56_+PY{<n;;>Kziu^_l~Kb}1ND!I3$F%j+mhP)6{woHJR%j7 zN{Go}dU58e1#qG=OCx!;q!)jFtB=2J>-!Y2fl;WDl=O3-2TVP=HnX6A-+viboc0oN zm!qv7y5L;iRdB@XxPK!I`nQ#ts94N)aJcg`bNz@6GuyHwz9)5MvFiT1Qpo?kI#sW7 zctplM9F9w_W!6Z<-*EYH5#GDCo9gWit-oC>^*okgd}+sCM_jdA^!8`qK|;y_M)8mM zz3mr^^z5UIY;gYAyq`5nQZ13w&J9~`YH4S@D24BeyfBv@@oOO8_j6O9`nQHQBE-LV zKzgLIZX4M%eHiIO&|w0`(^eOQ=OadpTL;51(VI`SA+yaZUbnm8h05&miFKaALRX2l z(<IleKKfm+(G+yo8U>FCFM@Z!ly+{9NsmR04QLr~szo552T`0a&0oue6mc~LN0lpW zWYUC)bA!@67YoX}^cx*7)j`hFWKW-@T6vnSOlf4D<okf6zDE?^?`@wp`myWG;Q_}0 zt{>Q|6T7WViU9u31X#hdYW-7h!caIt7-MUP_S>%+;5rIbb3r@muP8|ygx;W5ybIcv z>dO#FXr&dM*FBwHYK_ULtMS}>2+2@{7LRW=a0opeM$H(RVTF@i#0=|nKtXk%ABJ8c z_ydKDb>CNslvWE$zpp^{u^CPsWt&9@p&|^4z3|7TyVw(6?;?GN;A)FspdVi6Uc<)E zg{oq|)Ku|S@5AR#(uPs(?Skvs;1I)%E)8DF6=sezl^0sMVfjgL^sS<or)kB(mxkUv z2Xa6po!tXB;~cuBGD?Ndk)HSqS<q0=cCVrrTF25T<oNu0`2wwXu4_QeUgYv%`DI~~ z$i;*eUVsCFQ9*1IGMlI`WXo!02|PPNIUh2Uq$R%Y-g%4lJou+iF45G<nZDP$WW)R3 zo)=|(#)C`a%0=TqXr1CnW$ue;CIw|JG+oRzS!LnEBOusY-$f2(ini+|dT7~D$PZ>I z&rOY{?ajQ*(7oSXawd|PLjSV9^;5k)z}B#8_SEJD>BH$k?OBdgJBG160S}9g>4FSF z2&)L5kzpIh<xxEg?ODBf{s&=Oy(*7E>cP%n$uO4k%vo8=Aw$8@k0xd!k#;(oRyCBi z_d{-Tm)URF+^j?q!5x{lF9K~qW3GP|gVsf~wT11$SW6B6S~K3x<4^5u``%w}ZlaSm zN*-`~WLA!h##oTD6tUZ$4^}6R4(@8UzfTIbV_#TiwTG#$8)me+87kEmkaE0GngqM# zdP~12K%(-zBb4v21X6qW+uV=QwTKJ<UzJ^VR8viq4<MjOFVYcFia_W^x>OOQNR^Is z2t_&}BoskGnuvmcB=p{tUP2HAq*v(>={<A;p>4iz&z`gU$L=}%{&{of+<V`fncv*G zGv~c~y{19JyFh|=jUgx`XVs@O9+K(#a`Nl>{d%@f9(j0+(zO>!!3skzke2y0DM&+h zTdGEciT;Lh_m$N9e`A>+-zX>H$F6vQ(FRPCe;40*Ia8@P?`;>7g{QoQ7p*47qaZGO z2oB2Qn3Ki;N^g%t(Z2R=!(`eJYDLM-X&{2|RW)|%Y#mf1zFj<meEU(P5qn$<Xq*1B zVkxI(o@{y5eZ6z=Wn}B~RE(2$lw<~#Kda5N8swkDKHY|e%-k^N0q8=Uman6e*NLcj z6%F9y&>u|E9p|=l4e!BD7X&1DsS5OrCw`jil%)j^%=O{ot@<-F!{jF7pUzvu(>-@B zsj~3acIINieli&G?epKaS;a)wx^Tliyr*oPdqfZ%j|g(v{kGc!;Z>vn^z^(3sGYE| z&;P#QbH~rl)lO!%EC>iw)&Lq<Xqepe9ec*xGY|rd2Qx^(c-{B+twQft1w(Nnvz%Ct zzB1;A*I=wgN~VVN-$t|Qt(){?HN3mVdyQEan`kArJxwWT1F}N4r4|$<L@qb=fTn|D zm6@h-6xi?AcR365PFbDnH#h+!%5J>ef3~e>N0icV;Y~Q*M}Q|zjck+SmV1LQ+wQCx zK1Q_EtTNS?ZQ-^~)8CMM^P*q>XQu9)h=0^+R%fXmdbMH`%llxi+kC*EV!`^}ga|N+ zcf1-a`zO$kuA54sCO}u?4*yZYd1QA1TkkCqScqZkd}tN-{V+=7=TAtCY%WmVm17Iu zhvGKc_SVGl=sT?PA(Lp*GTQb(b;>iH(d55~(g4zm&bsdTWQz7Ijd$b$jyN3nVlxkG zpL*Y>nK3Ox`{Va~G7G5`dDD}Lvq@BKdBHno{Ze+6Z;2IOF*ngcU2RE2lZneW*=Aq* z{d7G=v#NSrqyY8W#<Gge6Cxqc&s}QU4;d}TJd;Rv#7{i3MaBQR?XC4{3`A5fHcK=u zj3_ou5g4aI3_sQL`jrY2gtcWOmxm*pTI2dDjE$K=YawC>y9hUh>6J>uN!>2VEo0j; zQ~Uq2AX3@A5YTQ51>^@6R2B-R)LJkX0X=XG#`}x(kxN5eM)!Et*~Nz};2}c3KMeu* zxYy%C*#So3-z}f>g!Q((K<q~@?HH!i;%g`{BQt9jeKw{Sksa>u&YAua)nYWrs}AOY z(;4<=4G>Jb=j*k49-XF<2Qp|r9S#qClX#|_jl%zGxtl*RsRXbzBi*pD5`ttvn`K)0 zX^fC!s=-AJF46ONo^BG>6sUc;@M(!3aG?5Z(qG<EsZWWu+ClZWO9pSXGn8=SB#6j^ zhRsSt$bVw8405J}jfbr*8E$cADCpn=K*sn2NR4>Tk1+~7A#;U*D(-5x37xN3794nY zS83J;0v=HvTc5k}*}FVPoR%o!id9Y)<{&O7%`5Qx=x3{^NF|s-X$wIUMb(@#*-3hR za7O*J{1%kc=*~(vd;lDJ5YJ@0++1yKl94^T<h$F-1mIineXHWr`Z8U9reK~c9_^e% z8*Bqwq@(xJyZ#PK?O|<1+BH)YO<(Yyu%d)|4{z-I@JGCBz*rC|I&4ITZGvK$y;pD= z{w=OR(VvR*c2H0Vq2G4^en?4+)W&uhzI3;$9h{P={rS&DLH7O4Xv1{M4U5vvEMsUy z?=B?Ol$1HtgUa%Flynb$vjbXoGUd4VA?674_b@hEh8zR%v(j00+_3NHdum7WPz5v~ z_#{*LU>RO5_yQWlM0kTjUc|dD_a6bSJ0Hp!#uXC~m<U$4He^4tj25PMh<fOwtv&Y6 zB|~$5B@g81_Rxy9xJS#?#{Dn{$=KIAb?j%hISL;)`E%Oo8IZqY;u`D`?5a;49jm<( zHhR_`yxOt;I}E_cv^B--D||`HN<I}P3Wq5zb?yhr4|%~4&ZNbM#O>w6?oK{ikRJzs z2i*en&e+JE?v#K+md|2G9O2D7up|BTn85|F@NI*WUyI_6uYT5=nwm^<WIj3Qx<H+| z7|c>%kOi&ZM-RNz?DP8UpBMnG|2?B5&i>4XXdED9iERbv9d%qxTRk;jK6O(H7R(R8 zCcIeqvj5@&G!o;RI?tP6*&sGXSsNS=avpB`QBM>Gq8(0$&m#}Z6Q}t}XA+SFS$(mn zkQ2p;>tepxd7%@W#pHtgXyb>E6F(Tsu2dVAwy1vHOki?yaRaKEjFr!x0bJw~x-=%6 z0}(r)_JR9&e%)`el)z5$Zl6O1vo}E}igN3El1St0B<#`l!-t-LqPnlLGeh?i;=$mO zTYIoK*OPmJnh8Tzqqk~EJhU&)r2~{Cl`w$^M1rP#F~Fl-${z1A$<3&yTlX%q4T0T( z4ngWZoh;Smo>9bb`Ot!+Z+EQU*9UiJ*C%55#{A#{-I2|cwmmQJ3Zh=7q(W=9Thu46 z(>7hi=H$=Ax9brq>E34MgWsxcLYDQNlFB+xx2CLMNByJ~RQ9zf|B9>jO&gVT0&21- z34!=4MeybHSTeW4(E3xCpuq0R!TJ_oJ2jRxK$!k*79A2$suL@_tUGEL!rUf)n&4hB zC+%>(2V&Qm3<bTH@Lqg)Lpn4lZ*1@*MXxjI2-S4CjkaI8&TDcQt&&SlvDx1<KaHpj zy<L5?@EZr=Ts(^k1>ejME$%9(x$gDY3uB_y&rc5ud{+@ol_84EUIcxM2}kcIZ=O_A zAN0tSijv1g0<z4L*TR#<!=&k<d5;9sKNIjIoN<2og_KD947g2z(LYXti@5#>TH5%~ zH&oa3f-s>@FUR{`cn@`nq{zw-;uJKWfad^t?m*|gpXN&V0G~Q@h$JVifUgqipJGsK zvb0crtAZhNv*lC5H%gJrZF%7Y4XhvHzx3{R4KlZ}6D|!jZ0rh@S>b{_t!3xWc>#N^ zH-#yMV#uGK=T`RK>M{C(-O|$~N(?dOS;_@KL_nu0lF@d+#`5<X#GV07)T2jsNVGuR z8&-G^+BGpsSZYYEH~6|h_|1cEpUT5^LFrbgR7+O|>WMdcmm}?GPd%0;eMeg9vgRnA zF|2s8t$XiEehBeVa<a931}NoAM~A5{6sFP~HlMk<R2~f~lb2Et_lg>@Jy@ofj*0kv zjE~wiHF)jb_)H&(U2mUy@9Vrg>%0uwnSmByXRDu{c{*3#K~}u_zWTez5FFzSwXi?0 zwcwNx_dV5LcQ}4t#U}^jS$%K`cK@J)CNtUy(zTgl>szq;wzz6YJbQLJea7M(7TB83 z)G$YUV-@L~C0P_Wm6$mPt<gwM4VtKzOtEQ>5`VAq-uj%oU7W9aYKTn%{mJKCK2hi8 zhQ({~pv9=_k(f%<f+b4FlzRQR|5#1yFR6yg2tq&VdG!Q(c-~#irr8Azp5d_Mcj+Tf z@2UK^QF?i|NZP7;S_zJR1T=q{y{+Vv0sP5$Z$VE_O)bv>uSHEwtLw%8hX~Q&pcyIP zQssDS`^xAEB|wFk^AQ6t867w5_Ls*;4o1#^+d^d$=3m`m@3@zGax`vo{PQed7oatj ze-qpee%c@S$Tf;nkLdMN;%o`Y-<&ItISG|XU5?m!lRiD?c;B&Di^91Xq{*LTZOf&S z+d5|!)YM6)TfS8+tPW+OE*sDou_flzzJ{~v&W2y5mwl>SVcrNJj@W`$=H)Gf!>?mR zncFXYU3R}Sk9H@2sSubi-qw`)^#bLsF<-HVA>W;=M)ukb1PaF9y1Kqr918Ll;fgNV zpBS~(8RKvP0e***!msy2#$*9qORm)(srqg`femWC^v6_BG<59uc^Gvmr~<%#{vHE_ z!+(5dE0Csc?ttNSKSpT`V_568@GfZ?;N7>Y^rnKHQTaEeeZ?NZ(>XS04&WR2DLbz} zTZ|lY!VG#QU5E4IO8h&8Hi6>WNRbr|cu7d`@7<ojNY^J298TTB(c<DXb+&i*lxoYp z{^FViTD%_6W)G`y3e5nAX3SRAS5Btw*~ZX=Y{zXuQbK%ee&<`PZlKyKmzQXLxs4C( zq;UfpWg5FexdHA{gq-yIbF7o*K;ym%>PUGqu;2BMmYw@|-?5(1Y5YXlPQ2lB7$zej zh(WC`KYwsRAY+~SO*T{B0`TMh$HV!3vTk3T|5}6J_syx-pLbsA3y~60p{VLP+&5Zf zACVG86eXhmzSmD1olYshYDdUZ08~WvSrEM643x{d1%lJqAE%;ouU>x_lBS8^h$YvF zq?$Rgt5KnFW1&!d9Kc>#QQoK$9c5r#iNYx*h182C*_pAH+`Dm_ox)a6_*nVPWKB}& z_VZYea?<N%;sd9JbvEh!;&XVAzpnT|0<*n+@WREhtt{2;bSA5Kt7+?l+VDx#-6O_z z`}U+N^Kxr>dfT)hT2HH8&zft8H@4;pn$2a#A4P-oRMci_OLN9YX)~X(V0<ZbpTGY3 zimhs=T3I5(=WQCSRwbdPld_Mp8=rkycBpMQ$r5uvV7p|1gr>=@I&{jT%p)$PvOy`b z%L;x?dTj;_<M$4pg?przkT@fxMeaod%_%u)>+o2fnP+;6-^OUnN~QYBQ`7sEY~s4g zbH0OL&vjZ9k~IIyl*=wARHLc-RXJtMogl5!nl*{cKimwFR!FkTzjB=r$%?m0VpM<N z9alMFtatwHWA=ox_Voj=hIXMKTm_}7B-$6T^D`5cIAK0(nM-IXgf8nan;f+c999fi zP4p+-b={(P*1n*)j<i)v3H%dl9t&joYjE(0^-hP3qr|SXB3p7W1jV<|I?0xaxv&du z!44f%jgC8&-XbA=mp}WK;^OP3Z&VuW%i#46*0nGH;|gU56t@Nm)$BR;OboO@vbRaa zb}CGL`F$*ap+a66mNZFKE8n&KEsoi~D%kx(l03k|%0$O@e`m`i4c<Z9EE@Lyb)*8W zygdGkTLaRtp3SCKxc3-h?lC`)<)70{7P2&Zn37(n3NjPvUF$MVee_}$UfLHpOLrA? z=ea4W-YlcpQ;xtLR41E>-kGaLZ#J0B(eF0i$j<m8`d2StXo6hpTVbQJ9pxaTf3#Jy zbl&bv<(ynm$rLVvi9C09v+iehA|jzM-Z|XLzsrCkPGgtBc5m>^Z&dPUX7dZ<5nGlx zE7Kdf?Fv{gllT=s`&9?TwGSyRj0|mDoE|jniSl_9vU2gpH~*H*E5pa=Ov=8W-pX-S z6c(`1sp$zz?pqHM32ELkBj$<2K5TeC)@x*gx@m(zR>Ub&@%F~A1{k;iM&?>d&B;9O z+Qs^fsMjt{Fc*o9<1>FOW}1apYoKlgyhT~pXqgKu%ymPDhe#`pBz`cbd>)~3_bDYw zw!t%PR`Q&KFp99hyQqAr>5^Z~)kz4JT7crVj&H#gUqlci`*F^`OMXHFVkZ7Oh@8bp zG96MeFJo&a1Si&#e0u5k04$rWRr>r^@@YGuoY4tq>^7PwjKX;02E5V(KIhTn-YJAt z?8RmWg%7SDjE{GUT^(MicGmQb?Hy`&W=DT)ve&}2S|hSMtqT(eQT?8lG{QDqZU8=p z;UdPYNfHncd)c)BFTF4nN4_M2LjR<iI)OKIYLY(m2^8{%1giqW+8Xo<5qmn7)Bv+4 z(Z97Ah>T)CPtA&Jotw7Z$B%5}Piq~cK0xbjUEXmL4nGhPkZ-h;H+%kV-+`XIoIw0a zR?fGi*x_aNdSz=NV%CNM71K$58_Z@iF)r!!qYYD`44#a2QY|hbX%GJ{+)4t7eCLG) z3wWHGUtPXdu50!dlL06*Ds)j3fEq)%X;H!tpOB9*L7&IkMq)wKs|h=LY1HI^7yc8Z zMAGU001=4|F^kzxXwfYWa?|lY8<GH{&LahEY^s%K$^D}z6ti^?Xb&1WKC^D8Ca$uY zx{e)}llcNUA-MN2yLncijUv1sOhN*r;3*ovCavJ5s6F=#=C&`eagH5p5sW7_GQQwn z(<`K4V5y(s)LxFLv+E>Ih^l8Br-*SQidcqci|CX0D9B2zJeI6af2*<tQRW*8kk*wN zhE{fQZtC1CQjg5{t}kqmJw3Isg1_?+g6aT`O2Q^{OBdjKQalD_6{SLer;dJHvP`WD zMZ1)BRw&WiPu*Q+JvEztT2an>_e|7HSvMj@7ks@y)-7*J|BS9vtEaN^E0+|ZCqFY0 zn5Id6wE|9HI1&dX1xqFDprBY8lRck<{!+`==Ee%1F2{3k9ti4e3)bCJ%zyYEZ!iYe zGb+l_jakD6rt3#K<Kre}4NC4FZp|ZsdU51YvGtx_6_q9zm7%-Wih_#8hk?y&d!e;; z=Hd(SV>^Fl6zVGET9-(vqBQkQVix&J2ktcsOxl7rn|2>xd%glhtgaQTrH9n>CE2NW zw+S<y@B;#31IFFyXzl%$9F*-9hCeasrEWA<YD%|PsJyMaxBS`tRu<#h#i2RX>==nX z{mT(2%HK}@TZE}Gq?;*e0Zk`gpd<v#U0otsbY~j_bNuNU8GYKF$;rv*)>sNLZdCz6 zwhvrHpW+M%U|`tzw!zr47_FQt_3gavNCCzyf{3=y<awB`o>=osFO_2?%~Ohv$j=<m zJ6}_>@&6;~;5co#a$5KV1p2g*_`Gp5NP%3rYz$>nkS@YEe{-~iT3AoFNn3~azGSTS zJQZE2vE}hr#Cd8kWCp9@O0Zi3>xhVsK1|3hjgF4~9G3=<j@In?x*79-6WB3l=OEe3 zJ*?^tmWW4X8abkH67=VbxfY{mfk5bxssxuobWRReyhg6U0SIXNb+dXOWw?k4WhLu1 zLwQ5T<ng(xbGM>3@2st@IhetYH%3x`7GHOKBhwV`-W+hYFptWI@xp_+(DBM@HI#TJ zt|U!9`rykmQE_NOm07ije8!1|PtsaUG<|MSktX#mYvj=5I`?~B_Z_jIr!S7w)Y9~e zjrxxpJ5mN13cy@B<oFC!_-j>;tkbSw=nlS$Yv$2cqX{%V_Z!D0ZBjcu1H-_8<D{w< z^ODS!?DDic4UGqX|M7N=E51jhSe<bG9TIp?HiMe3A2;<^Vh9$@Wx#YgwoW;;IY}^t ze-W24y8;`5e--!R+gqjn>Q(!{5^Unod)Fq2QOk3!BT#W_v<n>`0QS64%zlm7-5bkN zncX1z5c&5Zh2VtW54pIL9MjSi1MwPc`Dw0C_Ka@U_T@OV5}j2_Ei`pv_B;CdiJ0Ke zFI_MbA<`r?BeEYIWpJgn=ag#rQL8?Z4nA1AyB6|{;Q6ORc0w8&29nb;IvSeC%;E|( zG)bRC|2yHW#z8~#a<NfvqxX%jQ!p1-PWur~=}MKS8hY8Y7j*K!LgC>d9xG&1bTfyY zQA(P0_%8ZKEko5x9=tB{9|RRuaTlI;#vuMJ|5c~ET#}&r=K)-fni*?9|J@O||GPaP zE@)~JJCaHJ2XAEk;i>SOvt)Gnli6;>C8kY#h;d+GV3oTUpAooaTw6`8#=5t+_t3!W zO#p3M?agInQquSQwc?5j`TbG+@ydMydXr2w71#*?0ATV{f8}TI<>BGz=?C!hcq8n? z3FK6D@$vF-_4lw)@h8OdaR0;O@Y>H&*51bve*@q@<QD^qNCU;BjYK45MPy_pq=5ev kL~79x+y5cp;pO1!1peOzenoW5;ROKC)pgY>RBR*u1FBO?7ytkO literal 0 HcmV?d00001 diff --git a/static/css/bootstrap-responsive.css b/static/css/bootstrap-responsive.css new file mode 100644 index 0000000000..0bc6de916b --- /dev/null +++ b/static/css/bootstrap-responsive.css @@ -0,0 +1,686 @@ +/*! + * Bootstrap Responsive v2.0.2 + * + * Copyright 2012 Twitter, Inc + * Licensed under the Apache License v2.0 + * http://www.apache.org/licenses/LICENSE-2.0 + * + * Designed and built with all the love in the world @twitter by @mdo and @fat. + */ +.clearfix { + *zoom: 1; +} +.clearfix:before, +.clearfix:after { + display: table; + content: ""; +} +.clearfix:after { + clear: both; +} +.hide-text { + overflow: hidden; + text-indent: 100%; + white-space: nowrap; +} +.input-block-level { + display: block; + width: 100%; + min-height: 28px; + /* Make inputs at least the height of their button counterpart */ + + /* Makes inputs behave like true block-level elements */ + + -webkit-box-sizing: border-box; + -moz-box-sizing: border-box; + -ms-box-sizing: border-box; + box-sizing: border-box; +} +.hidden { + display: none; + visibility: hidden; +} +.visible-phone { + display: none; +} +.visible-tablet { + display: none; +} +.visible-desktop { + display: block; +} +.hidden-phone { + display: block; +} +.hidden-tablet { + display: block; +} +.hidden-desktop { + display: none; +} +@media (max-width: 767px) { + .visible-phone { + display: block; + } + .hidden-phone { + display: none; + } + .hidden-desktop { + display: block; + } + .visible-desktop { + display: none; + } +} +@media (min-width: 768px) and (max-width: 979px) { + .visible-tablet { + display: block; + } + .hidden-tablet { + display: none; + } + .hidden-desktop { + display: block; + } + .visible-desktop { + display: none; + } +} +@media (max-width: 480px) { + .nav-collapse { + -webkit-transform: translate3d(0, 0, 0); + } + .page-header h1 small { + display: block; + line-height: 18px; + } + input[type="checkbox"], + input[type="radio"] { + border: 1px solid #ccc; + } + .form-horizontal .control-group > label { + float: none; + width: auto; + padding-top: 0; + text-align: left; + } + .form-horizontal .controls { + margin-left: 0; + } + .form-horizontal .control-list { + padding-top: 0; + } + .form-horizontal .form-actions { + padding-left: 10px; + padding-right: 10px; + } + .modal { + position: absolute; + top: 10px; + left: 10px; + right: 10px; + width: auto; + margin: 0; + } + .modal.fade.in { + top: auto; + } + .modal-header .close { + padding: 10px; + margin: -10px; + } + .carousel-caption { + position: static; + } +} +@media (max-width: 767px) { + body { + padding-left: 20px; + padding-right: 20px; + } + .navbar-fixed-top { + margin-left: -20px; + margin-right: -20px; + } + .container { + width: auto; + } + .row-fluid { + width: 100%; + } + .row { + margin-left: 0; + } + .row > [class*="span"], + .row-fluid > [class*="span"] { + float: none; + display: block; + width: auto; + margin: 0; + } + .thumbnails [class*="span"] { + width: auto; + } + input[class*="span"], + select[class*="span"], + textarea[class*="span"], + .uneditable-input { + display: block; + width: 100%; + min-height: 28px; + /* Make inputs at least the height of their button counterpart */ + + /* Makes inputs behave like true block-level elements */ + + -webkit-box-sizing: border-box; + -moz-box-sizing: border-box; + -ms-box-sizing: border-box; + box-sizing: border-box; + } + .input-prepend input[class*="span"], + .input-append input[class*="span"] { + width: auto; + } +} +@media (min-width: 768px) and (max-width: 979px) { + .row { + margin-left: -20px; + *zoom: 1; + } + .row:before, + .row:after { + display: table; + content: ""; + } + .row:after { + clear: both; + } + [class*="span"] { + float: left; + margin-left: 20px; + } + .container, + .navbar-fixed-top .container, + .navbar-fixed-bottom .container { + width: 724px; + } + .span12 { + width: 724px; + } + .span11 { + width: 662px; + } + .span10 { + width: 600px; + } + .span9 { + width: 538px; + } + .span8 { + width: 476px; + } + .span7 { + width: 414px; + } + .span6 { + width: 352px; + } + .span5 { + width: 290px; + } + .span4 { + width: 228px; + } + .span3 { + width: 166px; + } + .span2 { + width: 104px; + } + .span1 { + width: 42px; + } + .offset12 { + margin-left: 764px; + } + .offset11 { + margin-left: 702px; + } + .offset10 { + margin-left: 640px; + } + .offset9 { + margin-left: 578px; + } + .offset8 { + margin-left: 516px; + } + .offset7 { + margin-left: 454px; + } + .offset6 { + margin-left: 392px; + } + .offset5 { + margin-left: 330px; + } + .offset4 { + margin-left: 268px; + } + .offset3 { + margin-left: 206px; + } + .offset2 { + margin-left: 144px; + } + .offset1 { + margin-left: 82px; + } + .row-fluid { + width: 100%; + *zoom: 1; + } + .row-fluid:before, + .row-fluid:after { + display: table; + content: ""; + } + .row-fluid:after { + clear: both; + } + .row-fluid > [class*="span"] { + float: left; + margin-left: 2.762430939%; + } + .row-fluid > [class*="span"]:first-child { + margin-left: 0; + } + .row-fluid > .span12 { + width: 99.999999993%; + } + .row-fluid > .span11 { + width: 91.436464082%; + } + .row-fluid > .span10 { + width: 82.87292817100001%; + } + .row-fluid > .span9 { + width: 74.30939226%; + } + .row-fluid > .span8 { + width: 65.74585634900001%; + } + .row-fluid > .span7 { + width: 57.182320438000005%; + } + .row-fluid > .span6 { + width: 48.618784527%; + } + .row-fluid > .span5 { + width: 40.055248616%; + } + .row-fluid > .span4 { + width: 31.491712705%; + } + .row-fluid > .span3 { + width: 22.928176794%; + } + .row-fluid > .span2 { + width: 14.364640883%; + } + .row-fluid > .span1 { + width: 5.801104972%; + } + input, + textarea, + .uneditable-input { + margin-left: 0; + } + input.span12, textarea.span12, .uneditable-input.span12 { + width: 714px; + } + input.span11, textarea.span11, .uneditable-input.span11 { + width: 652px; + } + input.span10, textarea.span10, .uneditable-input.span10 { + width: 590px; + } + input.span9, textarea.span9, .uneditable-input.span9 { + width: 528px; + } + input.span8, textarea.span8, .uneditable-input.span8 { + width: 466px; + } + input.span7, textarea.span7, .uneditable-input.span7 { + width: 404px; + } + input.span6, textarea.span6, .uneditable-input.span6 { + width: 342px; + } + input.span5, textarea.span5, .uneditable-input.span5 { + width: 280px; + } + input.span4, textarea.span4, .uneditable-input.span4 { + width: 218px; + } + input.span3, textarea.span3, .uneditable-input.span3 { + width: 156px; + } + input.span2, textarea.span2, .uneditable-input.span2 { + width: 94px; + } + input.span1, textarea.span1, .uneditable-input.span1 { + width: 32px; + } +} +@media (max-width: 979px) { + body { + padding-top: 0; + } + .navbar-fixed-top { + position: static; + margin-bottom: 18px; + } + .navbar-fixed-top .navbar-inner { + padding: 5px; + } + .navbar .container { + width: auto; + padding: 0; + } + .navbar .brand { + padding-left: 10px; + padding-right: 10px; + margin: 0 0 0 -5px; + } + .navbar .nav-collapse { + clear: left; + } + .navbar .nav { + float: none; + margin: 0 0 9px; + } + .navbar .nav > li { + float: none; + } + .navbar .nav > li > a { + margin-bottom: 2px; + } + .navbar .nav > .divider-vertical { + display: none; + } + .navbar .nav .nav-header { + color: #999999; + text-shadow: none; + } + .navbar .nav > li > a, + .navbar .dropdown-menu a { + padding: 6px 15px; + font-weight: bold; + color: #999999; + -webkit-border-radius: 3px; + -moz-border-radius: 3px; + border-radius: 3px; + } + .navbar .dropdown-menu li + li a { + margin-bottom: 2px; + } + .navbar .nav > li > a:hover, + .navbar .dropdown-menu a:hover { + background-color: #222222; + } + .navbar .dropdown-menu { + position: static; + top: auto; + left: auto; + float: none; + display: block; + max-width: none; + margin: 0 15px; + padding: 0; + background-color: transparent; + border: none; + -webkit-border-radius: 0; + -moz-border-radius: 0; + border-radius: 0; + -webkit-box-shadow: none; + -moz-box-shadow: none; + box-shadow: none; + } + .navbar .dropdown-menu:before, + .navbar .dropdown-menu:after { + display: none; + } + .navbar .dropdown-menu .divider { + display: none; + } + .navbar-form, + .navbar-search { + float: none; + padding: 9px 15px; + margin: 9px 0; + border-top: 1px solid #222222; + border-bottom: 1px solid #222222; + -webkit-box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.1), 0 1px 0 rgba(255, 255, 255, 0.1); + -moz-box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.1), 0 1px 0 rgba(255, 255, 255, 0.1); + box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.1), 0 1px 0 rgba(255, 255, 255, 0.1); + } + .navbar .nav.pull-right { + float: none; + margin-left: 0; + } + .navbar-static .navbar-inner { + padding-left: 10px; + padding-right: 10px; + } + .btn-navbar { + display: block; + } + .nav-collapse { + overflow: hidden; + height: 0; + } +} +@media (min-width: 980px) { + .nav-collapse.collapse { + height: auto !important; + overflow: visible !important; + } +} +@media (min-width: 1200px) { + .row { + margin-left: -30px; + *zoom: 1; + } + .row:before, + .row:after { + display: table; + content: ""; + } + .row:after { + clear: both; + } + [class*="span"] { + float: left; + margin-left: 30px; + } + .container, + .navbar-fixed-top .container, + .navbar-fixed-bottom .container { + width: 1170px; + } + .span12 { + width: 1170px; + } + .span11 { + width: 1070px; + } + .span10 { + width: 970px; + } + .span9 { + width: 870px; + } + .span8 { + width: 770px; + } + .span7 { + width: 670px; + } + .span6 { + width: 570px; + } + .span5 { + width: 470px; + } + .span4 { + width: 370px; + } + .span3 { + width: 270px; + } + .span2 { + width: 170px; + } + .span1 { + width: 70px; + } + .offset12 { + margin-left: 1230px; + } + .offset11 { + margin-left: 1130px; + } + .offset10 { + margin-left: 1030px; + } + .offset9 { + margin-left: 930px; + } + .offset8 { + margin-left: 830px; + } + .offset7 { + margin-left: 730px; + } + .offset6 { + margin-left: 630px; + } + .offset5 { + margin-left: 530px; + } + .offset4 { + margin-left: 430px; + } + .offset3 { + margin-left: 330px; + } + .offset2 { + margin-left: 230px; + } + .offset1 { + margin-left: 130px; + } + .row-fluid { + width: 100%; + *zoom: 1; + } + .row-fluid:before, + .row-fluid:after { + display: table; + content: ""; + } + .row-fluid:after { + clear: both; + } + .row-fluid > [class*="span"] { + float: left; + margin-left: 2.564102564%; + } + .row-fluid > [class*="span"]:first-child { + margin-left: 0; + } + .row-fluid > .span12 { + width: 100%; + } + .row-fluid > .span11 { + width: 91.45299145300001%; + } + .row-fluid > .span10 { + width: 82.905982906%; + } + .row-fluid > .span9 { + width: 74.358974359%; + } + .row-fluid > .span8 { + width: 65.81196581200001%; + } + .row-fluid > .span7 { + width: 57.264957265%; + } + .row-fluid > .span6 { + width: 48.717948718%; + } + .row-fluid > .span5 { + width: 40.170940171000005%; + } + .row-fluid > .span4 { + width: 31.623931624%; + } + .row-fluid > .span3 { + width: 23.076923077%; + } + .row-fluid > .span2 { + width: 14.529914530000001%; + } + .row-fluid > .span1 { + width: 5.982905983%; + } + input, + textarea, + .uneditable-input { + margin-left: 0; + } + input.span12, textarea.span12, .uneditable-input.span12 { + width: 1160px; + } + input.span11, textarea.span11, .uneditable-input.span11 { + width: 1060px; + } + input.span10, textarea.span10, .uneditable-input.span10 { + width: 960px; + } + input.span9, textarea.span9, .uneditable-input.span9 { + width: 860px; + } + input.span8, textarea.span8, .uneditable-input.span8 { + width: 760px; + } + input.span7, textarea.span7, .uneditable-input.span7 { + width: 660px; + } + input.span6, textarea.span6, .uneditable-input.span6 { + width: 560px; + } + input.span5, textarea.span5, .uneditable-input.span5 { + width: 460px; + } + input.span4, textarea.span4, .uneditable-input.span4 { + width: 360px; + } + input.span3, textarea.span3, .uneditable-input.span3 { + width: 260px; + } + input.span2, textarea.span2, .uneditable-input.span2 { + width: 160px; + } + input.span1, textarea.span1, .uneditable-input.span1 { + width: 60px; + } + .thumbnails { + margin-left: -30px; + } + .thumbnails > li { + margin-left: 30px; + } +} diff --git a/static/bootstrap.css b/static/css/bootstrap.css similarity index 99% rename from static/bootstrap.css rename to static/css/bootstrap.css index 495188af7f..dee87331f3 100644 --- a/static/bootstrap.css +++ b/static/css/bootstrap.css @@ -1395,7 +1395,7 @@ table .span24 { height: 14px; line-height: 14px; vertical-align: text-top; - background-image: url("../img/glyphicons-halflings.png"); + background-image: url("/static/img/glyphicons-halflings.png"); background-position: 14px 14px; background-repeat: no-repeat; *margin-right: .3em; @@ -1405,7 +1405,7 @@ table .span24 { *margin-left: 0; } .icon-white { - background-image: url("../img/glyphicons-halflings-white.png"); + background-image: url("/static/img/glyphicons-halflings-white.png"); } .icon-glass { background-position: 0 0; diff --git a/static/glyphicons-halflings-white.png b/static/glyphicons-halflings-white.png deleted file mode 100644 index a20760bfde58d1c92cee95116059fba03c68d689..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 4352 zcmd6r_dnEu|G?izMxtxU%uI5!l8nr<BF?zWUS(u;&WdwZC0F)1B-!J<$%*WB$U3Xi z$ta3LaXK6#>)ZF&&*%FGe4jtO*5mbhJzhV&et11z&&^B?xH$MZ007{+ZK!Jj01(PQ zJBFS4pH$0DefCd1HM@h*JNkcsi%oOXzj>qsEle$eQ7ApHL(XYdn5Y$Lk_3-J9p9d) zFeVfl3J47_g1XaoDXWsnBp9ZzZ74CI9RN-Nw{>+8A&#rBpZgc9WX2H3Ssv6doZP?t zS!g}lGvW1<9%?dj_G_x}3WUMN(8(x{a6_pd0yiUsf^67GGS50uSB*ORe5x6}qAf1z z@Q;2y4G{Lb?f21p)uTpChN&4q%^blZ2IsusUOhk)pe0<chGtjyTP-b6%vl?4F2xqG zOU>yxPD6oHKXWSj<y;3B&r^tK>v8&2pMdnegiQUtoXt1U0MmWAWu2&>3j$eb^qKNV z_(`JQZP&mXLT@U%-2rPy!7r|*Y1oAdlarltaUyq+yq^|d{B9_>t@Rd#@_KW9w_6P$ z^Dv8(Hi8pDJK{r0Iqq*va$cL=isZh0=1)wIoQ^vYPs$<T2#x2Kj^?$few0Pe4I~zZ zeAYbg0c0)2OtIx}d)C`Mw&~<64nQ!Uk8$^SW6e!?j1HfU4$&%i_`y~2R>(rBz$+DY z`y}1}`M%-da686<lVV-dk8h2*Tn8V7;-njKI(p4zUJy$ofY$z#INdRf(>`}zw_w>8 z!BcqxVTim*F)-}$segV$ON*!Zl~dhX@Rz^K2Xu<c1P8u4bp<yQO?OQj^dKZcE}xh_ z<z&gNJz{ZTTu3nGIcR;qG9;?^M0kG|PuThGH1+;j!xXDN6I_*@xL=@r$xRBuVh{MN zIUGEgxYJ(DFHKoLGF3_xPSW_^TT*1w(&gCNFdnv^AMnNFK6+ia>rh<1-vjImult%O z!-WXvkA_agVuhluW};J;#r>)?^uHS;G?a?j;(z?Y^FTwOA?tzLFvQDf&X8}9s7Wh< znEfd_vPyF_V`?>kR`w_h@+%59oKa;NPVGUo52QjisO-|$cYE(VNmm#+`#T5a;gh|Z z8A0^l3UwQMn0J3x<h`4-5?ApmemDp`8K)X6T0efPN*-~cf<tL>XWL7tY~Ox<iRkdJ zU|072zio5s?pAI0%Yx0uJh1f5i7VKWaFIaB;45=yji!1nH9<de2OLj_y{&41?nyPO zUrZT8xW#w*TQ5)($;JeSp2Pgrams&!r<Pe}#(LDg-blL{ESlmQ?a5Th4_;WRJR+4E zw6tQreDz+4bser4GB#?<roQ`hsw<hwcyHa9dkP0IO=6)WWkTxg{$NTm-b*c?j2_ul zyuRy=77P?tF`%S2aa=XEJa>Au=_hGvp@_%SZKA)ec-h-dfwIhS3jGBLL6e6Os;1LR zRDG&3TF`HV*n{&*H!oTSsLq!U5xV5!Yr6I_!*VhmwC3a2BOYfWH13AtVY|n5jv49e zcb0xCCZnt0i$>-S$k9J@-c!8wG#siu(Lg<MtkAtqhD8bV`jR^%b&>y_r1nfy+}!<h zAF+SdUhcuD`9zF%pRIHymB_I~)P%%~M=eQ#Ic#<Zr+NPzGTI`9;4khM^2h2PqMd?5 zGH>W9g-ucwp=&Hs1=Vs4i_q;dQL$8~Uq2BVA4o4uY!6}S`xH(Qec+{mJD~qgg@6W8 zipi@Z!ZR+Kr_)u&G);pG$tg$8#KPrsl&N3(m($NAU&9ogH9rVfW<4Mw>^7$&96g<9 zHQzekG9T5SS7DVm7EFY%CjChhfRyap4+d;+^0ng^B)~xKFG^7d2oOo|R8uY&S|X0@ znAGMb^rFQwGPTzsFQ8ZK4S@WO(8`6T+$Yt9{jGMd?jrTeb|_!Un`n9xDZu-fW+_aJ z4Uyy_$)`Ot!~doWUHW`(?F!iYvc5+g-(W9X<-tX*h%6(f;+A(OQ@w{WYSiq&pjKnN z)tSH~5g)03sKk)U+&GyP*?86fusX1ttpH1ng8ruC6UOddM~t>0wvZh}1cW%&7{tT$ zze(TwkA~V|_~nL{6YE#^RUC__Mx26zo*w(EfK2Q@R6xo`VkJKs^Eax`&*O*bw~*ap zyaqA_p(~(POY{H5+NIgewtB{|(%ML_wR8o);^XGTQ|{*J>74v>{_iyU;U*NTN}A%` z`8ltg(&furYlb!j%1ra!KPSiG<VRTwPDN9f5*7>mJ>f4c!bkAtjb_qmQ+aVB(QohO zRo@%)1krVtMPgkT6&3T*u`XO8pE&-!!u((3qVnraj|gN5aDxvqtrPs*MCZcO3i^Qt zI7$&BFr)50exhv11)82?u`ab0FgUSw;dpbnAtmz4k^&Nx`xMQ$5(JW}ry%)ry+DV> zS)TWjtXz7V6iK5$ghFuPiT>;;fAp)oy%%7grs4UwqU5+Ms96%`wU=YU5W-UGw(6iq z2GhB=Zw49;Yu<#7=soc@tZvYFIVNfkRPsCT&;76cYOONM<!9yYT8XS_j|<f)GAw6X z_w&Wq9xu5;px-$u*_Z^YS22HQpD*L|Z1fb)`d&qCQ^smb{5_5>wv!v*e#(X?l7eB- z&pWvVcaO;IKDg7C8bZ-+Hm`g>n_WC6%BL=CZlc``M{0T;%eYQ4t}V%m20okR=HET) z@)@WU_}tJOqiH7w2K%l<a?3NQ^6bZPnFJ<Mk`|jLP2*o$M^nx2160!F+h^quABnz; zAF6)v=cSvmebPJaPi4k%(nh|zGG@U(va!x`)nhbzOU0MkhuA%7v6ZH!EaE%H>pe0P z^FhhCX$ufUPCq4?C1A8ZSrVz=$~!VZ>;=kb8eaI;S1TKb|E9j*muthJe2||9pYYI$ zR@lkEo?K76^_v{llrL+?Swi1koJYJqG_-g!v?$ITb=q4#Rk--)f<yZAd%OCYe=RDW z4aV9=2rZm-rEPrLKA|1kuMv{%I=`DA(f6L;GQJ=_TAoYWBDl;}XZ0E+YfGjvp>ABD zh4Ibu7+f~5HEzy@7xo<qj_3c_D9C_vmh4{K98*=04-QLt1~2F@dBZe-l2GMsk#;A` zYHOcLf#^)Gn+{G3Q4YowOIK^&zQ|LTx89&c{IWvimdkFT8nJ{0X1}p;P(C>P^f$=} z+D3gYZ3W>%>m=U)p#UNOPPd&2cD&<J9<&QiV~vk5R%jVK^J1%HQ}`fxWs9c=2}L>; zxb{vXTzpCjcJAOEA_~=RX^_BM+_BYW*T{zzM(3TosvFOmf6Kp0IerP4`MuBgFdrkZ zf9X~m0O$toCckMn8klZDxWKr2%FHNk1VLQE)$!{Hz9{*a@TaZjC7kKsC1dIUx*6AQ zJFZc8p~!CewW(VvE@yaTPFt-6n+dZ@TM582m7=-#9JoDOH#zYPe{)-Lza89t+w#Zd zvQ3k$)Q)mPF)g)_+v$Gqgq~*RwGeBn{vhp!IPgkixW8WY)H`S{&~om!keO$Sum=oY zTatGW#*O^aVU<^!#et91z~$IYa;_C@J7+V)`<1b_lh`8FHOAgc=Az}lf)k%5xTMrv zr6uV%eKaU~wvi7pU)MeB7<DU@<PM)Ua&x<*j67UgrpKP|!tXx2R%YzH<LQn0XK>HK z2D;27Dik%)-q@hK-!I|N(cl`lAF^EIv0C-t$d1qtFnKIkcMW<4b%Lzf3Y+~~qB7`< zj);HTQS0Oex%zA170>?kRVA_m_*O?rZRpS3v{+O+cifN7Eb&>$Z==vGKh1V)C`qGu z_u8y<#N3Wp&$V^@T??GnE&RN^IyXM)r0h(gS3;b2pt0O!eNIt4{;3H~V5Ln7vs>8{ ziqqZL4Nwlvj4CtEv0>;Fw~D>LB_+-ecI)tiR%a!^GI3BawvNQGz4#b|_d<K40`zom zmZ%w0mYHcNzK(Ivg#;79zJA3Qs(emYQh|-Y&A>f&`e||2k;K}WnvU!Dx=0#ue(=U# zK&pYNNf5RQZOveUm+;dQ*FIA0&#`?@z*bBhUgr(n9_FpoHPB2pI8iMpW|sF*D{+75 z-k;nba~m^}=b7P$<BGu%3I<`>FAF1)S!oDKtNG-`%h{XQi6=SMH5GZ%8j?ugqt~!K zw<hNaHlewKU9pKh0n@^4X=DQ<4~UnDj4@h3>vA_m(*=EI<IgUo)z0l9R@mb|@QOas zWU>ssFVW0EZ;o=u#R5gBB$CUL+->U32;2PM2O(drij20XBy|hH+=bu!0*KIKBj%c+ z^{)B`3$NB2yp-IHf02C#Fw!(;S&rR%2P<?W3i)a{Hv71$$mqNwIwWJTc5XCVCY(ZM zZEUT%{m1IMAyv+ZxJdeiWsFSau%`*Ji4gu)?i`XAkA6AeCLD>q(!<`Q=u&+_V4eCe z?!d0m@n<F6bnzf#{rI&DDtbzb{#Q?q`iI`Fv^=Q#{GVsrKi@5H!=Yk{`KU+uXc?t@ zxGi_IMbsNpVL63R9MI#c?&2tT**S1&xk6UXV{?VrG2Vb8uwy$l2i~-P)jArRJvd+p zAMPX_jhyzm3a}Qc-9M){f2vD<`B3X9uKLW{DLodF&IsV$kXKT%@Qtp6|3s@S0+S=% zV+#X9n<D=<XzlauBx&tS1|?-doY!<IKSZPJ`vt2XRD)VP6|a+O3xDEZOZR$X3e5-S zuOL@^Te?HwRm63Ch16HfZ|^W=1@ax6$xAQ(4$2J*D69D!1&Ss_Wp=KanXxf%3)jB= zyl{(zRa6B4dz*qTVGFnQ#lf#G^~(Orm6*fvz@t#mixM85R=piy5ZZ)?<t2uZj~#Q1 z%87M&!_4Xmtg&aKmcnz`(+k~CS_9jg?1HcPF4&*jQGA1B5O}@9G995LTJuL|d}-c# zRi6~5UoNF~Ng3*RH>dhMu%QZ`ERBCD+uU~%h<WLJg$(5L-k}}ce*Ymz9%AWcG8~o) zrgMWKP5N71i-Vz&u9fBxjTT}~QT7=y$EdDt>>+E^Qd;Cz=IlGV(IwUrOz(+1Gkd7O z$HME|^+mAGBc4k(2jEj5$g30r-BUoK@Nn!*Td)5USoe+IZ-x9)#yd)sD}2Z?2{4@) zb|)xsK&pqOpB;+H#gbf^Pto29M<2Y>dU5pAF4p{+j=oBZ$2EXA*xI~AM@g20H7o_x z{2-Kc;SRpcxLXzU)a53ZoX%ndB^i8=>Sf&{i6CYkGSkvLj0<@C-!VKm#iX8dws__S zKp`T~rIAfaogJ!tV(~rs5)ctD#A};YXgPNI`<5=nWQjnIf<=1Pzn2y$C8yUkFKhwM z@%Ah?L`DM^@d<2evu->Oo=SVaiR<1GjYwe^G2)XY`l$Q%4H`|PpFA($N_8=6uOr0s zj+)C5x<cICx<i}#5D8LZ3LNFG7uU}%Q5<kbowYRV6Bs|^frDu{l2XM2Lj-Yh_!|?f z+a6@mRKb9j3p<Zh$+a4#UQQYhPF@-a9mWMpS)m;R6VEWV!i;mbS?{`eur*GS8_tX$ jEfLfZC2@~9k9g`Sv9u1yERTOL1mL!wsczLx=g0p8M%V6I diff --git a/static/glyphicons-halflings.png b/static/glyphicons-halflings.png deleted file mode 100644 index 92d4445dfd0af414835467132cf50c7c38a303af..0000000000000000000000000000000000000000 GIT binary patch literal 0 HcmV?d00001 literal 4352 zcmc(jSvb@I*TDbCl4#mw&6;FnOR{7wTf|sqB70@Y*4Sf=t&%DGGDxy7<4<NH`!>in zwn`&QQOr<`27|~lU*GNfe)r$+;%v`3=Q$VW;ymZMrG+ssw-7e~0K7L%46Ffwh5XNs z<6`?KHS^P-{ZmgZZ@~?jOs2~JH%~nY@PG5j1zTI#0Amn(L8qe2oETm=+B^jogFL!D zS!ISRHW3ybWQ6o&?2=byQi)JhfBSH9PzL~<0B#!S!^50cUq25lRnLyYPq06zWw>~J z`$KJG?wJet%MCZ1y81U)c?UzG;{mBi?no2aAHvt8L__Xy66K$DAupSD_4^VSeG;vA zGhrY7dmCA}Zg<=d*dvUYvYMo40k!iu>o|-n)q^ld6Q(6yBtUWr1GY<4vK2?uoeS|r zT(a}}&NC3;#Lv8{0Y$f=#j|95fZYUrx?foCUQ)KvUf$-LSb+6D%%)z#|1KO+ZTgw~ zNbE_n|4p~xYoc$edOQF-XOS;%<r!#dmHF{5#RTzN2!T(FFMc;x+SmC=Km>evzdNi3 zk@(r9h#R5FpacG)j3VDRRz>g49u-o5A=@X`M=nQQ@W&MqFu3+}8)vIJ<N(sT_Zk8X zMLcU+@C0(GanqcI+g=S0kMDE|mIlGu&c=CozOm!OJr0PRi4D`Obo#+t^;Xncwa7ai zdh<9v@cF*U;YbI{iHB@gJAiGAx>yezf?(vDF#3iq72Yg1rU0$uCw``L1fzH6tU=MT zJ)FP#7~BMLoosB<>)Y`BnyxN?%PW`qwa_nrmk;P<^+|3lA$<ii8%uY~81lp=vs^qj zbHc@jPjA%v+=Qq|+H=tEesx$(-?7Mn9R7&2+ZkE|b0%rF{pOe&2PywxrLyZ}ob?{? zS!X14D0!!&R7j4z&a_ZX7E96o-d9#)-rDWl);JNdUKsSn^M1g(Sofin)_^D2A6fsk zK%N&KDHIEtjz^2e+RnzNElc?mvW&i)!L?OOITL^U!tz7HAYtpl+few+Se~$Nk0>cC z!KnRdI-*8rENgl-h*t3^hviocbR?_BCX&(%?-)#H*`RRAUES@w^(0ey@bvFIq^EE0 zYIYPpa4Xz>{9(cUIq~=IuByDHtJskc@OXkoyhOvqjT$BRxhihe#hq<$(TaV?g(bYx zzk*$b_y4xdrKd-u!#@W)7x%!%FE62JOZu)fTpnAUKW94KXQKo9lR9BoI`nN#BV<pu zN$Y&tINUw4JJ60wNhX=$oO%xnS0~8-36@e}lO69__j)7adZ<L2U#u5vwGeo2shUYF zH*Rf1efjD`jdvTV8a6X+&!xQkbfP<z!gz1jlz##Puuh>NL^WLc-2PBnDb`!FkQ6Yw zt8#VMCqN`vOx>8A-pqa3!sg7$vF4w|C29%3h5O_{d+D-|gED!U;S&A}5QU_Uz%?vp zmMBIPvj7qQQG74PJJYIU8KAgcJcJvNO0O6=%8w|@chXvpUX6O34cERMj)m?X)jwit zWYksusgx8zcrOv1Kd4Cm%yUoW#?wfM-ee=?*pXt7dU<wL(ECgNtn7KAcQSgjF$wec z&wNDxS$nw$r4-^(dj0lt)f7DU5?+TTQ7UFh7R=*xI5;Wr=aA7JB?^0SzgQ^V;4r`? zBrN-yp=!hwMFq0PE?Y!UWLSr9S4c>vyZrhI*Zx3!VQzm2&D<yRh#LVfjXeOPcj~wR z5UG;7Ix04MSLbA=`nZloXfY{`*@7=#K0}`VWppv~RO%H}$!V*DNHvZFBHUqfI?CD0 zbx!B4^9`#pqXl&iB{Pv^*lNn33}KeCeaE4o?M=ZBEL9o|=KG==a{vbsI4@1LO3@|! z=#F_^eo|k6WLCD`I?D^lB}ZeRa3j2$+MNG{fZN~d@a`$my6AxPBfp8Irx1gDj_8y_ zB{|_Ko-%@Zv$H~Px&z9e&#zqq`(8HmN?{uv#cDixDOJ%G_;k$j?o_(Za8|9R0~pd~ zhP6EvoFeWkI{=X$R-d0BaUhyb8w0in4s%stxoODXOl;El?W^#yR`?d86Ax#>k2i(z zv;J?=_W|Z`2Nb*9*m`XJ^1ixr>GY^eNXXM8UzHKbJ%`E&g=n<QM>C-&t%U{b2>k}4 zM^eC8z9@VJ)NO6~zgW94x7psn_*GsP&AXPV>|c7+3V*`GDl?NuNHOr8_5jSBY+FrJ zxxFy&omakmacj-wPLUexLeI~s2^i^7j<QS1^o69wqChX$OY6u{tW}exT*h=kf_UuP z+XaMs<6dAuy-kT^H%eXIYHYk4Q!FTjJ*&L%*Q})SYV#u;NgCV`gwN=QJ~!7t_q2+B zpbd_ZMR9D%dyk)}nec)ZXV~q^?S+kxZJj&X5@|w?zO<x_02M#Q3a*5JM8Y&n;d~#^ zX?>diy$lDh;U-ze^bf8Wq&_j48xx9sRj~I0?AI|l`&NRKa0xj_M7{QQP8x>W$llZ# z^2}mA)Bep^+iA@Qw-LK1wT3nbnW#j??18HOX9M~EwO_4MW54*U(nB|yBja(g7FnMC zblZNR)Y{`EcNWNZ9&#=!$@W#;-?`_@7{fb;%BTG<Be%)pb!CB`M;1FsO>aNt!jg%h zP{`+<{G!`T5|=OLq>Z*{Z2O&8zMn16ACVB$Qm``DYk?tjJdb2uC7aci<-`J?E%OU+ zGrN5UtA#%|w#4Z;NP?k$>n!<|SrjF%qnK<QD=|fvQ-`MgFRin=cJ~1?W$Nv-%7>36 z-X#tb9{hRfZswTsPVZBN8H~75sHKLYIz~6u+pKzy#crwlQTpM#$E~+Abk)TD#sz#v zXX8Go`ZaF>B8Zu%M9U<U?k5{O<y&QE7KlDa9?QUr-S}#I$LYUm81UoWaH<><;>RXE zbfFb@39Y9#&~E%DMKl*GIPjFwcNZ7nuMbVEpA0WbvBjM9QA!sp{YiDoe131&NawG0 z)w7{^`zTTBX*b%&r|n~U@dMgnxo!))g;D+Qg=`Xw5@VHk^{hiH?Dbc#u;gsXHzn0i z2)8o6*&Kl>6tpGG-xYv<M}QNBKQ@Z8AUtKe=QqbSl$Amw(w@PJ2Fl*B4kD#B1X|@h zND6v-C(>B-r`9coW<<#c<0|E=wQpY(XerrkkfVOt!t*N?wvbI|9F@&~JQ7q2jXe2H zCW^MvkWX8I-=%fo@BdI{A^py@pAB`s<yjfB3(la;jxJW|8b9;qtmahyAaiMpzZU^P zxD>hd&A{*amKE*X!a7A2Yu?Z%f;af$36@t#hgGI$UAqZQr>(vfUM3&C0L=d07kpTV z65hXXqa6SYLUvQ%beIm#w8HN~d3!4?$?iB2Owr|ut8l>>rMSqaZB}JGncrpN>H)eX z?`{XC$$(nou>9J>y&RJ_GCHrPS%%Jr+GeZ-p;^lV`1YLmyxKN-u#7+}dnx}N%zgXH z$CV1rQyi4eN)t(4&9Ix9{_jMeW*4;LYis@>9EQ2Es^gfy-VKyn0lc8i{7q3yuQV}F zD6Fom;2?qz@ukzYpge~g8?BAWbC}{;E82F=WrGc<q3x&8B^qmty_aky%YQ{CKTGq< zYP!kE(69SylMU^oAELgld(|`QSIDWIzU`!z4rh5Kn4EmCqu{yU{SIwx=mqDK8w<~1 zUPFy^`6*;La<HSR(O`c-+NrbAEnz=wxz=;F=D$%Gr5~UQ*wG%^^eW0ENv91u_qR-a z$S)u&@oi_Fi#yBZUxTms_h&AvlAOS|`l_14f97W-V>0;?er)DQ&9VG84bSn{>9B(k zwM%!e%*jQ~?@0DuS;yYC#^~O_E+}d7VN;GP%ockmCFlj4DNZ%yl_X-Hn$v_=+Er1z z)xF^ugN@xFweaki3bVXB3?uwjsn55R<b|OgeId~Hv@}>D1&YMi6B+jBAEU6|0Y1ne zLxbyOnkM9BHX2f}bHa<7WG>P_pz=aP(B)D(uo1i&yvId9DaA3GTsK?WdG%g5Q5z-% zUfT;wH`Xu@LDvM>F<4<`LiFUdk7UO)oS&1>Rnv!81;V#S1gZ^;byAIw5fmjY3m)nw z?+@SmlmBCWV>bFM8|-jGB{WLeI3o9DaWo<)11@8`kh*v=cN0DNB+st4sz6R#2I0qi z4c&8ZcAexDoiEyzoZJ((D9)8bG%^Z+MCs@_Q)++#Uvn&7#CI<7^ioFM{2qLTEAfMX z#1kD>oACS6EsTK8F}{R&pahvhyt|}$lX5-EzVP=!*jL*U(=7^7%UUF#`g>m(9)4uh zN+-O*&B&PgYQ520)x+!;$#)PXM`Kgq-o1CQLPsDGuSVi?k7|gIEtmv^WewHMkLAio zl1Us*ZM8T5*j_cED4OCIiNDZ{(dj&{3{g&T+~4Y*L((GimlI~v8Q&*2;zNurHxdEX zDgWY5T-u#~Rw6AH53<&eUOA_3sJa+<`S@61`0Z+&gPPC(dA9xY-3vCHs+QQ8y<*H| zq`~2~B6ACGIIhlq0<JP>$V=$vE_&HDcwxCpLD6$_1>ZT*h{SQByL1NMw0+fOj?Wz& zFvJdbQkbJBeJ=wX#hUle7%rUXR$4yPWhM|#t(`DrC+d#^K8*!sRn%{Eee5S%bqSan z?Gaxb6y6;Dw^4Ura3@7~UnV3ahsAZxfc!%uwqZbo@PGj7@>ji1sVn}8fiB(aiz~Jo zTDXK*@oVh~gVo^Iu~o8PQNMj6)RalL?o3^H@pnjZNLWoX&@@;gDJHvX&C-&SZCkAF z?Pux@B3eZQ037cWb&FZMuP+XLz1yG`s8)?SoCs!ygWlxG$PB`Eka2i37Fv)TK{|58 zJti;S=?xo)8?eTei(HD#<H{`dIBo}QZ*qye7Ch&8W=G`>f`Jq8j>vX~5NRzRU9sf_ z>oxtdr~$>ax+OJ;^X)vsSztp0JYJsoQlX{)JP`NN^%4mv6u3oW-hBTdM2W@5-Fze> z9n9nd!<vn@x)+DSqur{lShQR5c_q20z&z9X_VI@tF-sZITiJ8(=%yDq%20jBZq4o? zgCC2nZ#R@cyO{hJ?i_$meOX?m;pkq%(#414r`r1hpFn%A^?fTAk~P~=C0`Omj7x)= z_=sB}!Gp5B>;qg7R6d&M#&&}CPAvA|mF^4XPltG`XZl9!t)5o^flxcEGJRDAZjOjF zQ0Iea%DG$E3bP&!(93|2RCY3l5t3s3J*JOik0=hGeaJ@3@H8tD7<k9<<dKwp&eQ6Z z9|U0$hb)b5lItCim6MC_Nf&^qL{S0zjAEPdi{G~l$mUBpQVcZOtKq$za5*WnwuQO{ zxF$NXUlSh-TEr%CuFbjgKX@wV^CqEZM<ObXOWagY0q?8j*FR)BnR)!IQXA#2X-7RS zQDDqU9@ib_?%osL+z(HZl~m@gbUVL(W{K>CVRqHg&`+R3j0a8@kqB}PI}{$m!yRab zvul5lL(>3*TF>n~)*#hsmwUTtKRAA2Fnk0PENdI!9GrZLu@zyKzs+&m-IKFviqv>& kg1Lm#gqI~e;$iYPkmG5c&N-g{UI@TVLkokN>#mRg2V?7pi2wiq diff --git a/static/js/bootstrap-dropdown.js b/static/js/bootstrap-dropdown.js new file mode 100644 index 0000000000..2bf8858749 --- /dev/null +++ b/static/js/bootstrap-dropdown.js @@ -0,0 +1,92 @@ +/* ============================================================ + * bootstrap-dropdown.js v2.0.2 + * http://twitter.github.com/bootstrap/javascript.html#dropdowns + * ============================================================ + * Copyright 2012 Twitter, Inc. + * + * Licensed under the Apache License, Version 2.0 (the "License"); + * you may not use this file except in compliance with the License. + * You may obtain a copy of the License at + * + * http://www.apache.org/licenses/LICENSE-2.0 + * + * Unless required by applicable law or agreed to in writing, software + * distributed under the License is distributed on an "AS IS" BASIS, + * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. + * See the License for the specific language governing permissions and + * limitations under the License. + * ============================================================ */ + + +!function( $ ){ + + "use strict" + + /* DROPDOWN CLASS DEFINITION + * ========================= */ + + var toggle = '[data-toggle="dropdown"]' + , Dropdown = function ( element ) { + var $el = $(element).on('click.dropdown.data-api', this.toggle) + $('html').on('click.dropdown.data-api', function () { + $el.parent().removeClass('open') + }) + } + + Dropdown.prototype = { + + constructor: Dropdown + + , toggle: function ( e ) { + var $this = $(this) + , selector = $this.attr('data-target') + , $parent + , isActive + + if (!selector) { + selector = $this.attr('href') + selector = selector && selector.replace(/.*(?=#[^\s]*$)/, '') //strip for ie7 + } + + $parent = $(selector) + $parent.length || ($parent = $this.parent()) + + isActive = $parent.hasClass('open') + + clearMenus() + !isActive && $parent.toggleClass('open') + + return false + } + + } + + function clearMenus() { + $(toggle).parent().removeClass('open') + } + + + /* DROPDOWN PLUGIN DEFINITION + * ========================== */ + + $.fn.dropdown = function ( option ) { + return this.each(function () { + var $this = $(this) + , data = $this.data('dropdown') + if (!data) $this.data('dropdown', (data = new Dropdown(this))) + if (typeof option == 'string') data[option].call($this) + }) + } + + $.fn.dropdown.Constructor = Dropdown + + + /* APPLY TO STANDARD DROPDOWN ELEMENTS + * =================================== */ + + $(function () { + $('html').on('click.dropdown.data-api', clearMenus) + $('body').on('click.dropdown.data-api', toggle, Dropdown.prototype.toggle) + }) + +}( window.jQuery ); diff --git a/templates/bootstrap.hamlet b/templates/bootstrap.hamlet new file mode 100644 index 0000000000..c03c459a64 --- /dev/null +++ b/templates/bootstrap.hamlet @@ -0,0 +1,52 @@ +$doctype 5 +<html> + <head> + <title>#{baseTitle webapp} #{pageTitle page} + <link rel="icon" href=@{StaticR favicon_ico} type="image/x-icon"> + <meta name="viewport" content="width=device-width,initial-scale=1.0"> + <style type="text/css"> + body { + padding-top: 60px; + padding-bottom: 40px; + } + .sidebar-nav { + padding: 9px 0; + } + ^{pageHead page} + <body> + + <div class="navbar navbar-fixed-top"> + <div class="navbar-inner"> + <div class="container"> + <a class="brand" href="#"> + git-annex + <ul class="nav"> + <li class="active"> + <a href="#">Dashboard</a> + <li> + <a href="@{ConfigR}">Config</a> + <ul class="nav pull-right"> + <li class="dropdown" id="menu1"> + <a class="dropdown-toggle" data-toggle="dropdown" href="#menu1"> + Current Repository: #{baseTitle webapp} + <b class="caret"></b> + <ul class="dropdown-menu"> + <li><a href="#">#{baseTitle webapp}</a></li> + <li class="divider"></li> + <li><a href="#">Add new repository</a></li> + + <div class="container-fluid"> + <div class="row-fluid"> + <div class="span3"> + <div class="sidebar-nav"> + <div class="alert alert-info"> + <b>This is just a demo.</b> If this were not just a demo, + I'd not be filling this sidebar with silly alerts. + <div class="alert alert-success"> + <b>Well done!</b> + You successfully read this important alert message. + <div class="alert alert-error"> + <b>Whoops!</b> + Unable to connect to blah blah.. + <div class="span9"> + ^{pageBody page} diff --git a/templates/default-layout.hamlet b/templates/default-layout.hamlet index bd16969f93..3701e3c42f 100644 --- a/templates/default-layout.hamlet +++ b/templates/default-layout.hamlet @@ -1,10 +1,3 @@ -$doctype 5 -<html> - <head> - <title>#{baseTitle webapp} #{pageTitle page} - <link rel="icon" href=@{StaticR favicon_ico} type="image/x-icon"> - ^{pageHead page} - <body> - $maybe msg <- mmsg - <div #message>#{msg} - ^{pageBody page} +$maybe msg <- mmsg + <div #message>#{msg} +^{widget} diff --git a/templates/longpolling.julius b/templates/longpolling.julius index 351f2f8c60..eff8d3f444 100644 --- a/templates/longpolling.julius +++ b/templates/longpolling.julius @@ -1,5 +1,5 @@ -// Uses long-polling to update a div with id=#{poll} +// Uses long-polling to update a div with id=#{updating} // The gethtml route should return a new div, with the same id. // // Maximum update frequency is controlled by #{startdelay} @@ -16,7 +16,7 @@ $.LongPoll = (function() { 'url': '@{gethtml}', 'dataType': 'html', 'success': function(data, status, jqxhr) { - $('##{poll}').replaceWith(data); + $('##{updating}').replaceWith(data); setTimeout($.LongPoll.send, #{delay}); numerrs=0; }, diff --git a/templates/status.hamlet b/templates/status.hamlet index 1f975b35f4..1da189d1f3 100644 --- a/templates/status.hamlet +++ b/templates/status.hamlet @@ -1,2 +1,26 @@ -<div id="#{poll}"> - polled at #{time} +<span id="#{updating}"> + <div class="hero-unit"> + <div class="row-fluid"> + <h3> + foo ← + <small>usb drive</small> + <small class="pull-right">40% of 10 mb</small> + <div class="progress progress-striped"> + <div class="bar" style="width: 40%;"> + <div class="row-fluid"> + <h3> + some_filenames_are_long_and_ugly_like_this_one.mp3 → + <small>Amazon S3</small> + <small class="pull-right">10% of 50 mb</small> + <div class="progress progress-striped"> + <div class="bar" style="width: 10%;"> + <div class="row-fluid"> + <h3> + bigfile ← + <small>usb drive</small> + <small class="pull-right">0% of 512 mb</small> + <div class="progress progress-striped"> + <div class="bar" style="width: 0%;"> + <footer> + <span> + polled at #{time} From 0f6292920ac360f78c3c4a3b9d883b758900c063 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Fri, 27 Jul 2012 11:47:34 -0400 Subject: [PATCH 134/331] webapp now displays the real running and queued transfers yowza!!! --- Assistant.hs | 2 +- Assistant/Threads/Transferrer.hs | 8 ++--- Assistant/Threads/WebApp.hs | 54 ++++++++++++++++++++------------ Assistant/TransferQueue.hs | 25 +++++++++++---- Logs/Transfer.hs | 17 +++++++--- templates/status.hamlet | 48 +++++++++++++++------------- 6 files changed, 96 insertions(+), 58 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index b539b27bc4..072aa3be3b 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -155,7 +155,7 @@ startDaemon assistant foreground , mountWatcherThread st dstatus scanremotes , transferScannerThread st scanremotes transferqueue #ifdef WITH_WEBAPP - , webAppThread st dstatus + , webAppThread st dstatus transferqueue #endif , watchThread st dstatus transferqueue changechan ] diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs index 4ee5290e1c..d8a1469484 100644 --- a/Assistant/Threads/Transferrer.hs +++ b/Assistant/Threads/Transferrer.hs @@ -38,7 +38,7 @@ transfererThread st dstatus transferqueue slots = go ifM (runThreadState st $ shouldTransfer dstatus t info) ( do debug thisThread [ "Transferring:" , show t ] - runTransfer st dstatus slots t info + transferThread st dstatus slots t info , debug thisThread [ "Skipping unnecessary transfer:" , show t ] ) go @@ -76,8 +76,8 @@ shouldTransfer dstatus t info = - thread's cache must be invalidated once a transfer completes, as - changes may have been made to the git-annex branch. -} -runTransfer :: ThreadState -> DaemonStatusHandle -> TransferSlots -> Transfer -> TransferInfo -> IO () -runTransfer st dstatus slots t info = case (transferRemote info, associatedFile info) of +transferThread :: ThreadState -> DaemonStatusHandle -> TransferSlots -> Transfer -> TransferInfo -> IO () +transferThread st dstatus slots t info = case (transferRemote info, associatedFile info) of (Nothing, _) -> noop (_, Nothing) -> noop (Just remote, Just file) -> do @@ -99,7 +99,7 @@ runTransfer st dstatus slots t info = case (transferRemote info, associatedFile transferprocess remote file = do showStart "copy" file showAction $ tofrom ++ " " ++ Remote.name remote - ok <- transfer t (Just file) $ + ok <- runTransfer t (Just file) $ if isdownload then getViaTmp key $ Remote.retrieveKeyFile remote key (Just file) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 050d62cf17..171c7fd9c4 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -12,19 +12,26 @@ module Assistant.Threads.WebApp where import Assistant.Common import Assistant.ThreadedMonad import Assistant.DaemonStatus +import Assistant.TransferQueue import Utility.WebApp import Utility.Yesod import Utility.FileMode import Utility.TempFile import Git +import Logs.Transfer +import Utility.Percentage +import Utility.DataUnits +import Types.Key +import qualified Remote import Yesod import Yesod.Static import Text.Hamlet import Network.Socket (PortNumber) import Text.Blaze.Renderer.String -import Data.Text +import Data.Text (Text, pack, unpack) import Data.Time.Clock +import qualified Data.Map as M thisThread :: String thisThread = "WebApp" @@ -32,6 +39,7 @@ thisThread = "WebApp" data WebApp = WebApp { threadState :: ThreadState , daemonStatus :: DaemonStatusHandle + , transferQueue :: TransferQueue , secretToken :: Text , baseTitle :: String , getStatic :: Static @@ -104,6 +112,12 @@ statusDisplay = do webapp <- lift getYesod time <- show <$> liftIO getCurrentTime + current <- liftIO $ runThreadState (threadState webapp) $ + M.toList . currentTransfers + <$> getDaemonStatus (daemonStatus webapp) + queued <- liftIO $ getTransferQueue $ transferQueue webapp + let transfers = current ++ queued + updating <- lift newIdent $(widgetFile "status") @@ -131,31 +145,31 @@ getConfigR = defaultLayout $ do setTitle "configuration" [whamlet|<a href="@{HomeR}">main|] -webAppThread :: ThreadState -> DaemonStatusHandle -> IO () -webAppThread st dstatus = do - webapp <- mkWebApp st dstatus +webAppThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> IO () +webAppThread st dstatus transferqueue = do + webapp <- mkWebApp app <- toWaiAppPlain webapp app' <- ifM debugEnabled ( return $ httpDebugLogger app , return app ) runWebApp app' $ \port -> runThreadState st $ writeHtmlShim webapp port - -mkWebApp :: ThreadState -> DaemonStatusHandle -> IO WebApp -mkWebApp st dstatus = do - dir <- absPath =<< runThreadState st (fromRepo repoPath) - home <- myHomeDir - let reldir = if dirContains home dir - then relPathDirToFile home dir - else dir - token <- genRandomToken - return $ WebApp - { threadState = st - , daemonStatus = dstatus - , secretToken = pack token - , baseTitle = reldir - , getStatic = $(embed "static") - } + where + mkWebApp = do + dir <- absPath =<< runThreadState st (fromRepo repoPath) + home <- myHomeDir + let reldir = if dirContains home dir + then relPathDirToFile home dir + else dir + token <- genRandomToken + return $ WebApp + { threadState = st + , daemonStatus = dstatus + , transferQueue = transferqueue + , secretToken = pack token + , baseTitle = reldir + , getStatic = $(embed "static") + } {- Creates a html shim file that's used to redirect into the webapp, - to avoid exposing the secretToken when launching the web browser. -} diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs index 9f0ea5cbe1..414a1f9bee 100644 --- a/Assistant/TransferQueue.hs +++ b/Assistant/TransferQueue.hs @@ -9,6 +9,7 @@ module Assistant.TransferQueue ( TransferQueue, Schedule(..), newTransferQueue, + getTransferQueue, queueTransfers, queueTransfer, queueTransferAt, @@ -24,17 +25,26 @@ import qualified Remote import Control.Concurrent.STM {- The transfer queue consists of a channel listing the transfers to make; - - the size of the queue is also tracked -} + - the size of the queue is also tracked, and a list is maintained + - in parallel to allow for reading. -} data TransferQueue = TransferQueue { queue :: TChan (Transfer, TransferInfo) , queuesize :: TVar Integer + , queuelist :: TVar [(Transfer, TransferInfo)] } data Schedule = Next | Later deriving (Eq) newTransferQueue :: IO TransferQueue -newTransferQueue = atomically $ TransferQueue <$> newTChan <*> newTVar 0 +newTransferQueue = atomically $ TransferQueue + <$> newTChan + <*> newTVar 0 + <*> newTVar [] + +{- Reads the queue's content without blocking or changing it. -} +getTransferQueue :: TransferQueue -> IO [(Transfer, TransferInfo)] +getTransferQueue q = atomically $ readTVar $ queuelist q stubInfo :: AssociatedFile -> Remote -> TransferInfo stubInfo f r = TransferInfo @@ -75,12 +85,14 @@ queueTransfers schedule q daemonstatus k f direction = do enqueue :: Schedule -> TransferQueue -> Transfer -> TransferInfo -> STM () enqueue schedule q t info - | schedule == Next = go unGetTChan - | otherwise = go writeTChan + | schedule == Next = go unGetTChan (new:) + | otherwise = go writeTChan (\l -> l++[new]) where - go a = do - void $ a (queue q) (t, info) + new = (t, info) + go modqueue modlist = do + void $ modqueue (queue q) new void $ modifyTVar' (queuesize q) succ + void $ modifyTVar' (queuelist q) modlist {- Adds a transfer to the queue. -} queueTransfer :: Schedule -> TransferQueue -> AssociatedFile -> Transfer -> Remote -> IO () @@ -100,4 +112,5 @@ queueTransferAt wantsz schedule q f t remote = atomically $ do getNextTransfer :: TransferQueue -> IO (Transfer, TransferInfo) getNextTransfer q = atomically $ do void $ modifyTVar' (queuesize q) pred + void $ modifyTVar' (queuelist q) (drop 1) readTChan (queue q) diff --git a/Logs/Transfer.hs b/Logs/Transfer.hs index b6962262d1..b0e21481cc 100644 --- a/Logs/Transfer.hs +++ b/Logs/Transfer.hs @@ -12,7 +12,9 @@ import Annex.Perms import Annex.Exception import qualified Git import Types.Remote +import Types.Key import qualified Fields +import Utility.Percentage import System.Posix.Types import Data.Time.Clock @@ -58,24 +60,29 @@ readDirection "upload" = Just Upload readDirection "download" = Just Download readDirection _ = Nothing +percentComplete :: Transfer -> TransferInfo -> Maybe Percentage +percentComplete (Transfer { transferKey = key }) (TransferInfo { bytesComplete = Just complete }) = + (\size -> percentage size complete) <$> keySize key +percentComplete _ _ = Nothing + upload :: UUID -> Key -> AssociatedFile -> Annex a -> Annex a -upload u key file a = transfer (Transfer Upload u key) file a +upload u key file a = runTransfer (Transfer Upload u key) file a download :: UUID -> Key -> AssociatedFile -> Annex a -> Annex a -download u key file a = transfer (Transfer Download u key) file a +download u key file a = runTransfer (Transfer Download u key) file a fieldTransfer :: Direction -> Key -> Annex a -> Annex a fieldTransfer direction key a = do afile <- Fields.getField Fields.associatedFile - maybe a (\u -> transfer (Transfer direction (toUUID u) key) afile a) + maybe a (\u -> runTransfer (Transfer direction (toUUID u) key) afile a) =<< Fields.getField Fields.remoteUUID {- Runs a transfer action. Creates and locks the lock file while the - action is running, and stores info in the transfer information - file. Will throw an error if the transfer is already in progress. -} -transfer :: Transfer -> Maybe FilePath -> Annex a -> Annex a -transfer t file a = do +runTransfer :: Transfer -> Maybe FilePath -> Annex a -> Annex a +runTransfer t file a = do tfile <- fromRepo $ transferFile t createAnnexDirectory $ takeDirectory tfile mode <- annexFileMode diff --git a/templates/status.hamlet b/templates/status.hamlet index 1da189d1f3..9b9b0f7d18 100644 --- a/templates/status.hamlet +++ b/templates/status.hamlet @@ -1,26 +1,30 @@ <span id="#{updating}"> - <div class="hero-unit"> - <div class="row-fluid"> - <h3> - foo ← - <small>usb drive</small> - <small class="pull-right">40% of 10 mb</small> - <div class="progress progress-striped"> - <div class="bar" style="width: 40%;"> - <div class="row-fluid"> - <h3> - some_filenames_are_long_and_ugly_like_this_one.mp3 → - <small>Amazon S3</small> - <small class="pull-right">10% of 50 mb</small> - <div class="progress progress-striped"> - <div class="bar" style="width: 10%;"> - <div class="row-fluid"> - <h3> - bigfile ← - <small>usb drive</small> - <small class="pull-right">0% of 512 mb</small> - <div class="progress progress-striped"> - <div class="bar" style="width: 0%;"> + <div class="span9"> + $if null transfers + <h2>No current transfers + $else + <h2>Transfers + $forall (transfer, info) <- transfers + $with percent <- maybe "unknown" (showPercentage 0) $ percentComplete transfer info + <div class="row-fluid"> + <h3> + $maybe file <- associatedFile info + #{file} + $nothing + #{show $ transferKey transfer} + $case transferDirection transfer + $of Upload + → + $of Download + ← + <small>#{maybe "unknown" Remote.name $ transferRemote info}</small> + $with size <- maybe "unknown" (roughSize dataUnits True) $ keySize $ transferKey transfer + $if isJust $ startedTime info + <small class="pull-right"><b>#{percent} of #{size}</b></small> + $else + <small class="pull-right">queued (#{size})</small> + <div class="progress progress-striped"> + <div class="bar" style="width: #{percent};"> <footer> <span> polled at #{time} From 3305e019db5938385172429216c96a9a1f328642 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Fri, 27 Jul 2012 12:09:34 -0400 Subject: [PATCH 135/331] add yesod-default another dependency cabal works without here, oddly --- debian/control | 1 + doc/install.mdwn | 1 + git-annex.cabal | 6 +++--- 3 files changed, 5 insertions(+), 3 deletions(-) diff --git a/debian/control b/debian/control index 1e7cb19e2c..89ca892834 100644 --- a/debian/control +++ b/debian/control @@ -25,6 +25,7 @@ Build-Depends: libghc-dbus-dev, libghc-yesod-dev, libghc-yesod-static-dev, + libghc-yesod-default-dev, libghc-case-insensitive-dev, libghc-http-types-dev, libghc-transformers-dev, diff --git a/doc/install.mdwn b/doc/install.mdwn index e529952611..76bffa00cf 100644 --- a/doc/install.mdwn +++ b/doc/install.mdwn @@ -51,6 +51,7 @@ libraries. To build and use git-annex by hand, you will need: * [dbus](http://hackage.haskell.org/package/dbus) * [yesod](http://hackage.haskell.org/package/yesod) * [yesod-static](http://hackage.haskell.org/package/yesod-static) + * [yesod-default](http://hackage.haskell.org/package/yesod-default) * [case-insensitive](http://hackage.haskell.org/package/case-insensitive) * [http-types](http://hackage.haskell.org/package/http-types) * [transformers](http://hackage.haskell.org/package/transformers) diff --git a/git-annex.cabal b/git-annex.cabal index aa71dacb6f..24e0df9c99 100644 --- a/git-annex.cabal +++ b/git-annex.cabal @@ -74,9 +74,9 @@ Executable git-annex CPP-Options: -DWITH_DBUS if flag(Webapp) - Build-Depends: yesod, yesod-static, case-insensitive, http-types, - transformers, wai, wai-logger, warp, blaze-builder, blaze-html, - blaze-markup, crypto-api, hamlet, clientsession + Build-Depends: yesod, yesod-static, yesod-default, case-insensitive, + http-types, transformers, wai, wai-logger, warp, blaze-builder, + blaze-html, blaze-markup, crypto-api, hamlet, clientsession CPP-Options: -DWITH_WEBAPP if os(darwin) From f1f90cb30b5318b3d13c1d401bd81a0747ec7b40 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Fri, 27 Jul 2012 12:14:57 -0400 Subject: [PATCH 136/331] add warning when building without the webapp --- Assistant.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/Assistant.hs b/Assistant.hs index 072aa3be3b..6b155a4a67 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -115,6 +115,8 @@ import Assistant.Threads.MountWatcher import Assistant.Threads.TransferScanner #ifdef WITH_WEBAPP import Assistant.Threads.WebApp +#else +#warning Building without the webapp. You probably need to install Yesod.. #endif import qualified Utility.Daemon import Utility.LogFile From c93b546ebdd4693e2ce32150ca14b5a90e8b09ba Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Fri, 27 Jul 2012 14:06:06 -0400 Subject: [PATCH 137/331] remove bogus AI_NUMERICSERV Not needed, and causes a segfault on OSX when it tries to dereference the NULL servicename. (Linux handles this case better.) --- Utility/WebApp.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Utility/WebApp.hs b/Utility/WebApp.hs index 517251a7a9..69864dc6d3 100644 --- a/Utility/WebApp.hs +++ b/Utility/WebApp.hs @@ -69,7 +69,7 @@ localSocket = do go $ Prelude.head addrs where hints = defaultHints - { addrFlags = [AI_ADDRCONFIG, AI_NUMERICSERV] + { addrFlags = [AI_ADDRCONFIG] , addrSocketType = Stream } go addr = bracketOnError (open addr) close (use addr) From bc5b1516175f143f42bda2d12f512768d2df7c9e Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Fri, 27 Jul 2012 14:45:19 -0400 Subject: [PATCH 138/331] update to newer version of Bootstrap This does fix some UI issues I was having. --- debian/copyright | 2 +- static/css/bootstrap-responsive.css | 563 +++--- static/css/bootstrap.css | 2473 +++++++++++++++++++-------- 3 files changed, 2080 insertions(+), 958 deletions(-) diff --git a/debian/copyright b/debian/copyright index 4cab3a048f..4e7345fd87 100644 --- a/debian/copyright +++ b/debian/copyright @@ -58,7 +58,7 @@ License: MIT or GPL-2 WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. Files: static/*/bootstrap* -Copyright: 2011-2012 Twitter, Inc. +Copyright: 2012 Twitter, Inc. License: Apache-2.0 Licensed under the Apache License, Version 2.0 (the "License"); you may not use this file except in compliance with the License. diff --git a/static/css/bootstrap-responsive.css b/static/css/bootstrap-responsive.css index 0bc6de916b..06e55c0b45 100644 --- a/static/css/bootstrap-responsive.css +++ b/static/css/bootstrap-responsive.css @@ -1,5 +1,5 @@ /*! - * Bootstrap Responsive v2.0.2 + * Bootstrap Responsive v2.0.4 * * Copyright 2012 Twitter, Inc * Licensed under the Apache License v2.0 @@ -7,85 +7,86 @@ * * Designed and built with all the love in the world @twitter by @mdo and @fat. */ + .clearfix { *zoom: 1; } + .clearfix:before, .clearfix:after { display: table; content: ""; } + .clearfix:after { clear: both; } + .hide-text { - overflow: hidden; - text-indent: 100%; - white-space: nowrap; + font: 0/0 a; + color: transparent; + text-shadow: none; + background-color: transparent; + border: 0; } + .input-block-level { display: block; width: 100%; min-height: 28px; - /* Make inputs at least the height of their button counterpart */ - - /* Makes inputs behave like true block-level elements */ - -webkit-box-sizing: border-box; - -moz-box-sizing: border-box; - -ms-box-sizing: border-box; - box-sizing: border-box; + -moz-box-sizing: border-box; + -ms-box-sizing: border-box; + box-sizing: border-box; } + .hidden { display: none; visibility: hidden; } + .visible-phone { - display: none; + display: none !important; } + .visible-tablet { - display: none; -} -.visible-desktop { - display: block; -} -.hidden-phone { - display: block; -} -.hidden-tablet { - display: block; + display: none !important; } + .hidden-desktop { - display: none; + display: none !important; } + @media (max-width: 767px) { .visible-phone { - display: block; + display: inherit !important; } .hidden-phone { - display: none; + display: none !important; } .hidden-desktop { - display: block; + display: inherit !important; } .visible-desktop { - display: none; + display: none !important; } } + @media (min-width: 768px) and (max-width: 979px) { .visible-tablet { - display: block; + display: inherit !important; } .hidden-tablet { - display: none; + display: none !important; } .hidden-desktop { - display: block; + display: inherit !important; } .visible-desktop { - display: none; + display: none !important ; } } + @media (max-width: 480px) { .nav-collapse { -webkit-transform: translate3d(0, 0, 0); @@ -111,14 +112,14 @@ padding-top: 0; } .form-horizontal .form-actions { - padding-left: 10px; padding-right: 10px; + padding-left: 10px; } .modal { position: absolute; top: 10px; - left: 10px; right: 10px; + left: 10px; width: auto; margin: 0; } @@ -133,14 +134,28 @@ position: static; } } + @media (max-width: 767px) { body { - padding-left: 20px; padding-right: 20px; + padding-left: 20px; } - .navbar-fixed-top { - margin-left: -20px; + .navbar-fixed-top, + .navbar-fixed-bottom { margin-right: -20px; + margin-left: -20px; + } + .container-fluid { + padding: 0; + } + .dl-horizontal dt { + float: none; + width: auto; + clear: none; + text-align: left; + } + .dl-horizontal dd { + margin-left: 0; } .container { width: auto; @@ -148,19 +163,20 @@ .row-fluid { width: 100%; } - .row { + .row, + .thumbnails { margin-left: 0; } - .row > [class*="span"], - .row-fluid > [class*="span"] { - float: none; + [class*="span"], + .row-fluid [class*="span"] { display: block; + float: none; width: auto; - margin: 0; - } - .thumbnails [class*="span"] { - width: auto; + margin-left: 0; } + .input-large, + .input-xlarge, + .input-xxlarge, input[class*="span"], select[class*="span"], textarea[class*="span"], @@ -168,20 +184,20 @@ display: block; width: 100%; min-height: 28px; - /* Make inputs at least the height of their button counterpart */ - - /* Makes inputs behave like true block-level elements */ - -webkit-box-sizing: border-box; - -moz-box-sizing: border-box; - -ms-box-sizing: border-box; - box-sizing: border-box; + -moz-box-sizing: border-box; + -ms-box-sizing: border-box; + box-sizing: border-box; } + .input-prepend input, + .input-append input, .input-prepend input[class*="span"], .input-append input[class*="span"] { + display: inline-block; width: auto; } } + @media (min-width: 768px) and (max-width: 979px) { .row { margin-left: -20px; @@ -288,205 +304,136 @@ .row-fluid:after { clear: both; } - .row-fluid > [class*="span"] { + .row-fluid [class*="span"] { + display: block; float: left; + width: 100%; + min-height: 28px; margin-left: 2.762430939%; + *margin-left: 2.709239449638298%; + -webkit-box-sizing: border-box; + -moz-box-sizing: border-box; + -ms-box-sizing: border-box; + box-sizing: border-box; } - .row-fluid > [class*="span"]:first-child { + .row-fluid [class*="span"]:first-child { margin-left: 0; } - .row-fluid > .span12 { + .row-fluid .span12 { width: 99.999999993%; + *width: 99.9468085036383%; } - .row-fluid > .span11 { + .row-fluid .span11 { width: 91.436464082%; + *width: 91.38327259263829%; } - .row-fluid > .span10 { + .row-fluid .span10 { width: 82.87292817100001%; + *width: 82.8197366816383%; } - .row-fluid > .span9 { + .row-fluid .span9 { width: 74.30939226%; + *width: 74.25620077063829%; } - .row-fluid > .span8 { + .row-fluid .span8 { width: 65.74585634900001%; + *width: 65.6926648596383%; } - .row-fluid > .span7 { + .row-fluid .span7 { width: 57.182320438000005%; + *width: 57.129128948638304%; } - .row-fluid > .span6 { + .row-fluid .span6 { width: 48.618784527%; + *width: 48.5655930376383%; } - .row-fluid > .span5 { + .row-fluid .span5 { width: 40.055248616%; + *width: 40.0020571266383%; } - .row-fluid > .span4 { + .row-fluid .span4 { width: 31.491712705%; + *width: 31.4385212156383%; } - .row-fluid > .span3 { + .row-fluid .span3 { width: 22.928176794%; + *width: 22.874985304638297%; } - .row-fluid > .span2 { + .row-fluid .span2 { width: 14.364640883%; + *width: 14.311449393638298%; } - .row-fluid > .span1 { + .row-fluid .span1 { width: 5.801104972%; + *width: 5.747913482638298%; } input, textarea, .uneditable-input { margin-left: 0; } - input.span12, textarea.span12, .uneditable-input.span12 { + input.span12, + textarea.span12, + .uneditable-input.span12 { width: 714px; } - input.span11, textarea.span11, .uneditable-input.span11 { + input.span11, + textarea.span11, + .uneditable-input.span11 { width: 652px; } - input.span10, textarea.span10, .uneditable-input.span10 { + input.span10, + textarea.span10, + .uneditable-input.span10 { width: 590px; } - input.span9, textarea.span9, .uneditable-input.span9 { + input.span9, + textarea.span9, + .uneditable-input.span9 { width: 528px; } - input.span8, textarea.span8, .uneditable-input.span8 { + input.span8, + textarea.span8, + .uneditable-input.span8 { width: 466px; } - input.span7, textarea.span7, .uneditable-input.span7 { + input.span7, + textarea.span7, + .uneditable-input.span7 { width: 404px; } - input.span6, textarea.span6, .uneditable-input.span6 { + input.span6, + textarea.span6, + .uneditable-input.span6 { width: 342px; } - input.span5, textarea.span5, .uneditable-input.span5 { + input.span5, + textarea.span5, + .uneditable-input.span5 { width: 280px; } - input.span4, textarea.span4, .uneditable-input.span4 { + input.span4, + textarea.span4, + .uneditable-input.span4 { width: 218px; } - input.span3, textarea.span3, .uneditable-input.span3 { + input.span3, + textarea.span3, + .uneditable-input.span3 { width: 156px; } - input.span2, textarea.span2, .uneditable-input.span2 { + input.span2, + textarea.span2, + .uneditable-input.span2 { width: 94px; } - input.span1, textarea.span1, .uneditable-input.span1 { + input.span1, + textarea.span1, + .uneditable-input.span1 { width: 32px; } } -@media (max-width: 979px) { - body { - padding-top: 0; - } - .navbar-fixed-top { - position: static; - margin-bottom: 18px; - } - .navbar-fixed-top .navbar-inner { - padding: 5px; - } - .navbar .container { - width: auto; - padding: 0; - } - .navbar .brand { - padding-left: 10px; - padding-right: 10px; - margin: 0 0 0 -5px; - } - .navbar .nav-collapse { - clear: left; - } - .navbar .nav { - float: none; - margin: 0 0 9px; - } - .navbar .nav > li { - float: none; - } - .navbar .nav > li > a { - margin-bottom: 2px; - } - .navbar .nav > .divider-vertical { - display: none; - } - .navbar .nav .nav-header { - color: #999999; - text-shadow: none; - } - .navbar .nav > li > a, - .navbar .dropdown-menu a { - padding: 6px 15px; - font-weight: bold; - color: #999999; - -webkit-border-radius: 3px; - -moz-border-radius: 3px; - border-radius: 3px; - } - .navbar .dropdown-menu li + li a { - margin-bottom: 2px; - } - .navbar .nav > li > a:hover, - .navbar .dropdown-menu a:hover { - background-color: #222222; - } - .navbar .dropdown-menu { - position: static; - top: auto; - left: auto; - float: none; - display: block; - max-width: none; - margin: 0 15px; - padding: 0; - background-color: transparent; - border: none; - -webkit-border-radius: 0; - -moz-border-radius: 0; - border-radius: 0; - -webkit-box-shadow: none; - -moz-box-shadow: none; - box-shadow: none; - } - .navbar .dropdown-menu:before, - .navbar .dropdown-menu:after { - display: none; - } - .navbar .dropdown-menu .divider { - display: none; - } - .navbar-form, - .navbar-search { - float: none; - padding: 9px 15px; - margin: 9px 0; - border-top: 1px solid #222222; - border-bottom: 1px solid #222222; - -webkit-box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.1), 0 1px 0 rgba(255, 255, 255, 0.1); - -moz-box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.1), 0 1px 0 rgba(255, 255, 255, 0.1); - box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.1), 0 1px 0 rgba(255, 255, 255, 0.1); - } - .navbar .nav.pull-right { - float: none; - margin-left: 0; - } - .navbar-static .navbar-inner { - padding-left: 10px; - padding-right: 10px; - } - .btn-navbar { - display: block; - } - .nav-collapse { - overflow: hidden; - height: 0; - } -} -@media (min-width: 980px) { - .nav-collapse.collapse { - height: auto !important; - overflow: visible !important; - } -} + @media (min-width: 1200px) { .row { margin-left: -30px; @@ -593,88 +540,132 @@ .row-fluid:after { clear: both; } - .row-fluid > [class*="span"] { + .row-fluid [class*="span"] { + display: block; float: left; + width: 100%; + min-height: 28px; margin-left: 2.564102564%; + *margin-left: 2.510911074638298%; + -webkit-box-sizing: border-box; + -moz-box-sizing: border-box; + -ms-box-sizing: border-box; + box-sizing: border-box; } - .row-fluid > [class*="span"]:first-child { + .row-fluid [class*="span"]:first-child { margin-left: 0; } - .row-fluid > .span12 { + .row-fluid .span12 { width: 100%; + *width: 99.94680851063829%; } - .row-fluid > .span11 { + .row-fluid .span11 { width: 91.45299145300001%; + *width: 91.3997999636383%; } - .row-fluid > .span10 { + .row-fluid .span10 { width: 82.905982906%; + *width: 82.8527914166383%; } - .row-fluid > .span9 { + .row-fluid .span9 { width: 74.358974359%; + *width: 74.30578286963829%; } - .row-fluid > .span8 { + .row-fluid .span8 { width: 65.81196581200001%; + *width: 65.7587743226383%; } - .row-fluid > .span7 { + .row-fluid .span7 { width: 57.264957265%; + *width: 57.2117657756383%; } - .row-fluid > .span6 { + .row-fluid .span6 { width: 48.717948718%; + *width: 48.6647572286383%; } - .row-fluid > .span5 { + .row-fluid .span5 { width: 40.170940171000005%; + *width: 40.117748681638304%; } - .row-fluid > .span4 { + .row-fluid .span4 { width: 31.623931624%; + *width: 31.5707401346383%; } - .row-fluid > .span3 { + .row-fluid .span3 { width: 23.076923077%; + *width: 23.0237315876383%; } - .row-fluid > .span2 { + .row-fluid .span2 { width: 14.529914530000001%; + *width: 14.4767230406383%; } - .row-fluid > .span1 { + .row-fluid .span1 { width: 5.982905983%; + *width: 5.929714493638298%; } input, textarea, .uneditable-input { margin-left: 0; } - input.span12, textarea.span12, .uneditable-input.span12 { + input.span12, + textarea.span12, + .uneditable-input.span12 { width: 1160px; } - input.span11, textarea.span11, .uneditable-input.span11 { + input.span11, + textarea.span11, + .uneditable-input.span11 { width: 1060px; } - input.span10, textarea.span10, .uneditable-input.span10 { + input.span10, + textarea.span10, + .uneditable-input.span10 { width: 960px; } - input.span9, textarea.span9, .uneditable-input.span9 { + input.span9, + textarea.span9, + .uneditable-input.span9 { width: 860px; } - input.span8, textarea.span8, .uneditable-input.span8 { + input.span8, + textarea.span8, + .uneditable-input.span8 { width: 760px; } - input.span7, textarea.span7, .uneditable-input.span7 { + input.span7, + textarea.span7, + .uneditable-input.span7 { width: 660px; } - input.span6, textarea.span6, .uneditable-input.span6 { + input.span6, + textarea.span6, + .uneditable-input.span6 { width: 560px; } - input.span5, textarea.span5, .uneditable-input.span5 { + input.span5, + textarea.span5, + .uneditable-input.span5 { width: 460px; } - input.span4, textarea.span4, .uneditable-input.span4 { + input.span4, + textarea.span4, + .uneditable-input.span4 { width: 360px; } - input.span3, textarea.span3, .uneditable-input.span3 { + input.span3, + textarea.span3, + .uneditable-input.span3 { width: 260px; } - input.span2, textarea.span2, .uneditable-input.span2 { + input.span2, + textarea.span2, + .uneditable-input.span2 { width: 160px; } - input.span1, textarea.span1, .uneditable-input.span1 { + input.span1, + textarea.span1, + .uneditable-input.span1 { width: 60px; } .thumbnails { @@ -683,4 +674,142 @@ .thumbnails > li { margin-left: 30px; } + .row-fluid .thumbnails { + margin-left: 0; + } +} + +@media (max-width: 979px) { + body { + padding-top: 0; + } + .navbar-fixed-top, + .navbar-fixed-bottom { + position: static; + } + .navbar-fixed-top { + margin-bottom: 18px; + } + .navbar-fixed-bottom { + margin-top: 18px; + } + .navbar-fixed-top .navbar-inner, + .navbar-fixed-bottom .navbar-inner { + padding: 5px; + } + .navbar .container { + width: auto; + padding: 0; + } + .navbar .brand { + padding-right: 10px; + padding-left: 10px; + margin: 0 0 0 -5px; + } + .nav-collapse { + clear: both; + } + .nav-collapse .nav { + float: none; + margin: 0 0 9px; + } + .nav-collapse .nav > li { + float: none; + } + .nav-collapse .nav > li > a { + margin-bottom: 2px; + } + .nav-collapse .nav > .divider-vertical { + display: none; + } + .nav-collapse .nav .nav-header { + color: #999999; + text-shadow: none; + } + .nav-collapse .nav > li > a, + .nav-collapse .dropdown-menu a { + padding: 6px 15px; + font-weight: bold; + color: #999999; + -webkit-border-radius: 3px; + -moz-border-radius: 3px; + border-radius: 3px; + } + .nav-collapse .btn { + padding: 4px 10px 4px; + font-weight: normal; + -webkit-border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; + } + .nav-collapse .dropdown-menu li + li a { + margin-bottom: 2px; + } + .nav-collapse .nav > li > a:hover, + .nav-collapse .dropdown-menu a:hover { + background-color: #222222; + } + .nav-collapse.in .btn-group { + padding: 0; + margin-top: 5px; + } + .nav-collapse .dropdown-menu { + position: static; + top: auto; + left: auto; + display: block; + float: none; + max-width: none; + padding: 0; + margin: 0 15px; + background-color: transparent; + border: none; + -webkit-border-radius: 0; + -moz-border-radius: 0; + border-radius: 0; + -webkit-box-shadow: none; + -moz-box-shadow: none; + box-shadow: none; + } + .nav-collapse .dropdown-menu:before, + .nav-collapse .dropdown-menu:after { + display: none; + } + .nav-collapse .dropdown-menu .divider { + display: none; + } + .nav-collapse .navbar-form, + .nav-collapse .navbar-search { + float: none; + padding: 9px 15px; + margin: 9px 0; + border-top: 1px solid #222222; + border-bottom: 1px solid #222222; + -webkit-box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.1), 0 1px 0 rgba(255, 255, 255, 0.1); + -moz-box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.1), 0 1px 0 rgba(255, 255, 255, 0.1); + box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.1), 0 1px 0 rgba(255, 255, 255, 0.1); + } + .navbar .nav-collapse .nav.pull-right { + float: none; + margin-left: 0; + } + .nav-collapse, + .nav-collapse.collapse { + height: 0; + overflow: hidden; + } + .navbar .btn-navbar { + display: block; + } + .navbar-static .navbar-inner { + padding-right: 10px; + padding-left: 10px; + } +} + +@media (min-width: 980px) { + .nav-collapse.collapse { + height: auto !important; + overflow: visible !important; + } } diff --git a/static/css/bootstrap.css b/static/css/bootstrap.css index dee87331f3..bb40c85f7d 100644 --- a/static/css/bootstrap.css +++ b/static/css/bootstrap.css @@ -1,5 +1,5 @@ /*! - * Bootstrap v2.0.2 + * Bootstrap v2.0.4 * * Copyright 2012 Twitter, Inc * Licensed under the Apache License v2.0 @@ -7,6 +7,7 @@ * * Designed and built with all the love in the world @twitter by @mdo and @fat. */ + article, aside, details, @@ -19,6 +20,7 @@ nav, section { display: block; } + audio, canvas, video { @@ -26,23 +28,28 @@ video { *display: inline; *zoom: 1; } + audio:not([controls]) { display: none; } + html { font-size: 100%; -webkit-text-size-adjust: 100%; - -ms-text-size-adjust: 100%; + -ms-text-size-adjust: 100%; } + a:focus { outline: thin dotted #333; outline: 5px auto -webkit-focus-ring-color; outline-offset: -2px; } + a:hover, a:active { outline: 0; } + sub, sup { position: relative; @@ -50,18 +57,26 @@ sup { line-height: 0; vertical-align: baseline; } + sup { top: -0.5em; } + sub { bottom: -0.25em; } + img { - height: auto; + max-width: 100%; + vertical-align: middle; border: 0; -ms-interpolation-mode: bicubic; - vertical-align: middle; } + +#map_canvas img { + max-width: none; +} + button, input, select, @@ -70,16 +85,19 @@ textarea { font-size: 100%; vertical-align: middle; } + button, input { *overflow: visible; line-height: normal; } + button::-moz-focus-inner, input::-moz-focus-inner { padding: 0; border: 0; } + button, input[type="button"], input[type="reset"], @@ -87,49 +105,56 @@ input[type="submit"] { cursor: pointer; -webkit-appearance: button; } + input[type="search"] { - -webkit-appearance: textfield; -webkit-box-sizing: content-box; - -moz-box-sizing: content-box; - box-sizing: content-box; + -moz-box-sizing: content-box; + box-sizing: content-box; + -webkit-appearance: textfield; } + input[type="search"]::-webkit-search-decoration, input[type="search"]::-webkit-search-cancel-button { -webkit-appearance: none; } + textarea { overflow: auto; vertical-align: top; } + .clearfix { *zoom: 1; } + .clearfix:before, .clearfix:after { display: table; content: ""; } + .clearfix:after { clear: both; } + .hide-text { - overflow: hidden; - text-indent: 100%; - white-space: nowrap; + font: 0/0 a; + color: transparent; + text-shadow: none; + background-color: transparent; + border: 0; } + .input-block-level { display: block; width: 100%; min-height: 28px; - /* Make inputs at least the height of their button counterpart */ - - /* Makes inputs behave like true block-level elements */ - -webkit-box-sizing: border-box; - -moz-box-sizing: border-box; - -ms-box-sizing: border-box; - box-sizing: border-box; + -moz-box-sizing: border-box; + -ms-box-sizing: border-box; + box-sizing: border-box; } + body { margin: 0; font-family: "Helvetica Neue", Helvetica, Arial, sans-serif; @@ -138,204 +163,279 @@ body { color: #333333; background-color: #ffffff; } + a { color: #0088cc; text-decoration: none; } + a:hover { color: #005580; text-decoration: underline; } + .row { margin-left: -20px; *zoom: 1; } + .row:before, .row:after { display: table; content: ""; } + .row:after { clear: both; } + [class*="span"] { float: left; margin-left: 20px; } + .container, .navbar-fixed-top .container, .navbar-fixed-bottom .container { width: 940px; } + .span12 { width: 940px; } + .span11 { width: 860px; } + .span10 { width: 780px; } + .span9 { width: 700px; } + .span8 { width: 620px; } + .span7 { width: 540px; } + .span6 { width: 460px; } + .span5 { width: 380px; } + .span4 { width: 300px; } + .span3 { width: 220px; } + .span2 { width: 140px; } + .span1 { width: 60px; } + .offset12 { margin-left: 980px; } + .offset11 { margin-left: 900px; } + .offset10 { margin-left: 820px; } + .offset9 { margin-left: 740px; } + .offset8 { margin-left: 660px; } + .offset7 { margin-left: 580px; } + .offset6 { margin-left: 500px; } + .offset5 { margin-left: 420px; } + .offset4 { margin-left: 340px; } + .offset3 { margin-left: 260px; } + .offset2 { margin-left: 180px; } + .offset1 { margin-left: 100px; } + .row-fluid { width: 100%; *zoom: 1; } + .row-fluid:before, .row-fluid:after { display: table; content: ""; } + .row-fluid:after { clear: both; } -.row-fluid > [class*="span"] { + +.row-fluid [class*="span"] { + display: block; float: left; + width: 100%; + min-height: 28px; margin-left: 2.127659574%; + *margin-left: 2.0744680846382977%; + -webkit-box-sizing: border-box; + -moz-box-sizing: border-box; + -ms-box-sizing: border-box; + box-sizing: border-box; } -.row-fluid > [class*="span"]:first-child { + +.row-fluid [class*="span"]:first-child { margin-left: 0; } -.row-fluid > .span12 { + +.row-fluid .span12 { width: 99.99999998999999%; + *width: 99.94680850063828%; } -.row-fluid > .span11 { + +.row-fluid .span11 { width: 91.489361693%; + *width: 91.4361702036383%; } -.row-fluid > .span10 { + +.row-fluid .span10 { width: 82.97872339599999%; + *width: 82.92553190663828%; } -.row-fluid > .span9 { + +.row-fluid .span9 { width: 74.468085099%; + *width: 74.4148936096383%; } -.row-fluid > .span8 { + +.row-fluid .span8 { width: 65.95744680199999%; + *width: 65.90425531263828%; } -.row-fluid > .span7 { + +.row-fluid .span7 { width: 57.446808505%; + *width: 57.3936170156383%; } -.row-fluid > .span6 { + +.row-fluid .span6 { width: 48.93617020799999%; + *width: 48.88297871863829%; } -.row-fluid > .span5 { + +.row-fluid .span5 { width: 40.425531911%; + *width: 40.3723404216383%; } -.row-fluid > .span4 { + +.row-fluid .span4 { width: 31.914893614%; + *width: 31.8617021246383%; } -.row-fluid > .span3 { + +.row-fluid .span3 { width: 23.404255317%; + *width: 23.3510638276383%; } -.row-fluid > .span2 { + +.row-fluid .span2 { width: 14.89361702%; + *width: 14.8404255306383%; } -.row-fluid > .span1 { + +.row-fluid .span1 { width: 6.382978723%; + *width: 6.329787233638298%; } + .container { - margin-left: auto; margin-right: auto; + margin-left: auto; *zoom: 1; } + .container:before, .container:after { display: table; content: ""; } + .container:after { clear: both; } + .container-fluid { - padding-left: 20px; padding-right: 20px; + padding-left: 20px; *zoom: 1; } + .container-fluid:before, .container-fluid:after { display: table; content: ""; } + .container-fluid:after { clear: both; } + p { margin: 0 0 9px; - font-family: "Helvetica Neue", Helvetica, Arial, sans-serif; - font-size: 13px; - line-height: 18px; } + p small { font-size: 11px; color: #999999; } + .lead { margin-bottom: 18px; font-size: 20px; font-weight: 200; line-height: 27px; } + h1, h2, h3, @@ -348,6 +448,7 @@ h6 { color: inherit; text-rendering: optimizelegibility; } + h1 small, h2 small, h3 small, @@ -357,227 +458,280 @@ h6 small { font-weight: normal; color: #999999; } + h1 { font-size: 30px; line-height: 36px; } + h1 small { font-size: 18px; } + h2 { font-size: 24px; line-height: 36px; } + h2 small { font-size: 18px; } + h3 { - line-height: 27px; font-size: 18px; + line-height: 27px; } + h3 small { font-size: 14px; } + h4, h5, h6 { line-height: 18px; } + h4 { font-size: 14px; } + h4 small { font-size: 12px; } + h5 { font-size: 12px; } + h6 { font-size: 11px; color: #999999; text-transform: uppercase; } + .page-header { padding-bottom: 17px; margin: 18px 0; border-bottom: 1px solid #eeeeee; } + .page-header h1 { line-height: 1; } + ul, ol { padding: 0; margin: 0 0 9px 25px; } + ul ul, ul ol, ol ol, ol ul { margin-bottom: 0; } + ul { list-style: disc; } + ol { list-style: decimal; } + li { line-height: 18px; } + ul.unstyled, ol.unstyled { margin-left: 0; list-style: none; } + dl { margin-bottom: 18px; } + dt, dd { line-height: 18px; } + dt { font-weight: bold; line-height: 17px; } + dd { margin-left: 9px; } + .dl-horizontal dt { float: left; - clear: left; width: 120px; + overflow: hidden; + clear: left; text-align: right; + text-overflow: ellipsis; + white-space: nowrap; } + .dl-horizontal dd { margin-left: 130px; } + hr { margin: 18px 0; border: 0; border-top: 1px solid #eeeeee; border-bottom: 1px solid #ffffff; } + strong { font-weight: bold; } + em { font-style: italic; } + .muted { color: #999999; } + abbr[title] { - border-bottom: 1px dotted #ddd; cursor: help; + border-bottom: 1px dotted #999999; } + abbr.initialism { font-size: 90%; text-transform: uppercase; } + blockquote { padding: 0 0 0 15px; margin: 0 0 18px; border-left: 5px solid #eeeeee; } + blockquote p { margin-bottom: 0; font-size: 16px; font-weight: 300; line-height: 22.5px; } + blockquote small { display: block; line-height: 18px; color: #999999; } + blockquote small:before { content: '\2014 \00A0'; } + blockquote.pull-right { float: right; - padding-left: 0; padding-right: 15px; - border-left: 0; + padding-left: 0; border-right: 5px solid #eeeeee; + border-left: 0; } + blockquote.pull-right p, blockquote.pull-right small { text-align: right; } + q:before, q:after, blockquote:before, blockquote:after { content: ""; } + address { display: block; margin-bottom: 18px; - line-height: 18px; font-style: normal; + line-height: 18px; } + small { font-size: 100%; } + cite { font-style: normal; } + code, pre { padding: 0 3px 2px; - font-family: Menlo, Monaco, "Courier New", monospace; + font-family: Menlo, Monaco, Consolas, "Courier New", monospace; font-size: 12px; color: #333333; -webkit-border-radius: 3px; - -moz-border-radius: 3px; - border-radius: 3px; + -moz-border-radius: 3px; + border-radius: 3px; } + code { padding: 2px 4px; color: #d14; background-color: #f7f7f9; border: 1px solid #e1e1e8; } + pre { display: block; padding: 8.5px; margin: 0 0 9px; font-size: 12.025px; line-height: 18px; + word-break: break-all; + word-wrap: break-word; + white-space: pre; + white-space: pre-wrap; background-color: #f5f5f5; border: 1px solid #ccc; border: 1px solid rgba(0, 0, 0, 0.15); -webkit-border-radius: 4px; - -moz-border-radius: 4px; - border-radius: 4px; - white-space: pre; - white-space: pre-wrap; - word-break: break-all; - word-wrap: break-word; + -moz-border-radius: 4px; + border-radius: 4px; } + pre.prettyprint { margin-bottom: 18px; } + pre code { padding: 0; color: inherit; background-color: transparent; border: 0; } + .pre-scrollable { max-height: 340px; overflow-y: scroll; } + form { margin: 0 0 18px; } + fieldset { padding: 0; margin: 0; border: 0; } + legend { display: block; width: 100%; @@ -587,12 +741,14 @@ legend { line-height: 36px; color: #333333; border: 0; - border-bottom: 1px solid #eee; + border-bottom: 1px solid #e5e5e5; } + legend small { font-size: 13.5px; color: #999999; } + label, input, button, @@ -602,82 +758,134 @@ textarea { font-weight: normal; line-height: 18px; } + input, button, select, textarea { font-family: "Helvetica Neue", Helvetica, Arial, sans-serif; } + label { display: block; margin-bottom: 5px; - color: #333333; } -input, -textarea, + select, +textarea, +input[type="text"], +input[type="password"], +input[type="datetime"], +input[type="datetime-local"], +input[type="date"], +input[type="month"], +input[type="time"], +input[type="week"], +input[type="number"], +input[type="email"], +input[type="url"], +input[type="search"], +input[type="tel"], +input[type="color"], .uneditable-input { display: inline-block; - width: 210px; height: 18px; padding: 4px; margin-bottom: 9px; font-size: 13px; line-height: 18px; color: #555555; +} + +input, +textarea { + width: 210px; +} + +textarea { + height: auto; +} + +textarea, +input[type="text"], +input[type="password"], +input[type="datetime"], +input[type="datetime-local"], +input[type="date"], +input[type="month"], +input[type="time"], +input[type="week"], +input[type="number"], +input[type="email"], +input[type="url"], +input[type="search"], +input[type="tel"], +input[type="color"], +.uneditable-input { + background-color: #ffffff; border: 1px solid #cccccc; -webkit-border-radius: 3px; - -moz-border-radius: 3px; - border-radius: 3px; + -moz-border-radius: 3px; + border-radius: 3px; + -webkit-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075); + -moz-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075); + box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075); + -webkit-transition: border linear 0.2s, box-shadow linear 0.2s; + -moz-transition: border linear 0.2s, box-shadow linear 0.2s; + -ms-transition: border linear 0.2s, box-shadow linear 0.2s; + -o-transition: border linear 0.2s, box-shadow linear 0.2s; + transition: border linear 0.2s, box-shadow linear 0.2s; } -.uneditable-textarea { - width: auto; - height: auto; + +textarea:focus, +input[type="text"]:focus, +input[type="password"]:focus, +input[type="datetime"]:focus, +input[type="datetime-local"]:focus, +input[type="date"]:focus, +input[type="month"]:focus, +input[type="time"]:focus, +input[type="week"]:focus, +input[type="number"]:focus, +input[type="email"]:focus, +input[type="url"]:focus, +input[type="search"]:focus, +input[type="tel"]:focus, +input[type="color"]:focus, +.uneditable-input:focus { + border-color: rgba(82, 168, 236, 0.8); + outline: 0; + outline: thin dotted \9; + /* IE6-9 */ + + -webkit-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 0 0 8px rgba(82, 168, 236, 0.6); + -moz-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 0 0 8px rgba(82, 168, 236, 0.6); + box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 0 0 8px rgba(82, 168, 236, 0.6); } -label input, -label textarea, -label select { - display: block; -} -input[type="image"], -input[type="checkbox"], -input[type="radio"] { - width: auto; - height: auto; - padding: 0; + +input[type="radio"], +input[type="checkbox"] { margin: 3px 0; *margin-top: 0; /* IE7 */ line-height: normal; cursor: pointer; - -webkit-border-radius: 0; - -moz-border-radius: 0; - border-radius: 0; - border: 0 \9; - /* IE9 and down */ +} -} -input[type="image"] { - border: 0; -} -input[type="file"] { - width: auto; - padding: initial; - line-height: initial; - border: initial; - background-color: #ffffff; - background-color: initial; - -webkit-box-shadow: none; - -moz-box-shadow: none; - box-shadow: none; -} -input[type="button"], +input[type="submit"], input[type="reset"], -input[type="submit"] { +input[type="button"], +input[type="radio"], +input[type="checkbox"] { + width: auto; +} + +.uneditable-textarea { width: auto; height: auto; } + select, input[type="file"] { height: 28px; @@ -688,41 +896,43 @@ input[type="file"] { line-height: 28px; } -input[type="file"] { - line-height: 18px \9; -} + select { width: 220px; - background-color: #ffffff; + border: 1px solid #bbb; } + select[multiple], select[size] { height: auto; } -input[type="image"] { - -webkit-box-shadow: none; - -moz-box-shadow: none; - box-shadow: none; -} -textarea { - height: auto; -} -input[type="hidden"] { - display: none; + +select:focus, +input[type="file"]:focus, +input[type="radio"]:focus, +input[type="checkbox"]:focus { + outline: thin dotted #333; + outline: 5px auto -webkit-focus-ring-color; + outline-offset: -2px; } + .radio, .checkbox { + min-height: 18px; padding-left: 18px; } + .radio input[type="radio"], .checkbox input[type="checkbox"] { float: left; margin-left: -18px; } + .controls > .radio:first-child, .controls > .checkbox:first-child { padding-top: 5px; } + .radio.inline, .checkbox.inline { display: inline-block; @@ -730,290 +940,368 @@ input[type="hidden"] { margin-bottom: 0; vertical-align: middle; } + .radio.inline + .radio.inline, .checkbox.inline + .checkbox.inline { margin-left: 10px; } -input, -textarea { - -webkit-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075); - -moz-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075); - box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075); - -webkit-transition: border linear 0.2s, box-shadow linear 0.2s; - -moz-transition: border linear 0.2s, box-shadow linear 0.2s; - -ms-transition: border linear 0.2s, box-shadow linear 0.2s; - -o-transition: border linear 0.2s, box-shadow linear 0.2s; - transition: border linear 0.2s, box-shadow linear 0.2s; -} -input:focus, -textarea:focus { - border-color: rgba(82, 168, 236, 0.8); - -webkit-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 0 0 8px rgba(82, 168, 236, 0.6); - -moz-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 0 0 8px rgba(82, 168, 236, 0.6); - box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 0 0 8px rgba(82, 168, 236, 0.6); - outline: 0; - outline: thin dotted \9; - /* IE6-9 */ -} -input[type="file"]:focus, -input[type="radio"]:focus, -input[type="checkbox"]:focus, -select:focus { - -webkit-box-shadow: none; - -moz-box-shadow: none; - box-shadow: none; - outline: thin dotted #333; - outline: 5px auto -webkit-focus-ring-color; - outline-offset: -2px; -} .input-mini { width: 60px; } + .input-small { width: 90px; } + .input-medium { width: 150px; } + .input-large { width: 210px; } + .input-xlarge { width: 270px; } + .input-xxlarge { width: 530px; } + input[class*="span"], select[class*="span"], textarea[class*="span"], -.uneditable-input { +.uneditable-input[class*="span"], +.row-fluid input[class*="span"], +.row-fluid select[class*="span"], +.row-fluid textarea[class*="span"], +.row-fluid .uneditable-input[class*="span"] { float: none; margin-left: 0; } + +.input-append input[class*="span"], +.input-append .uneditable-input[class*="span"], +.input-prepend input[class*="span"], +.input-prepend .uneditable-input[class*="span"], +.row-fluid .input-prepend [class*="span"], +.row-fluid .input-append [class*="span"] { + display: inline-block; +} + input, textarea, .uneditable-input { margin-left: 0; } -input.span12, textarea.span12, .uneditable-input.span12 { + +input.span12, +textarea.span12, +.uneditable-input.span12 { width: 930px; } -input.span11, textarea.span11, .uneditable-input.span11 { + +input.span11, +textarea.span11, +.uneditable-input.span11 { width: 850px; } -input.span10, textarea.span10, .uneditable-input.span10 { + +input.span10, +textarea.span10, +.uneditable-input.span10 { width: 770px; } -input.span9, textarea.span9, .uneditable-input.span9 { + +input.span9, +textarea.span9, +.uneditable-input.span9 { width: 690px; } -input.span8, textarea.span8, .uneditable-input.span8 { + +input.span8, +textarea.span8, +.uneditable-input.span8 { width: 610px; } -input.span7, textarea.span7, .uneditable-input.span7 { + +input.span7, +textarea.span7, +.uneditable-input.span7 { width: 530px; } -input.span6, textarea.span6, .uneditable-input.span6 { + +input.span6, +textarea.span6, +.uneditable-input.span6 { width: 450px; } -input.span5, textarea.span5, .uneditable-input.span5 { + +input.span5, +textarea.span5, +.uneditable-input.span5 { width: 370px; } -input.span4, textarea.span4, .uneditable-input.span4 { + +input.span4, +textarea.span4, +.uneditable-input.span4 { width: 290px; } -input.span3, textarea.span3, .uneditable-input.span3 { + +input.span3, +textarea.span3, +.uneditable-input.span3 { width: 210px; } -input.span2, textarea.span2, .uneditable-input.span2 { + +input.span2, +textarea.span2, +.uneditable-input.span2 { width: 130px; } -input.span1, textarea.span1, .uneditable-input.span1 { + +input.span1, +textarea.span1, +.uneditable-input.span1 { width: 50px; } + input[disabled], select[disabled], textarea[disabled], input[readonly], select[readonly], textarea[readonly] { + cursor: not-allowed; background-color: #eeeeee; border-color: #ddd; - cursor: not-allowed; } + +input[type="radio"][disabled], +input[type="checkbox"][disabled], +input[type="radio"][readonly], +input[type="checkbox"][readonly] { + background-color: transparent; +} + .control-group.warning > label, .control-group.warning .help-block, .control-group.warning .help-inline { color: #c09853; } + +.control-group.warning .checkbox, +.control-group.warning .radio, .control-group.warning input, .control-group.warning select, .control-group.warning textarea { color: #c09853; border-color: #c09853; } + +.control-group.warning .checkbox:focus, +.control-group.warning .radio:focus, .control-group.warning input:focus, .control-group.warning select:focus, .control-group.warning textarea:focus { border-color: #a47e3c; -webkit-box-shadow: 0 0 6px #dbc59e; - -moz-box-shadow: 0 0 6px #dbc59e; - box-shadow: 0 0 6px #dbc59e; + -moz-box-shadow: 0 0 6px #dbc59e; + box-shadow: 0 0 6px #dbc59e; } + .control-group.warning .input-prepend .add-on, .control-group.warning .input-append .add-on { color: #c09853; background-color: #fcf8e3; border-color: #c09853; } + .control-group.error > label, .control-group.error .help-block, .control-group.error .help-inline { color: #b94a48; } + +.control-group.error .checkbox, +.control-group.error .radio, .control-group.error input, .control-group.error select, .control-group.error textarea { color: #b94a48; border-color: #b94a48; } + +.control-group.error .checkbox:focus, +.control-group.error .radio:focus, .control-group.error input:focus, .control-group.error select:focus, .control-group.error textarea:focus { border-color: #953b39; -webkit-box-shadow: 0 0 6px #d59392; - -moz-box-shadow: 0 0 6px #d59392; - box-shadow: 0 0 6px #d59392; + -moz-box-shadow: 0 0 6px #d59392; + box-shadow: 0 0 6px #d59392; } + .control-group.error .input-prepend .add-on, .control-group.error .input-append .add-on { color: #b94a48; background-color: #f2dede; border-color: #b94a48; } + .control-group.success > label, .control-group.success .help-block, .control-group.success .help-inline { color: #468847; } + +.control-group.success .checkbox, +.control-group.success .radio, .control-group.success input, .control-group.success select, .control-group.success textarea { color: #468847; border-color: #468847; } + +.control-group.success .checkbox:focus, +.control-group.success .radio:focus, .control-group.success input:focus, .control-group.success select:focus, .control-group.success textarea:focus { border-color: #356635; -webkit-box-shadow: 0 0 6px #7aba7b; - -moz-box-shadow: 0 0 6px #7aba7b; - box-shadow: 0 0 6px #7aba7b; + -moz-box-shadow: 0 0 6px #7aba7b; + box-shadow: 0 0 6px #7aba7b; } + .control-group.success .input-prepend .add-on, .control-group.success .input-append .add-on { color: #468847; background-color: #dff0d8; border-color: #468847; } + input:focus:required:invalid, textarea:focus:required:invalid, select:focus:required:invalid { color: #b94a48; border-color: #ee5f5b; } + input:focus:required:invalid:focus, textarea:focus:required:invalid:focus, select:focus:required:invalid:focus { border-color: #e9322d; -webkit-box-shadow: 0 0 6px #f8b9b7; - -moz-box-shadow: 0 0 6px #f8b9b7; - box-shadow: 0 0 6px #f8b9b7; + -moz-box-shadow: 0 0 6px #f8b9b7; + box-shadow: 0 0 6px #f8b9b7; } + .form-actions { padding: 17px 20px 18px; margin-top: 18px; margin-bottom: 18px; - background-color: #eeeeee; - border-top: 1px solid #ddd; + background-color: #f5f5f5; + border-top: 1px solid #e5e5e5; *zoom: 1; } + .form-actions:before, .form-actions:after { display: table; content: ""; } + .form-actions:after { clear: both; } + .uneditable-input { - display: block; + overflow: hidden; + white-space: nowrap; + cursor: not-allowed; background-color: #ffffff; border-color: #eee; -webkit-box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.025); - -moz-box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.025); - box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.025); - cursor: not-allowed; + -moz-box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.025); + box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.025); } + :-moz-placeholder { color: #999999; } + +:-ms-input-placeholder { + color: #999999; +} + ::-webkit-input-placeholder { color: #999999; } + .help-block, .help-inline { color: #555555; } + .help-block { display: block; margin-bottom: 9px; } + .help-inline { display: inline-block; *display: inline; - /* IE7 inline-block hack */ - - *zoom: 1; - vertical-align: middle; padding-left: 5px; + vertical-align: middle; + *zoom: 1; } + .input-prepend, .input-append { margin-bottom: 5px; } + .input-prepend input, .input-append input, .input-prepend select, .input-append select, .input-prepend .uneditable-input, .input-append .uneditable-input { + position: relative; + margin-bottom: 0; *margin-left: 0; + vertical-align: middle; -webkit-border-radius: 0 3px 3px 0; - -moz-border-radius: 0 3px 3px 0; - border-radius: 0 3px 3px 0; + -moz-border-radius: 0 3px 3px 0; + border-radius: 0 3px 3px 0; } + .input-prepend input:focus, .input-append input:focus, .input-prepend select:focus, .input-append select:focus, .input-prepend .uneditable-input:focus, .input-append .uneditable-input:focus { - position: relative; z-index: 2; } + .input-prepend .uneditable-input, .input-append .uneditable-input { border-left-color: #ccc; } + .input-prepend .add-on, .input-append .add-on { display: inline-block; width: auto; - min-width: 16px; height: 18px; + min-width: 16px; padding: 4px 5px; font-weight: normal; line-height: 18px; @@ -1023,69 +1311,92 @@ select:focus:required:invalid:focus { background-color: #eeeeee; border: 1px solid #ccc; } + .input-prepend .add-on, .input-append .add-on, .input-prepend .btn, .input-append .btn { - -webkit-border-radius: 3px 0 0 3px; - -moz-border-radius: 3px 0 0 3px; - border-radius: 3px 0 0 3px; + margin-left: -1px; + -webkit-border-radius: 0; + -moz-border-radius: 0; + border-radius: 0; } + .input-prepend .active, .input-append .active { background-color: #a9dba9; border-color: #46a546; } + .input-prepend .add-on, .input-prepend .btn { margin-right: -1px; } -.input-append input, -.input-append select .uneditable-input { + +.input-prepend .add-on:first-child, +.input-prepend .btn:first-child { -webkit-border-radius: 3px 0 0 3px; - -moz-border-radius: 3px 0 0 3px; - border-radius: 3px 0 0 3px; + -moz-border-radius: 3px 0 0 3px; + border-radius: 3px 0 0 3px; } + +.input-append input, +.input-append select, +.input-append .uneditable-input { + -webkit-border-radius: 3px 0 0 3px; + -moz-border-radius: 3px 0 0 3px; + border-radius: 3px 0 0 3px; +} + .input-append .uneditable-input { - border-left-color: #eee; border-right-color: #ccc; + border-left-color: #eee; } -.input-append .add-on, -.input-append .btn { - margin-left: -1px; + +.input-append .add-on:last-child, +.input-append .btn:last-child { -webkit-border-radius: 0 3px 3px 0; - -moz-border-radius: 0 3px 3px 0; - border-radius: 0 3px 3px 0; + -moz-border-radius: 0 3px 3px 0; + border-radius: 0 3px 3px 0; } + .input-prepend.input-append input, .input-prepend.input-append select, .input-prepend.input-append .uneditable-input { -webkit-border-radius: 0; - -moz-border-radius: 0; - border-radius: 0; + -moz-border-radius: 0; + border-radius: 0; } + .input-prepend.input-append .add-on:first-child, .input-prepend.input-append .btn:first-child { margin-right: -1px; -webkit-border-radius: 3px 0 0 3px; - -moz-border-radius: 3px 0 0 3px; - border-radius: 3px 0 0 3px; + -moz-border-radius: 3px 0 0 3px; + border-radius: 3px 0 0 3px; } + .input-prepend.input-append .add-on:last-child, .input-prepend.input-append .btn:last-child { margin-left: -1px; -webkit-border-radius: 0 3px 3px 0; - -moz-border-radius: 0 3px 3px 0; - border-radius: 0 3px 3px 0; + -moz-border-radius: 0 3px 3px 0; + border-radius: 0 3px 3px 0; } + .search-query { - padding-left: 14px; padding-right: 14px; + padding-right: 4px \9; + padding-left: 14px; + padding-left: 4px \9; + /* IE7-8 doesn't have border-radius, so don't indent the padding */ + margin-bottom: 0; -webkit-border-radius: 14px; - -moz-border-radius: 14px; - border-radius: 14px; + -moz-border-radius: 14px; + border-radius: 14px; } + .form-search input, .form-inline input, .form-horizontal input, @@ -1108,23 +1419,29 @@ select:focus:required:invalid:focus { .form-inline .input-append, .form-horizontal .input-append { display: inline-block; + *display: inline; margin-bottom: 0; + *zoom: 1; } + .form-search .hide, .form-inline .hide, .form-horizontal .hide { display: none; } + .form-search label, .form-inline label { display: inline-block; } + .form-search .input-append, .form-inline .input-append, .form-search .input-prepend, .form-inline .input-prepend { margin-bottom: 0; } + .form-search .radio, .form-search .checkbox, .form-inline .radio, @@ -1133,64 +1450,79 @@ select:focus:required:invalid:focus { margin-bottom: 0; vertical-align: middle; } + .form-search .radio input[type="radio"], .form-search .checkbox input[type="checkbox"], .form-inline .radio input[type="radio"], .form-inline .checkbox input[type="checkbox"] { float: left; - margin-left: 0; margin-right: 3px; + margin-left: 0; } + .control-group { margin-bottom: 9px; } + legend + .control-group { margin-top: 18px; -webkit-margin-top-collapse: separate; } + .form-horizontal .control-group { margin-bottom: 18px; *zoom: 1; } + .form-horizontal .control-group:before, .form-horizontal .control-group:after { display: table; content: ""; } + .form-horizontal .control-group:after { clear: both; } + .form-horizontal .control-label { float: left; width: 140px; padding-top: 5px; text-align: right; } -.form-horizontal .controls { - margin-left: 160px; - /* Super jank IE7 fix to ensure the inputs in .input-append and input-prepend don't inherit the margin of the parent, in this case .controls */ +.form-horizontal .controls { *display: inline-block; - *margin-left: 0; *padding-left: 20px; + margin-left: 160px; + *margin-left: 0; } + +.form-horizontal .controls:first-child { + *padding-left: 160px; +} + .form-horizontal .help-block { margin-top: 9px; margin-bottom: 0; } + .form-horizontal .form-actions { padding-left: 160px; } + table { max-width: 100%; + background-color: transparent; border-collapse: collapse; border-spacing: 0; - background-color: transparent; } + .table { width: 100%; margin-bottom: 18px; } + .table th, .table td { padding: 8px; @@ -1199,646 +1531,907 @@ table { vertical-align: top; border-top: 1px solid #dddddd; } + .table th { font-weight: bold; } + .table thead th { vertical-align: bottom; } + +.table caption + thead tr:first-child th, +.table caption + thead tr:first-child td, .table colgroup + thead tr:first-child th, .table colgroup + thead tr:first-child td, .table thead:first-child tr:first-child th, .table thead:first-child tr:first-child td { border-top: 0; } + .table tbody + tbody { border-top: 2px solid #dddddd; } + .table-condensed th, .table-condensed td { padding: 4px 5px; } + .table-bordered { border: 1px solid #dddddd; - border-left: 0; border-collapse: separate; *border-collapse: collapsed; + border-left: 0; -webkit-border-radius: 4px; - -moz-border-radius: 4px; - border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; } + .table-bordered th, .table-bordered td { border-left: 1px solid #dddddd; } + +.table-bordered caption + thead tr:first-child th, +.table-bordered caption + tbody tr:first-child th, +.table-bordered caption + tbody tr:first-child td, +.table-bordered colgroup + thead tr:first-child th, +.table-bordered colgroup + tbody tr:first-child th, +.table-bordered colgroup + tbody tr:first-child td, .table-bordered thead:first-child tr:first-child th, .table-bordered tbody:first-child tr:first-child th, .table-bordered tbody:first-child tr:first-child td { border-top: 0; } + .table-bordered thead:first-child tr:first-child th:first-child, .table-bordered tbody:first-child tr:first-child td:first-child { - -webkit-border-radius: 4px 0 0 0; - -moz-border-radius: 4px 0 0 0; - border-radius: 4px 0 0 0; + -webkit-border-top-left-radius: 4px; + border-top-left-radius: 4px; + -moz-border-radius-topleft: 4px; } + .table-bordered thead:first-child tr:first-child th:last-child, .table-bordered tbody:first-child tr:first-child td:last-child { - -webkit-border-radius: 0 4px 0 0; - -moz-border-radius: 0 4px 0 0; - border-radius: 0 4px 0 0; + -webkit-border-top-right-radius: 4px; + border-top-right-radius: 4px; + -moz-border-radius-topright: 4px; } + .table-bordered thead:last-child tr:last-child th:first-child, .table-bordered tbody:last-child tr:last-child td:first-child { -webkit-border-radius: 0 0 0 4px; - -moz-border-radius: 0 0 0 4px; - border-radius: 0 0 0 4px; + -moz-border-radius: 0 0 0 4px; + border-radius: 0 0 0 4px; + -webkit-border-bottom-left-radius: 4px; + border-bottom-left-radius: 4px; + -moz-border-radius-bottomleft: 4px; } + .table-bordered thead:last-child tr:last-child th:last-child, .table-bordered tbody:last-child tr:last-child td:last-child { - -webkit-border-radius: 0 0 4px 0; - -moz-border-radius: 0 0 4px 0; - border-radius: 0 0 4px 0; + -webkit-border-bottom-right-radius: 4px; + border-bottom-right-radius: 4px; + -moz-border-radius-bottomright: 4px; } + .table-striped tbody tr:nth-child(odd) td, .table-striped tbody tr:nth-child(odd) th { background-color: #f9f9f9; } + .table tbody tr:hover td, .table tbody tr:hover th { background-color: #f5f5f5; } + table .span1 { float: none; width: 44px; margin-left: 0; } + table .span2 { float: none; width: 124px; margin-left: 0; } + table .span3 { float: none; width: 204px; margin-left: 0; } + table .span4 { float: none; width: 284px; margin-left: 0; } + table .span5 { float: none; width: 364px; margin-left: 0; } + table .span6 { float: none; width: 444px; margin-left: 0; } + table .span7 { float: none; width: 524px; margin-left: 0; } + table .span8 { float: none; width: 604px; margin-left: 0; } + table .span9 { float: none; width: 684px; margin-left: 0; } + table .span10 { float: none; width: 764px; margin-left: 0; } + table .span11 { float: none; width: 844px; margin-left: 0; } + table .span12 { float: none; width: 924px; margin-left: 0; } + table .span13 { float: none; width: 1004px; margin-left: 0; } + table .span14 { float: none; width: 1084px; margin-left: 0; } + table .span15 { float: none; width: 1164px; margin-left: 0; } + table .span16 { float: none; width: 1244px; margin-left: 0; } + table .span17 { float: none; width: 1324px; margin-left: 0; } + table .span18 { float: none; width: 1404px; margin-left: 0; } + table .span19 { float: none; width: 1484px; margin-left: 0; } + table .span20 { float: none; width: 1564px; margin-left: 0; } + table .span21 { float: none; width: 1644px; margin-left: 0; } + table .span22 { float: none; width: 1724px; margin-left: 0; } + table .span23 { float: none; width: 1804px; margin-left: 0; } + table .span24 { float: none; width: 1884px; margin-left: 0; } + [class^="icon-"], [class*=" icon-"] { display: inline-block; width: 14px; height: 14px; + *margin-right: .3em; line-height: 14px; vertical-align: text-top; - background-image: url("/static/img/glyphicons-halflings.png"); + background-image: url("../img/glyphicons-halflings.png"); background-position: 14px 14px; background-repeat: no-repeat; - *margin-right: .3em; } + [class^="icon-"]:last-child, [class*=" icon-"]:last-child { *margin-left: 0; } + .icon-white { - background-image: url("/static/img/glyphicons-halflings-white.png"); + background-image: url("../img/glyphicons-halflings-white.png"); } + .icon-glass { background-position: 0 0; } + .icon-music { background-position: -24px 0; } + .icon-search { background-position: -48px 0; } + .icon-envelope { background-position: -72px 0; } + .icon-heart { background-position: -96px 0; } + .icon-star { background-position: -120px 0; } + .icon-star-empty { background-position: -144px 0; } + .icon-user { background-position: -168px 0; } + .icon-film { background-position: -192px 0; } + .icon-th-large { background-position: -216px 0; } + .icon-th { background-position: -240px 0; } + .icon-th-list { background-position: -264px 0; } + .icon-ok { background-position: -288px 0; } + .icon-remove { background-position: -312px 0; } + .icon-zoom-in { background-position: -336px 0; } + .icon-zoom-out { background-position: -360px 0; } + .icon-off { background-position: -384px 0; } + .icon-signal { background-position: -408px 0; } + .icon-cog { background-position: -432px 0; } + .icon-trash { background-position: -456px 0; } + .icon-home { background-position: 0 -24px; } + .icon-file { background-position: -24px -24px; } + .icon-time { background-position: -48px -24px; } + .icon-road { background-position: -72px -24px; } + .icon-download-alt { background-position: -96px -24px; } + .icon-download { background-position: -120px -24px; } + .icon-upload { background-position: -144px -24px; } + .icon-inbox { background-position: -168px -24px; } + .icon-play-circle { background-position: -192px -24px; } + .icon-repeat { background-position: -216px -24px; } + .icon-refresh { background-position: -240px -24px; } + .icon-list-alt { background-position: -264px -24px; } + .icon-lock { background-position: -287px -24px; } + .icon-flag { background-position: -312px -24px; } + .icon-headphones { background-position: -336px -24px; } + .icon-volume-off { background-position: -360px -24px; } + .icon-volume-down { background-position: -384px -24px; } + .icon-volume-up { background-position: -408px -24px; } + .icon-qrcode { background-position: -432px -24px; } + .icon-barcode { background-position: -456px -24px; } + .icon-tag { background-position: 0 -48px; } + .icon-tags { background-position: -25px -48px; } + .icon-book { background-position: -48px -48px; } + .icon-bookmark { background-position: -72px -48px; } + .icon-print { background-position: -96px -48px; } + .icon-camera { background-position: -120px -48px; } + .icon-font { background-position: -144px -48px; } + .icon-bold { background-position: -167px -48px; } + .icon-italic { background-position: -192px -48px; } + .icon-text-height { background-position: -216px -48px; } + .icon-text-width { background-position: -240px -48px; } + .icon-align-left { background-position: -264px -48px; } + .icon-align-center { background-position: -288px -48px; } + .icon-align-right { background-position: -312px -48px; } + .icon-align-justify { background-position: -336px -48px; } + .icon-list { background-position: -360px -48px; } + .icon-indent-left { background-position: -384px -48px; } + .icon-indent-right { background-position: -408px -48px; } + .icon-facetime-video { background-position: -432px -48px; } + .icon-picture { background-position: -456px -48px; } + .icon-pencil { background-position: 0 -72px; } + .icon-map-marker { background-position: -24px -72px; } + .icon-adjust { background-position: -48px -72px; } + .icon-tint { background-position: -72px -72px; } + .icon-edit { background-position: -96px -72px; } + .icon-share { background-position: -120px -72px; } + .icon-check { background-position: -144px -72px; } + .icon-move { background-position: -168px -72px; } + .icon-step-backward { background-position: -192px -72px; } + .icon-fast-backward { background-position: -216px -72px; } + .icon-backward { background-position: -240px -72px; } + .icon-play { background-position: -264px -72px; } + .icon-pause { background-position: -288px -72px; } + .icon-stop { background-position: -312px -72px; } + .icon-forward { background-position: -336px -72px; } + .icon-fast-forward { background-position: -360px -72px; } + .icon-step-forward { background-position: -384px -72px; } + .icon-eject { background-position: -408px -72px; } + .icon-chevron-left { background-position: -432px -72px; } + .icon-chevron-right { background-position: -456px -72px; } + .icon-plus-sign { background-position: 0 -96px; } + .icon-minus-sign { background-position: -24px -96px; } + .icon-remove-sign { background-position: -48px -96px; } + .icon-ok-sign { background-position: -72px -96px; } + .icon-question-sign { background-position: -96px -96px; } + .icon-info-sign { background-position: -120px -96px; } + .icon-screenshot { background-position: -144px -96px; } + .icon-remove-circle { background-position: -168px -96px; } + .icon-ok-circle { background-position: -192px -96px; } + .icon-ban-circle { background-position: -216px -96px; } + .icon-arrow-left { background-position: -240px -96px; } + .icon-arrow-right { background-position: -264px -96px; } + .icon-arrow-up { background-position: -289px -96px; } + .icon-arrow-down { background-position: -312px -96px; } + .icon-share-alt { background-position: -336px -96px; } + .icon-resize-full { background-position: -360px -96px; } + .icon-resize-small { background-position: -384px -96px; } + .icon-plus { background-position: -408px -96px; } + .icon-minus { background-position: -433px -96px; } + .icon-asterisk { background-position: -456px -96px; } + .icon-exclamation-sign { background-position: 0 -120px; } + .icon-gift { background-position: -24px -120px; } + .icon-leaf { background-position: -48px -120px; } + .icon-fire { background-position: -72px -120px; } + .icon-eye-open { background-position: -96px -120px; } + .icon-eye-close { background-position: -120px -120px; } + .icon-warning-sign { background-position: -144px -120px; } + .icon-plane { background-position: -168px -120px; } + .icon-calendar { background-position: -192px -120px; } + .icon-random { background-position: -216px -120px; } + .icon-comment { background-position: -240px -120px; } + .icon-magnet { background-position: -264px -120px; } + .icon-chevron-up { background-position: -288px -120px; } + .icon-chevron-down { background-position: -313px -119px; } + .icon-retweet { background-position: -336px -120px; } + .icon-shopping-cart { background-position: -360px -120px; } + .icon-folder-close { background-position: -384px -120px; } + .icon-folder-open { background-position: -408px -120px; } + .icon-resize-vertical { background-position: -432px -119px; } + .icon-resize-horizontal { background-position: -456px -118px; } + +.icon-hdd { + background-position: 0 -144px; +} + +.icon-bullhorn { + background-position: -24px -144px; +} + +.icon-bell { + background-position: -48px -144px; +} + +.icon-certificate { + background-position: -72px -144px; +} + +.icon-thumbs-up { + background-position: -96px -144px; +} + +.icon-thumbs-down { + background-position: -120px -144px; +} + +.icon-hand-right { + background-position: -144px -144px; +} + +.icon-hand-left { + background-position: -168px -144px; +} + +.icon-hand-up { + background-position: -192px -144px; +} + +.icon-hand-down { + background-position: -216px -144px; +} + +.icon-circle-arrow-right { + background-position: -240px -144px; +} + +.icon-circle-arrow-left { + background-position: -264px -144px; +} + +.icon-circle-arrow-up { + background-position: -288px -144px; +} + +.icon-circle-arrow-down { + background-position: -312px -144px; +} + +.icon-globe { + background-position: -336px -144px; +} + +.icon-wrench { + background-position: -360px -144px; +} + +.icon-tasks { + background-position: -384px -144px; +} + +.icon-filter { + background-position: -408px -144px; +} + +.icon-briefcase { + background-position: -432px -144px; +} + +.icon-fullscreen { + background-position: -456px -144px; +} + +.dropup, .dropdown { position: relative; } + .dropdown-toggle { *margin-bottom: -3px; } + .dropdown-toggle:active, .open .dropdown-toggle { outline: 0; } + .caret { display: inline-block; width: 0; height: 0; vertical-align: top; - border-left: 4px solid transparent; - border-right: 4px solid transparent; border-top: 4px solid #000000; + border-right: 4px solid transparent; + border-left: 4px solid transparent; + content: ""; opacity: 0.3; filter: alpha(opacity=30); - content: ""; } + .dropdown .caret { margin-top: 8px; margin-left: 2px; } + .dropdown:hover .caret, -.open.dropdown .caret { +.open .caret { opacity: 1; filter: alpha(opacity=100); } + .dropdown-menu { position: absolute; top: 100%; left: 0; z-index: 1000; - float: left; display: none; + float: left; min-width: 160px; padding: 4px 0; - margin: 0; + margin: 1px 0 0; list-style: none; background-color: #ffffff; - border-color: #ccc; - border-color: rgba(0, 0, 0, 0.2); - border-style: solid; - border-width: 1px; - -webkit-border-radius: 0 0 5px 5px; - -moz-border-radius: 0 0 5px 5px; - border-radius: 0 0 5px 5px; - -webkit-box-shadow: 0 5px 10px rgba(0, 0, 0, 0.2); - -moz-box-shadow: 0 5px 10px rgba(0, 0, 0, 0.2); - box-shadow: 0 5px 10px rgba(0, 0, 0, 0.2); - -webkit-background-clip: padding-box; - -moz-background-clip: padding; - background-clip: padding-box; + border: 1px solid #ccc; + border: 1px solid rgba(0, 0, 0, 0.2); *border-right-width: 2px; *border-bottom-width: 2px; + -webkit-border-radius: 5px; + -moz-border-radius: 5px; + border-radius: 5px; + -webkit-box-shadow: 0 5px 10px rgba(0, 0, 0, 0.2); + -moz-box-shadow: 0 5px 10px rgba(0, 0, 0, 0.2); + box-shadow: 0 5px 10px rgba(0, 0, 0, 0.2); + -webkit-background-clip: padding-box; + -moz-background-clip: padding; + background-clip: padding-box; } + .dropdown-menu.pull-right { right: 0; left: auto; } + .dropdown-menu .divider { + *width: 100%; height: 1px; margin: 8px 1px; + *margin: -5px 0 5px; overflow: hidden; background-color: #e5e5e5; border-bottom: 1px solid #ffffff; - *width: 100%; - *margin: -5px 0 5px; } + .dropdown-menu a { display: block; padding: 3px 15px; @@ -1848,6 +2441,7 @@ table .span24 { color: #333333; white-space: nowrap; } + .dropdown-menu li > a:hover, .dropdown-menu .active > a, .dropdown-menu .active > a:hover { @@ -1855,39 +2449,41 @@ table .span24 { text-decoration: none; background-color: #0088cc; } -.dropdown.open { + +.open { *z-index: 1000; } -.dropdown.open .dropdown-toggle { - color: #ffffff; - background: #ccc; - background: rgba(0, 0, 0, 0.3); -} -.dropdown.open .dropdown-menu { + +.open > .dropdown-menu { display: block; } -.pull-right .dropdown-menu { - left: auto; + +.pull-right > .dropdown-menu { right: 0; + left: auto; } + .dropup .caret, .navbar-fixed-bottom .dropdown .caret { border-top: 0; border-bottom: 4px solid #000000; content: "\2191"; } + .dropup .dropdown-menu, .navbar-fixed-bottom .dropdown .dropdown-menu { top: auto; bottom: 100%; margin-bottom: 1px; } + .typeahead { margin-top: 2px; -webkit-border-radius: 4px; - -moz-border-radius: 4px; - border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; } + .well { min-height: 20px; padding: 19px; @@ -1896,52 +2492,60 @@ table .span24 { border: 1px solid #eee; border: 1px solid rgba(0, 0, 0, 0.05); -webkit-border-radius: 4px; - -moz-border-radius: 4px; - border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; -webkit-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.05); - -moz-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.05); - box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.05); + -moz-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.05); + box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.05); } + .well blockquote { border-color: #ddd; border-color: rgba(0, 0, 0, 0.15); } + .well-large { padding: 24px; -webkit-border-radius: 6px; - -moz-border-radius: 6px; - border-radius: 6px; + -moz-border-radius: 6px; + border-radius: 6px; } + .well-small { padding: 9px; -webkit-border-radius: 3px; - -moz-border-radius: 3px; - border-radius: 3px; + -moz-border-radius: 3px; + border-radius: 3px; } + .fade { - -webkit-transition: opacity 0.15s linear; - -moz-transition: opacity 0.15s linear; - -ms-transition: opacity 0.15s linear; - -o-transition: opacity 0.15s linear; - transition: opacity 0.15s linear; opacity: 0; + -webkit-transition: opacity 0.15s linear; + -moz-transition: opacity 0.15s linear; + -ms-transition: opacity 0.15s linear; + -o-transition: opacity 0.15s linear; + transition: opacity 0.15s linear; } + .fade.in { opacity: 1; } + .collapse { - -webkit-transition: height 0.35s ease; - -moz-transition: height 0.35s ease; - -ms-transition: height 0.35s ease; - -o-transition: height 0.35s ease; - transition: height 0.35s ease; position: relative; - overflow: hidden; height: 0; + overflow: hidden; + -webkit-transition: height 0.35s ease; + -moz-transition: height 0.35s ease; + -ms-transition: height 0.35s ease; + -o-transition: height 0.35s ease; + transition: height 0.35s ease; } + .collapse.in { height: auto; } + .close { float: right; font-size: 20px; @@ -1952,125 +2556,153 @@ table .span24 { opacity: 0.2; filter: alpha(opacity=20); } + .close:hover { color: #000000; text-decoration: none; + cursor: pointer; opacity: 0.4; filter: alpha(opacity=40); - cursor: pointer; } + +button.close { + padding: 0; + cursor: pointer; + background: transparent; + border: 0; + -webkit-appearance: none; +} + .btn { display: inline-block; *display: inline; - /* IE7 inline-block hack */ - - *zoom: 1; padding: 4px 10px 4px; margin-bottom: 0; + *margin-left: .3em; font-size: 13px; line-height: 18px; + *line-height: 20px; color: #333333; text-align: center; text-shadow: 0 1px 1px rgba(255, 255, 255, 0.75); vertical-align: middle; + cursor: pointer; background-color: #f5f5f5; - background-image: -moz-linear-gradient(top, #ffffff, #e6e6e6); + *background-color: #e6e6e6; background-image: -ms-linear-gradient(top, #ffffff, #e6e6e6); background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#ffffff), to(#e6e6e6)); background-image: -webkit-linear-gradient(top, #ffffff, #e6e6e6); background-image: -o-linear-gradient(top, #ffffff, #e6e6e6); background-image: linear-gradient(top, #ffffff, #e6e6e6); + background-image: -moz-linear-gradient(top, #ffffff, #e6e6e6); background-repeat: repeat-x; - filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#ffffff', endColorstr='#e6e6e6', GradientType=0); - border-color: #e6e6e6 #e6e6e6 #bfbfbf; - border-color: rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.25); - filter: progid:dximagetransform.microsoft.gradient(enabled=false); border: 1px solid #cccccc; + *border: 0; + border-color: rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.25); + border-color: #e6e6e6 #e6e6e6 #bfbfbf; border-bottom-color: #b3b3b3; -webkit-border-radius: 4px; - -moz-border-radius: 4px; - border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; + filter: progid:dximagetransform.microsoft.gradient(startColorstr='#ffffff', endColorstr='#e6e6e6', GradientType=0); + filter: progid:dximagetransform.microsoft.gradient(enabled=false); + *zoom: 1; -webkit-box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.2), 0 1px 2px rgba(0, 0, 0, 0.05); - -moz-box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.2), 0 1px 2px rgba(0, 0, 0, 0.05); - box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.2), 0 1px 2px rgba(0, 0, 0, 0.05); - cursor: pointer; - *margin-left: .3em; + -moz-box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.2), 0 1px 2px rgba(0, 0, 0, 0.05); + box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.2), 0 1px 2px rgba(0, 0, 0, 0.05); } + .btn:hover, .btn:active, .btn.active, .btn.disabled, .btn[disabled] { background-color: #e6e6e6; + *background-color: #d9d9d9; } + .btn:active, .btn.active { background-color: #cccccc \9; } + .btn:first-child { *margin-left: 0; } + .btn:hover { color: #333333; text-decoration: none; background-color: #e6e6e6; + *background-color: #d9d9d9; + /* Buttons in IE7 don't get borders, so darken on hover */ + background-position: 0 -15px; -webkit-transition: background-position 0.1s linear; - -moz-transition: background-position 0.1s linear; - -ms-transition: background-position 0.1s linear; - -o-transition: background-position 0.1s linear; - transition: background-position 0.1s linear; + -moz-transition: background-position 0.1s linear; + -ms-transition: background-position 0.1s linear; + -o-transition: background-position 0.1s linear; + transition: background-position 0.1s linear; } + .btn:focus { outline: thin dotted #333; outline: 5px auto -webkit-focus-ring-color; outline-offset: -2px; } + .btn.active, .btn:active { - background-image: none; - -webkit-box-shadow: inset 0 2px 4px rgba(0, 0, 0, 0.15), 0 1px 2px rgba(0, 0, 0, 0.05); - -moz-box-shadow: inset 0 2px 4px rgba(0, 0, 0, 0.15), 0 1px 2px rgba(0, 0, 0, 0.05); - box-shadow: inset 0 2px 4px rgba(0, 0, 0, 0.15), 0 1px 2px rgba(0, 0, 0, 0.05); background-color: #e6e6e6; background-color: #d9d9d9 \9; + background-image: none; outline: 0; + -webkit-box-shadow: inset 0 2px 4px rgba(0, 0, 0, 0.15), 0 1px 2px rgba(0, 0, 0, 0.05); + -moz-box-shadow: inset 0 2px 4px rgba(0, 0, 0, 0.15), 0 1px 2px rgba(0, 0, 0, 0.05); + box-shadow: inset 0 2px 4px rgba(0, 0, 0, 0.15), 0 1px 2px rgba(0, 0, 0, 0.05); } + .btn.disabled, .btn[disabled] { cursor: default; - background-image: none; background-color: #e6e6e6; + background-image: none; opacity: 0.65; filter: alpha(opacity=65); -webkit-box-shadow: none; - -moz-box-shadow: none; - box-shadow: none; + -moz-box-shadow: none; + box-shadow: none; } + .btn-large { padding: 9px 14px; font-size: 15px; line-height: normal; -webkit-border-radius: 5px; - -moz-border-radius: 5px; - border-radius: 5px; + -moz-border-radius: 5px; + border-radius: 5px; } + .btn-large [class^="icon-"] { margin-top: 1px; } + .btn-small { padding: 5px 9px; font-size: 11px; line-height: 16px; } + .btn-small [class^="icon-"] { margin-top: -1px; } + .btn-mini { padding: 2px 6px; font-size: 11px; line-height: 14px; } + .btn-primary, .btn-primary:hover, .btn-warning, @@ -2083,9 +2715,10 @@ table .span24 { .btn-info:hover, .btn-inverse, .btn-inverse:hover { - text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.25); color: #ffffff; + text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.25); } + .btn-primary.active, .btn-warning.active, .btn-danger.active, @@ -2094,204 +2727,251 @@ table .span24 { .btn-inverse.active { color: rgba(255, 255, 255, 0.75); } + +.btn { + border-color: #ccc; + border-color: rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.25); +} + .btn-primary { background-color: #0074cc; - background-image: -moz-linear-gradient(top, #0088cc, #0055cc); + *background-color: #0055cc; background-image: -ms-linear-gradient(top, #0088cc, #0055cc); background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#0088cc), to(#0055cc)); background-image: -webkit-linear-gradient(top, #0088cc, #0055cc); background-image: -o-linear-gradient(top, #0088cc, #0055cc); + background-image: -moz-linear-gradient(top, #0088cc, #0055cc); background-image: linear-gradient(top, #0088cc, #0055cc); background-repeat: repeat-x; - filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#0088cc', endColorstr='#0055cc', GradientType=0); border-color: #0055cc #0055cc #003580; border-color: rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.25); + filter: progid:dximagetransform.microsoft.gradient(startColorstr='#0088cc', endColorstr='#0055cc', GradientType=0); filter: progid:dximagetransform.microsoft.gradient(enabled=false); } + .btn-primary:hover, .btn-primary:active, .btn-primary.active, .btn-primary.disabled, .btn-primary[disabled] { background-color: #0055cc; + *background-color: #004ab3; } + .btn-primary:active, .btn-primary.active { background-color: #004099 \9; } + .btn-warning { background-color: #faa732; - background-image: -moz-linear-gradient(top, #fbb450, #f89406); + *background-color: #f89406; background-image: -ms-linear-gradient(top, #fbb450, #f89406); background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#fbb450), to(#f89406)); background-image: -webkit-linear-gradient(top, #fbb450, #f89406); background-image: -o-linear-gradient(top, #fbb450, #f89406); + background-image: -moz-linear-gradient(top, #fbb450, #f89406); background-image: linear-gradient(top, #fbb450, #f89406); background-repeat: repeat-x; - filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#fbb450', endColorstr='#f89406', GradientType=0); border-color: #f89406 #f89406 #ad6704; border-color: rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.25); + filter: progid:dximagetransform.microsoft.gradient(startColorstr='#fbb450', endColorstr='#f89406', GradientType=0); filter: progid:dximagetransform.microsoft.gradient(enabled=false); } + .btn-warning:hover, .btn-warning:active, .btn-warning.active, .btn-warning.disabled, .btn-warning[disabled] { background-color: #f89406; + *background-color: #df8505; } + .btn-warning:active, .btn-warning.active { background-color: #c67605 \9; } + .btn-danger { background-color: #da4f49; - background-image: -moz-linear-gradient(top, #ee5f5b, #bd362f); + *background-color: #bd362f; background-image: -ms-linear-gradient(top, #ee5f5b, #bd362f); background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#ee5f5b), to(#bd362f)); background-image: -webkit-linear-gradient(top, #ee5f5b, #bd362f); background-image: -o-linear-gradient(top, #ee5f5b, #bd362f); + background-image: -moz-linear-gradient(top, #ee5f5b, #bd362f); background-image: linear-gradient(top, #ee5f5b, #bd362f); background-repeat: repeat-x; - filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#ee5f5b', endColorstr='#bd362f', GradientType=0); border-color: #bd362f #bd362f #802420; border-color: rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.25); + filter: progid:dximagetransform.microsoft.gradient(startColorstr='#ee5f5b', endColorstr='#bd362f', GradientType=0); filter: progid:dximagetransform.microsoft.gradient(enabled=false); } + .btn-danger:hover, .btn-danger:active, .btn-danger.active, .btn-danger.disabled, .btn-danger[disabled] { background-color: #bd362f; + *background-color: #a9302a; } + .btn-danger:active, .btn-danger.active { background-color: #942a25 \9; } + .btn-success { background-color: #5bb75b; - background-image: -moz-linear-gradient(top, #62c462, #51a351); + *background-color: #51a351; background-image: -ms-linear-gradient(top, #62c462, #51a351); background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#62c462), to(#51a351)); background-image: -webkit-linear-gradient(top, #62c462, #51a351); background-image: -o-linear-gradient(top, #62c462, #51a351); + background-image: -moz-linear-gradient(top, #62c462, #51a351); background-image: linear-gradient(top, #62c462, #51a351); background-repeat: repeat-x; - filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#62c462', endColorstr='#51a351', GradientType=0); border-color: #51a351 #51a351 #387038; border-color: rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.25); + filter: progid:dximagetransform.microsoft.gradient(startColorstr='#62c462', endColorstr='#51a351', GradientType=0); filter: progid:dximagetransform.microsoft.gradient(enabled=false); } + .btn-success:hover, .btn-success:active, .btn-success.active, .btn-success.disabled, .btn-success[disabled] { background-color: #51a351; + *background-color: #499249; } + .btn-success:active, .btn-success.active { background-color: #408140 \9; } + .btn-info { background-color: #49afcd; - background-image: -moz-linear-gradient(top, #5bc0de, #2f96b4); + *background-color: #2f96b4; background-image: -ms-linear-gradient(top, #5bc0de, #2f96b4); background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#5bc0de), to(#2f96b4)); background-image: -webkit-linear-gradient(top, #5bc0de, #2f96b4); background-image: -o-linear-gradient(top, #5bc0de, #2f96b4); + background-image: -moz-linear-gradient(top, #5bc0de, #2f96b4); background-image: linear-gradient(top, #5bc0de, #2f96b4); background-repeat: repeat-x; - filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#5bc0de', endColorstr='#2f96b4', GradientType=0); border-color: #2f96b4 #2f96b4 #1f6377; border-color: rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.25); + filter: progid:dximagetransform.microsoft.gradient(startColorstr='#5bc0de', endColorstr='#2f96b4', GradientType=0); filter: progid:dximagetransform.microsoft.gradient(enabled=false); } + .btn-info:hover, .btn-info:active, .btn-info.active, .btn-info.disabled, .btn-info[disabled] { background-color: #2f96b4; + *background-color: #2a85a0; } + .btn-info:active, .btn-info.active { background-color: #24748c \9; } + .btn-inverse { background-color: #414141; - background-image: -moz-linear-gradient(top, #555555, #222222); + *background-color: #222222; background-image: -ms-linear-gradient(top, #555555, #222222); background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#555555), to(#222222)); background-image: -webkit-linear-gradient(top, #555555, #222222); background-image: -o-linear-gradient(top, #555555, #222222); + background-image: -moz-linear-gradient(top, #555555, #222222); background-image: linear-gradient(top, #555555, #222222); background-repeat: repeat-x; - filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#555555', endColorstr='#222222', GradientType=0); border-color: #222222 #222222 #000000; border-color: rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.25); + filter: progid:dximagetransform.microsoft.gradient(startColorstr='#555555', endColorstr='#222222', GradientType=0); filter: progid:dximagetransform.microsoft.gradient(enabled=false); } + .btn-inverse:hover, .btn-inverse:active, .btn-inverse.active, .btn-inverse.disabled, .btn-inverse[disabled] { background-color: #222222; + *background-color: #151515; } + .btn-inverse:active, .btn-inverse.active { background-color: #080808 \9; } + button.btn, input[type="submit"].btn { *padding-top: 2px; *padding-bottom: 2px; } + button.btn::-moz-focus-inner, input[type="submit"].btn::-moz-focus-inner { padding: 0; border: 0; } + button.btn.btn-large, input[type="submit"].btn.btn-large { *padding-top: 7px; *padding-bottom: 7px; } + button.btn.btn-small, input[type="submit"].btn.btn-small { *padding-top: 3px; *padding-bottom: 3px; } + button.btn.btn-mini, input[type="submit"].btn.btn-mini { *padding-top: 1px; *padding-bottom: 1px; } + .btn-group { position: relative; - *zoom: 1; *margin-left: .3em; + *zoom: 1; } + .btn-group:before, .btn-group:after { display: table; content: ""; } + .btn-group:after { clear: both; } + .btn-group:first-child { *margin-left: 0; } + .btn-group + .btn-group { margin-left: 5px; } + .btn-toolbar { margin-top: 9px; margin-bottom: 9px; } + .btn-toolbar .btn-group { display: inline-block; *display: inline; @@ -2299,120 +2979,159 @@ input[type="submit"].btn.btn-mini { *zoom: 1; } -.btn-group .btn { + +.btn-group > .btn { position: relative; float: left; margin-left: -1px; -webkit-border-radius: 0; - -moz-border-radius: 0; - border-radius: 0; + -moz-border-radius: 0; + border-radius: 0; } -.btn-group .btn:first-child { + +.btn-group > .btn:first-child { margin-left: 0; - -webkit-border-top-left-radius: 4px; - -moz-border-radius-topleft: 4px; - border-top-left-radius: 4px; -webkit-border-bottom-left-radius: 4px; + border-bottom-left-radius: 4px; + -webkit-border-top-left-radius: 4px; + border-top-left-radius: 4px; -moz-border-radius-bottomleft: 4px; - border-bottom-left-radius: 4px; + -moz-border-radius-topleft: 4px; } -.btn-group .btn:last-child, -.btn-group .dropdown-toggle { + +.btn-group > .btn:last-child, +.btn-group > .dropdown-toggle { -webkit-border-top-right-radius: 4px; - -moz-border-radius-topright: 4px; - border-top-right-radius: 4px; + border-top-right-radius: 4px; -webkit-border-bottom-right-radius: 4px; + border-bottom-right-radius: 4px; + -moz-border-radius-topright: 4px; -moz-border-radius-bottomright: 4px; - border-bottom-right-radius: 4px; } -.btn-group .btn.large:first-child { + +.btn-group > .btn.large:first-child { margin-left: 0; - -webkit-border-top-left-radius: 6px; - -moz-border-radius-topleft: 6px; - border-top-left-radius: 6px; -webkit-border-bottom-left-radius: 6px; + border-bottom-left-radius: 6px; + -webkit-border-top-left-radius: 6px; + border-top-left-radius: 6px; -moz-border-radius-bottomleft: 6px; - border-bottom-left-radius: 6px; + -moz-border-radius-topleft: 6px; } -.btn-group .btn.large:last-child, -.btn-group .large.dropdown-toggle { + +.btn-group > .btn.large:last-child, +.btn-group > .large.dropdown-toggle { -webkit-border-top-right-radius: 6px; - -moz-border-radius-topright: 6px; - border-top-right-radius: 6px; + border-top-right-radius: 6px; -webkit-border-bottom-right-radius: 6px; + border-bottom-right-radius: 6px; + -moz-border-radius-topright: 6px; -moz-border-radius-bottomright: 6px; - border-bottom-right-radius: 6px; } -.btn-group .btn:hover, -.btn-group .btn:focus, -.btn-group .btn:active, -.btn-group .btn.active { + +.btn-group > .btn:hover, +.btn-group > .btn:focus, +.btn-group > .btn:active, +.btn-group > .btn.active { z-index: 2; } + .btn-group .dropdown-toggle:active, .btn-group.open .dropdown-toggle { outline: 0; } -.btn-group .dropdown-toggle { - padding-left: 8px; + +.btn-group > .dropdown-toggle { + *padding-top: 4px; padding-right: 8px; + *padding-bottom: 4px; + padding-left: 8px; -webkit-box-shadow: inset 1px 0 0 rgba(255, 255, 255, 0.125), inset 0 1px 0 rgba(255, 255, 255, 0.2), 0 1px 2px rgba(0, 0, 0, 0.05); - -moz-box-shadow: inset 1px 0 0 rgba(255, 255, 255, 0.125), inset 0 1px 0 rgba(255, 255, 255, 0.2), 0 1px 2px rgba(0, 0, 0, 0.05); - box-shadow: inset 1px 0 0 rgba(255, 255, 255, 0.125), inset 0 1px 0 rgba(255, 255, 255, 0.2), 0 1px 2px rgba(0, 0, 0, 0.05); - *padding-top: 3px; - *padding-bottom: 3px; + -moz-box-shadow: inset 1px 0 0 rgba(255, 255, 255, 0.125), inset 0 1px 0 rgba(255, 255, 255, 0.2), 0 1px 2px rgba(0, 0, 0, 0.05); + box-shadow: inset 1px 0 0 rgba(255, 255, 255, 0.125), inset 0 1px 0 rgba(255, 255, 255, 0.2), 0 1px 2px rgba(0, 0, 0, 0.05); } -.btn-group .btn-mini.dropdown-toggle { - padding-left: 5px; + +.btn-group > .btn-mini.dropdown-toggle { padding-right: 5px; - *padding-top: 1px; - *padding-bottom: 1px; + padding-left: 5px; } -.btn-group .btn-small.dropdown-toggle { + +.btn-group > .btn-small.dropdown-toggle { *padding-top: 4px; *padding-bottom: 4px; } -.btn-group .btn-large.dropdown-toggle { - padding-left: 12px; + +.btn-group > .btn-large.dropdown-toggle { padding-right: 12px; + padding-left: 12px; } -.btn-group.open { - *z-index: 1000; -} -.btn-group.open .dropdown-menu { - display: block; - margin-top: 1px; - -webkit-border-radius: 5px; - -moz-border-radius: 5px; - border-radius: 5px; -} + .btn-group.open .dropdown-toggle { background-image: none; - -webkit-box-shadow: inset 0 1px 6px rgba(0, 0, 0, 0.15), 0 1px 2px rgba(0, 0, 0, 0.05); - -moz-box-shadow: inset 0 1px 6px rgba(0, 0, 0, 0.15), 0 1px 2px rgba(0, 0, 0, 0.05); - box-shadow: inset 0 1px 6px rgba(0, 0, 0, 0.15), 0 1px 2px rgba(0, 0, 0, 0.05); + -webkit-box-shadow: inset 0 2px 4px rgba(0, 0, 0, 0.15), 0 1px 2px rgba(0, 0, 0, 0.05); + -moz-box-shadow: inset 0 2px 4px rgba(0, 0, 0, 0.15), 0 1px 2px rgba(0, 0, 0, 0.05); + box-shadow: inset 0 2px 4px rgba(0, 0, 0, 0.15), 0 1px 2px rgba(0, 0, 0, 0.05); } + +.btn-group.open .btn.dropdown-toggle { + background-color: #e6e6e6; +} + +.btn-group.open .btn-primary.dropdown-toggle { + background-color: #0055cc; +} + +.btn-group.open .btn-warning.dropdown-toggle { + background-color: #f89406; +} + +.btn-group.open .btn-danger.dropdown-toggle { + background-color: #bd362f; +} + +.btn-group.open .btn-success.dropdown-toggle { + background-color: #51a351; +} + +.btn-group.open .btn-info.dropdown-toggle { + background-color: #2f96b4; +} + +.btn-group.open .btn-inverse.dropdown-toggle { + background-color: #222222; +} + .btn .caret { margin-top: 7px; margin-left: 0; } + .btn:hover .caret, .open.btn-group .caret { opacity: 1; filter: alpha(opacity=100); } + .btn-mini .caret { margin-top: 5px; } + .btn-small .caret { margin-top: 6px; } + .btn-large .caret { margin-top: 6px; - border-left: 5px solid transparent; - border-right: 5px solid transparent; - border-top: 5px solid #000000; + border-top-width: 5px; + border-right-width: 5px; + border-left-width: 5px; } + +.dropup .btn-large .caret { + border-top: 0; + border-bottom: 5px solid #000000; +} + .btn-primary .caret, .btn-warning .caret, .btn-danger .caret, @@ -2424,65 +3143,82 @@ input[type="submit"].btn.btn-mini { opacity: 0.75; filter: alpha(opacity=75); } + .alert { padding: 8px 35px 8px 14px; margin-bottom: 18px; + color: #c09853; text-shadow: 0 1px 0 rgba(255, 255, 255, 0.5); background-color: #fcf8e3; border: 1px solid #fbeed5; -webkit-border-radius: 4px; - -moz-border-radius: 4px; - border-radius: 4px; - color: #c09853; + -moz-border-radius: 4px; + border-radius: 4px; } + .alert-heading { color: inherit; } + .alert .close { position: relative; top: -2px; right: -21px; line-height: 18px; } + .alert-success { + color: #468847; background-color: #dff0d8; border-color: #d6e9c6; - color: #468847; } + .alert-danger, .alert-error { + color: #b94a48; background-color: #f2dede; border-color: #eed3d7; - color: #b94a48; } + .alert-info { + color: #3a87ad; background-color: #d9edf7; border-color: #bce8f1; - color: #3a87ad; } + .alert-block { padding-top: 14px; padding-bottom: 14px; } + .alert-block > p, .alert-block > ul { margin-bottom: 0; } + .alert-block p + p { margin-top: 5px; } + .nav { - margin-left: 0; margin-bottom: 18px; + margin-left: 0; list-style: none; } + .nav > li > a { display: block; } + .nav > li > a:hover { text-decoration: none; background-color: #eeeeee; } + +.nav > .pull-right { + float: right; +} + .nav .nav-header { display: block; padding: 3px 15px; @@ -2493,45 +3229,54 @@ input[type="submit"].btn.btn-mini { text-shadow: 0 1px 0 rgba(255, 255, 255, 0.5); text-transform: uppercase; } + .nav li + .nav-header { margin-top: 9px; } + .nav-list { - padding-left: 15px; padding-right: 15px; + padding-left: 15px; margin-bottom: 0; } + .nav-list > li > a, .nav-list .nav-header { - margin-left: -15px; margin-right: -15px; + margin-left: -15px; text-shadow: 0 1px 0 rgba(255, 255, 255, 0.5); } + .nav-list > li > a { padding: 3px 15px; } + .nav-list > .active > a, .nav-list > .active > a:hover { color: #ffffff; text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.2); background-color: #0088cc; } + .nav-list [class^="icon-"] { margin-right: 2px; } + .nav-list .divider { + *width: 100%; height: 1px; margin: 8px 1px; + *margin: -5px 0 5px; overflow: hidden; background-color: #e5e5e5; border-bottom: 1px solid #ffffff; - *width: 100%; - *margin: -5px 0 5px; } + .nav-tabs, .nav-pills { *zoom: 1; } + .nav-tabs:before, .nav-pills:before, .nav-tabs:after, @@ -2539,14 +3284,17 @@ input[type="submit"].btn.btn-mini { display: table; content: ""; } + .nav-tabs:after, .nav-pills:after { clear: both; } + .nav-tabs > li, .nav-pills > li { float: left; } + .nav-tabs > li > a, .nav-pills > li > a { padding-right: 12px; @@ -2554,234 +3302,283 @@ input[type="submit"].btn.btn-mini { margin-right: 2px; line-height: 14px; } + .nav-tabs { border-bottom: 1px solid #ddd; } + .nav-tabs > li { margin-bottom: -1px; } + .nav-tabs > li > a { padding-top: 8px; padding-bottom: 8px; line-height: 18px; border: 1px solid transparent; -webkit-border-radius: 4px 4px 0 0; - -moz-border-radius: 4px 4px 0 0; - border-radius: 4px 4px 0 0; + -moz-border-radius: 4px 4px 0 0; + border-radius: 4px 4px 0 0; } + .nav-tabs > li > a:hover { border-color: #eeeeee #eeeeee #dddddd; } + .nav-tabs > .active > a, .nav-tabs > .active > a:hover { color: #555555; + cursor: default; background-color: #ffffff; border: 1px solid #ddd; border-bottom-color: transparent; - cursor: default; } + .nav-pills > li > a { padding-top: 8px; padding-bottom: 8px; margin-top: 2px; margin-bottom: 2px; -webkit-border-radius: 5px; - -moz-border-radius: 5px; - border-radius: 5px; + -moz-border-radius: 5px; + border-radius: 5px; } + .nav-pills > .active > a, .nav-pills > .active > a:hover { color: #ffffff; background-color: #0088cc; } + .nav-stacked > li { float: none; } + .nav-stacked > li > a { margin-right: 0; } + .nav-tabs.nav-stacked { border-bottom: 0; } + .nav-tabs.nav-stacked > li > a { border: 1px solid #ddd; -webkit-border-radius: 0; - -moz-border-radius: 0; - border-radius: 0; + -moz-border-radius: 0; + border-radius: 0; } + .nav-tabs.nav-stacked > li:first-child > a { -webkit-border-radius: 4px 4px 0 0; - -moz-border-radius: 4px 4px 0 0; - border-radius: 4px 4px 0 0; + -moz-border-radius: 4px 4px 0 0; + border-radius: 4px 4px 0 0; } + .nav-tabs.nav-stacked > li:last-child > a { -webkit-border-radius: 0 0 4px 4px; - -moz-border-radius: 0 0 4px 4px; - border-radius: 0 0 4px 4px; + -moz-border-radius: 0 0 4px 4px; + border-radius: 0 0 4px 4px; } + .nav-tabs.nav-stacked > li > a:hover { - border-color: #ddd; z-index: 2; + border-color: #ddd; } + .nav-pills.nav-stacked > li > a { margin-bottom: 3px; } + .nav-pills.nav-stacked > li:last-child > a { margin-bottom: 1px; } -.nav-tabs .dropdown-menu, -.nav-pills .dropdown-menu { - margin-top: 1px; - border-width: 1px; + +.nav-tabs .dropdown-menu { + -webkit-border-radius: 0 0 5px 5px; + -moz-border-radius: 0 0 5px 5px; + border-radius: 0 0 5px 5px; } + .nav-pills .dropdown-menu { -webkit-border-radius: 4px; - -moz-border-radius: 4px; - border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; } + .nav-tabs .dropdown-toggle .caret, .nav-pills .dropdown-toggle .caret { + margin-top: 6px; border-top-color: #0088cc; border-bottom-color: #0088cc; - margin-top: 6px; } + .nav-tabs .dropdown-toggle:hover .caret, .nav-pills .dropdown-toggle:hover .caret { border-top-color: #005580; border-bottom-color: #005580; } + .nav-tabs .active .dropdown-toggle .caret, .nav-pills .active .dropdown-toggle .caret { border-top-color: #333333; border-bottom-color: #333333; } + .nav > .dropdown.active > a:hover { color: #000000; cursor: pointer; } + .nav-tabs .open .dropdown-toggle, .nav-pills .open .dropdown-toggle, -.nav > .open.active > a:hover { +.nav > li.dropdown.open.active > a:hover { color: #ffffff; background-color: #999999; border-color: #999999; } -.nav .open .caret, -.nav .open.active .caret, -.nav .open a:hover .caret { + +.nav li.dropdown.open .caret, +.nav li.dropdown.open.active .caret, +.nav li.dropdown.open a:hover .caret { border-top-color: #ffffff; border-bottom-color: #ffffff; opacity: 1; filter: alpha(opacity=100); } + .tabs-stacked .open > a:hover { border-color: #999999; } + .tabbable { *zoom: 1; } + .tabbable:before, .tabbable:after { display: table; content: ""; } + .tabbable:after { clear: both; } + .tab-content { - display: table; - width: 100%; + overflow: auto; } -.tabs-below .nav-tabs, -.tabs-right .nav-tabs, -.tabs-left .nav-tabs { + +.tabs-below > .nav-tabs, +.tabs-right > .nav-tabs, +.tabs-left > .nav-tabs { border-bottom: 0; } + .tab-content > .tab-pane, .pill-content > .pill-pane { display: none; } + .tab-content > .active, .pill-content > .active { display: block; } -.tabs-below .nav-tabs { + +.tabs-below > .nav-tabs { border-top: 1px solid #ddd; } -.tabs-below .nav-tabs > li { + +.tabs-below > .nav-tabs > li { margin-top: -1px; margin-bottom: 0; } -.tabs-below .nav-tabs > li > a { + +.tabs-below > .nav-tabs > li > a { -webkit-border-radius: 0 0 4px 4px; - -moz-border-radius: 0 0 4px 4px; - border-radius: 0 0 4px 4px; + -moz-border-radius: 0 0 4px 4px; + border-radius: 0 0 4px 4px; } -.tabs-below .nav-tabs > li > a:hover { - border-bottom-color: transparent; + +.tabs-below > .nav-tabs > li > a:hover { border-top-color: #ddd; + border-bottom-color: transparent; } -.tabs-below .nav-tabs .active > a, -.tabs-below .nav-tabs .active > a:hover { + +.tabs-below > .nav-tabs > .active > a, +.tabs-below > .nav-tabs > .active > a:hover { border-color: transparent #ddd #ddd #ddd; } -.tabs-left .nav-tabs > li, -.tabs-right .nav-tabs > li { + +.tabs-left > .nav-tabs > li, +.tabs-right > .nav-tabs > li { float: none; } -.tabs-left .nav-tabs > li > a, -.tabs-right .nav-tabs > li > a { + +.tabs-left > .nav-tabs > li > a, +.tabs-right > .nav-tabs > li > a { min-width: 74px; margin-right: 0; margin-bottom: 3px; } -.tabs-left .nav-tabs { + +.tabs-left > .nav-tabs { float: left; margin-right: 19px; border-right: 1px solid #ddd; } -.tabs-left .nav-tabs > li > a { + +.tabs-left > .nav-tabs > li > a { margin-right: -1px; -webkit-border-radius: 4px 0 0 4px; - -moz-border-radius: 4px 0 0 4px; - border-radius: 4px 0 0 4px; + -moz-border-radius: 4px 0 0 4px; + border-radius: 4px 0 0 4px; } -.tabs-left .nav-tabs > li > a:hover { + +.tabs-left > .nav-tabs > li > a:hover { border-color: #eeeeee #dddddd #eeeeee #eeeeee; } -.tabs-left .nav-tabs .active > a, -.tabs-left .nav-tabs .active > a:hover { + +.tabs-left > .nav-tabs .active > a, +.tabs-left > .nav-tabs .active > a:hover { border-color: #ddd transparent #ddd #ddd; *border-right-color: #ffffff; } -.tabs-right .nav-tabs { + +.tabs-right > .nav-tabs { float: right; margin-left: 19px; border-left: 1px solid #ddd; } -.tabs-right .nav-tabs > li > a { + +.tabs-right > .nav-tabs > li > a { margin-left: -1px; -webkit-border-radius: 0 4px 4px 0; - -moz-border-radius: 0 4px 4px 0; - border-radius: 0 4px 4px 0; + -moz-border-radius: 0 4px 4px 0; + border-radius: 0 4px 4px 0; } -.tabs-right .nav-tabs > li > a:hover { + +.tabs-right > .nav-tabs > li > a:hover { border-color: #eeeeee #eeeeee #eeeeee #dddddd; } -.tabs-right .nav-tabs .active > a, -.tabs-right .nav-tabs .active > a:hover { + +.tabs-right > .nav-tabs .active > a, +.tabs-right > .nav-tabs .active > a:hover { border-color: #ddd #ddd #ddd transparent; *border-left-color: #ffffff; } + .navbar { *position: relative; *z-index: 2; - overflow: visible; margin-bottom: 18px; + overflow: visible; } + .navbar-inner { - padding-left: 20px; + min-height: 40px; padding-right: 20px; + padding-left: 20px; background-color: #2c2c2c; background-image: -moz-linear-gradient(top, #333333, #222222); background-image: -ms-linear-gradient(top, #333333, #222222); @@ -2790,138 +3587,116 @@ input[type="submit"].btn.btn-mini { background-image: -o-linear-gradient(top, #333333, #222222); background-image: linear-gradient(top, #333333, #222222); background-repeat: repeat-x; - filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#333333', endColorstr='#222222', GradientType=0); -webkit-border-radius: 4px; - -moz-border-radius: 4px; - border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; + filter: progid:dximagetransform.microsoft.gradient(startColorstr='#333333', endColorstr='#222222', GradientType=0); -webkit-box-shadow: 0 1px 3px rgba(0, 0, 0, 0.25), inset 0 -1px 0 rgba(0, 0, 0, 0.1); - -moz-box-shadow: 0 1px 3px rgba(0, 0, 0, 0.25), inset 0 -1px 0 rgba(0, 0, 0, 0.1); - box-shadow: 0 1px 3px rgba(0, 0, 0, 0.25), inset 0 -1px 0 rgba(0, 0, 0, 0.1); + -moz-box-shadow: 0 1px 3px rgba(0, 0, 0, 0.25), inset 0 -1px 0 rgba(0, 0, 0, 0.1); + box-shadow: 0 1px 3px rgba(0, 0, 0, 0.25), inset 0 -1px 0 rgba(0, 0, 0, 0.1); } + .navbar .container { width: auto; } -.btn-navbar { - display: none; - float: right; - padding: 7px 10px; - margin-left: 5px; - margin-right: 5px; - background-color: #2c2c2c; - background-image: -moz-linear-gradient(top, #333333, #222222); - background-image: -ms-linear-gradient(top, #333333, #222222); - background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#333333), to(#222222)); - background-image: -webkit-linear-gradient(top, #333333, #222222); - background-image: -o-linear-gradient(top, #333333, #222222); - background-image: linear-gradient(top, #333333, #222222); - background-repeat: repeat-x; - filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#333333', endColorstr='#222222', GradientType=0); - border-color: #222222 #222222 #000000; - border-color: rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.25); - filter: progid:dximagetransform.microsoft.gradient(enabled=false); - -webkit-box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.1), 0 1px 0 rgba(255, 255, 255, 0.075); - -moz-box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.1), 0 1px 0 rgba(255, 255, 255, 0.075); - box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.1), 0 1px 0 rgba(255, 255, 255, 0.075); -} -.btn-navbar:hover, -.btn-navbar:active, -.btn-navbar.active, -.btn-navbar.disabled, -.btn-navbar[disabled] { - background-color: #222222; -} -.btn-navbar:active, -.btn-navbar.active { - background-color: #080808 \9; -} -.btn-navbar .icon-bar { - display: block; - width: 18px; - height: 2px; - background-color: #f5f5f5; - -webkit-border-radius: 1px; - -moz-border-radius: 1px; - border-radius: 1px; - -webkit-box-shadow: 0 1px 0 rgba(0, 0, 0, 0.25); - -moz-box-shadow: 0 1px 0 rgba(0, 0, 0, 0.25); - box-shadow: 0 1px 0 rgba(0, 0, 0, 0.25); -} -.btn-navbar .icon-bar + .icon-bar { - margin-top: 3px; -} + .nav-collapse.collapse { height: auto; } + .navbar { color: #999999; } + .navbar .brand:hover { text-decoration: none; } + .navbar .brand { - float: left; display: block; + float: left; padding: 8px 20px 12px; margin-left: -20px; font-size: 20px; font-weight: 200; line-height: 1; - color: #ffffff; + color: #999999; } + .navbar .navbar-text { margin-bottom: 0; line-height: 40px; } + +.navbar .navbar-link { + color: #999999; +} + +.navbar .navbar-link:hover { + color: #ffffff; +} + .navbar .btn, .navbar .btn-group { margin-top: 5px; } + .navbar .btn-group .btn { - margin-top: 0; + margin: 0; } + .navbar-form { margin-bottom: 0; *zoom: 1; } + .navbar-form:before, .navbar-form:after { display: table; content: ""; } + .navbar-form:after { clear: both; } + .navbar-form input, .navbar-form select, .navbar-form .radio, .navbar-form .checkbox { margin-top: 5px; } + .navbar-form input, .navbar-form select { display: inline-block; margin-bottom: 0; } + .navbar-form input[type="image"], .navbar-form input[type="checkbox"], .navbar-form input[type="radio"] { margin-top: 3px; } + .navbar-form .input-append, .navbar-form .input-prepend { margin-top: 6px; white-space: nowrap; } + .navbar-form .input-append input, .navbar-form .input-prepend input { margin-top: 0; } + .navbar-search { position: relative; float: left; margin-top: 6px; margin-bottom: 0; } + .navbar-search .search-query { padding: 4px 9px; font-family: "Helvetica Neue", Helvetica, Arial, sans-serif; @@ -2931,21 +3706,28 @@ input[type="submit"].btn.btn-mini { color: #ffffff; background-color: #626262; border: 1px solid #151515; - -webkit-box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.1), 0 1px 0px rgba(255, 255, 255, 0.15); - -moz-box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.1), 0 1px 0px rgba(255, 255, 255, 0.15); - box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.1), 0 1px 0px rgba(255, 255, 255, 0.15); + -webkit-box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.1), 0 1px 0 rgba(255, 255, 255, 0.15); + -moz-box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.1), 0 1px 0 rgba(255, 255, 255, 0.15); + box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.1), 0 1px 0 rgba(255, 255, 255, 0.15); -webkit-transition: none; - -moz-transition: none; - -ms-transition: none; - -o-transition: none; - transition: none; + -moz-transition: none; + -ms-transition: none; + -o-transition: none; + transition: none; } + .navbar-search .search-query:-moz-placeholder { color: #cccccc; } + +.navbar-search .search-query:-ms-input-placeholder { + color: #cccccc; +} + .navbar-search .search-query::-webkit-input-placeholder { color: #cccccc; } + .navbar-search .search-query:focus, .navbar-search .search-query.focused { padding: 5px 10px; @@ -2953,11 +3735,12 @@ input[type="submit"].btn.btn-mini { text-shadow: 0 1px 0 #ffffff; background-color: #ffffff; border: 0; - -webkit-box-shadow: 0 0 3px rgba(0, 0, 0, 0.15); - -moz-box-shadow: 0 0 3px rgba(0, 0, 0, 0.15); - box-shadow: 0 0 3px rgba(0, 0, 0, 0.15); outline: 0; + -webkit-box-shadow: 0 0 3px rgba(0, 0, 0, 0.15); + -moz-box-shadow: 0 0 3px rgba(0, 0, 0, 0.15); + box-shadow: 0 0 3px rgba(0, 0, 0, 0.15); } + .navbar-fixed-top, .navbar-fixed-bottom { position: fixed; @@ -2966,24 +3749,29 @@ input[type="submit"].btn.btn-mini { z-index: 1030; margin-bottom: 0; } + .navbar-fixed-top .navbar-inner, .navbar-fixed-bottom .navbar-inner { - padding-left: 0; padding-right: 0; + padding-left: 0; -webkit-border-radius: 0; - -moz-border-radius: 0; - border-radius: 0; + -moz-border-radius: 0; + border-radius: 0; } + .navbar-fixed-top .container, .navbar-fixed-bottom .container { width: 940px; } + .navbar-fixed-top { top: 0; } + .navbar-fixed-bottom { bottom: 0; } + .navbar .nav { position: relative; left: 0; @@ -2991,116 +3779,196 @@ input[type="submit"].btn.btn-mini { float: left; margin: 0 10px 0 0; } + .navbar .nav.pull-right { float: right; } + .navbar .nav > li { display: block; float: left; } + .navbar .nav > li > a { float: none; - padding: 10px 10px 11px; + padding: 9px 10px 11px; line-height: 19px; color: #999999; text-decoration: none; text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.25); } + +.navbar .btn { + display: inline-block; + padding: 4px 10px 4px; + margin: 5px 5px 6px; + line-height: 18px; +} + +.navbar .btn-group { + padding: 5px 5px 6px; + margin: 0; +} + .navbar .nav > li > a:hover { - background-color: transparent; color: #ffffff; text-decoration: none; + background-color: transparent; } + .navbar .nav .active > a, .navbar .nav .active > a:hover { color: #ffffff; text-decoration: none; background-color: #222222; } + .navbar .divider-vertical { - height: 40px; width: 1px; + height: 40px; margin: 0 9px; overflow: hidden; background-color: #222222; border-right: 1px solid #333333; } + .navbar .nav.pull-right { - margin-left: 10px; margin-right: 0; + margin-left: 10px; } -.navbar .dropdown-menu { - margin-top: 1px; - -webkit-border-radius: 4px; - -moz-border-radius: 4px; - border-radius: 4px; + +.navbar .btn-navbar { + display: none; + float: right; + padding: 7px 10px; + margin-right: 5px; + margin-left: 5px; + background-color: #2c2c2c; + *background-color: #222222; + background-image: -ms-linear-gradient(top, #333333, #222222); + background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#333333), to(#222222)); + background-image: -webkit-linear-gradient(top, #333333, #222222); + background-image: -o-linear-gradient(top, #333333, #222222); + background-image: linear-gradient(top, #333333, #222222); + background-image: -moz-linear-gradient(top, #333333, #222222); + background-repeat: repeat-x; + border-color: #222222 #222222 #000000; + border-color: rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.1) rgba(0, 0, 0, 0.25); + filter: progid:dximagetransform.microsoft.gradient(startColorstr='#333333', endColorstr='#222222', GradientType=0); + filter: progid:dximagetransform.microsoft.gradient(enabled=false); + -webkit-box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.1), 0 1px 0 rgba(255, 255, 255, 0.075); + -moz-box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.1), 0 1px 0 rgba(255, 255, 255, 0.075); + box-shadow: inset 0 1px 0 rgba(255, 255, 255, 0.1), 0 1px 0 rgba(255, 255, 255, 0.075); } + +.navbar .btn-navbar:hover, +.navbar .btn-navbar:active, +.navbar .btn-navbar.active, +.navbar .btn-navbar.disabled, +.navbar .btn-navbar[disabled] { + background-color: #222222; + *background-color: #151515; +} + +.navbar .btn-navbar:active, +.navbar .btn-navbar.active { + background-color: #080808 \9; +} + +.navbar .btn-navbar .icon-bar { + display: block; + width: 18px; + height: 2px; + background-color: #f5f5f5; + -webkit-border-radius: 1px; + -moz-border-radius: 1px; + border-radius: 1px; + -webkit-box-shadow: 0 1px 0 rgba(0, 0, 0, 0.25); + -moz-box-shadow: 0 1px 0 rgba(0, 0, 0, 0.25); + box-shadow: 0 1px 0 rgba(0, 0, 0, 0.25); +} + +.btn-navbar .icon-bar + .icon-bar { + margin-top: 3px; +} + .navbar .dropdown-menu:before { - content: ''; - display: inline-block; - border-left: 7px solid transparent; - border-right: 7px solid transparent; - border-bottom: 7px solid #ccc; - border-bottom-color: rgba(0, 0, 0, 0.2); position: absolute; top: -7px; left: 9px; -} -.navbar .dropdown-menu:after { - content: ''; display: inline-block; - border-left: 6px solid transparent; - border-right: 6px solid transparent; - border-bottom: 6px solid #ffffff; + border-right: 7px solid transparent; + border-bottom: 7px solid #ccc; + border-left: 7px solid transparent; + border-bottom-color: rgba(0, 0, 0, 0.2); + content: ''; +} + +.navbar .dropdown-menu:after { position: absolute; top: -6px; left: 10px; + display: inline-block; + border-right: 6px solid transparent; + border-bottom: 6px solid #ffffff; + border-left: 6px solid transparent; + content: ''; } + .navbar-fixed-bottom .dropdown-menu:before { - border-top: 7px solid #ccc; - border-top-color: rgba(0, 0, 0, 0.2); - border-bottom: 0; - bottom: -7px; top: auto; + bottom: -7px; + border-top: 7px solid #ccc; + border-bottom: 0; + border-top-color: rgba(0, 0, 0, 0.2); } + .navbar-fixed-bottom .dropdown-menu:after { + top: auto; + bottom: -6px; border-top: 6px solid #ffffff; border-bottom: 0; - bottom: -6px; - top: auto; } -.navbar .nav .dropdown-toggle .caret, -.navbar .nav .open.dropdown .caret { + +.navbar .nav li.dropdown .dropdown-toggle .caret, +.navbar .nav li.dropdown.open .caret { border-top-color: #ffffff; border-bottom-color: #ffffff; } -.navbar .nav .active .caret { + +.navbar .nav li.dropdown.active .caret { opacity: 1; filter: alpha(opacity=100); } -.navbar .nav .open > .dropdown-toggle, -.navbar .nav .active > .dropdown-toggle, -.navbar .nav .open.active > .dropdown-toggle { + +.navbar .nav li.dropdown.open > .dropdown-toggle, +.navbar .nav li.dropdown.active > .dropdown-toggle, +.navbar .nav li.dropdown.open.active > .dropdown-toggle { background-color: transparent; } -.navbar .nav .active > .dropdown-toggle:hover { + +.navbar .nav li.dropdown.active > .dropdown-toggle:hover { color: #ffffff; } -.navbar .nav.pull-right .dropdown-menu, -.navbar .nav .dropdown-menu.pull-right { - left: auto; + +.navbar .pull-right .dropdown-menu, +.navbar .dropdown-menu.pull-right { right: 0; -} -.navbar .nav.pull-right .dropdown-menu:before, -.navbar .nav .dropdown-menu.pull-right:before { left: auto; +} + +.navbar .pull-right .dropdown-menu:before, +.navbar .dropdown-menu.pull-right:before { right: 12px; -} -.navbar .nav.pull-right .dropdown-menu:after, -.navbar .nav .dropdown-menu.pull-right:after { left: auto; - right: 13px; } + +.navbar .pull-right .dropdown-menu:after, +.navbar .dropdown-menu.pull-right:after { + right: 13px; + left: auto; +} + .breadcrumb { padding: 7px 14px; margin: 0 0 18px; @@ -3113,52 +3981,55 @@ input[type="submit"].btn.btn-mini { background-image: -o-linear-gradient(top, #ffffff, #f5f5f5); background-image: linear-gradient(top, #ffffff, #f5f5f5); background-repeat: repeat-x; - filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#ffffff', endColorstr='#f5f5f5', GradientType=0); border: 1px solid #ddd; -webkit-border-radius: 3px; - -moz-border-radius: 3px; - border-radius: 3px; + -moz-border-radius: 3px; + border-radius: 3px; + filter: progid:dximagetransform.microsoft.gradient(startColorstr='#ffffff', endColorstr='#f5f5f5', GradientType=0); -webkit-box-shadow: inset 0 1px 0 #ffffff; - -moz-box-shadow: inset 0 1px 0 #ffffff; - box-shadow: inset 0 1px 0 #ffffff; + -moz-box-shadow: inset 0 1px 0 #ffffff; + box-shadow: inset 0 1px 0 #ffffff; } + .breadcrumb li { display: inline-block; *display: inline; - /* IE7 inline-block hack */ - - *zoom: 1; text-shadow: 0 1px 0 #ffffff; + *zoom: 1; } + .breadcrumb .divider { padding: 0 5px; color: #999999; } + .breadcrumb .active a { color: #333333; } + .pagination { height: 36px; margin: 18px 0; } + .pagination ul { display: inline-block; *display: inline; - /* IE7 inline-block hack */ - - *zoom: 1; - margin-left: 0; margin-bottom: 0; + margin-left: 0; -webkit-border-radius: 3px; - -moz-border-radius: 3px; - border-radius: 3px; + -moz-border-radius: 3px; + border-radius: 3px; + *zoom: 1; -webkit-box-shadow: 0 1px 2px rgba(0, 0, 0, 0.05); - -moz-box-shadow: 0 1px 2px rgba(0, 0, 0, 0.05); - box-shadow: 0 1px 2px rgba(0, 0, 0, 0.05); + -moz-box-shadow: 0 1px 2px rgba(0, 0, 0, 0.05); + box-shadow: 0 1px 2px rgba(0, 0, 0, 0.05); } + .pagination li { display: inline; } + .pagination a { float: left; padding: 0 14px; @@ -3167,93 +4038,114 @@ input[type="submit"].btn.btn-mini { border: 1px solid #ddd; border-left-width: 0; } + .pagination a:hover, .pagination .active a { background-color: #f5f5f5; } + .pagination .active a { color: #999999; cursor: default; } + .pagination .disabled span, .pagination .disabled a, .pagination .disabled a:hover { color: #999999; - background-color: transparent; cursor: default; + background-color: transparent; } + .pagination li:first-child a { border-left-width: 1px; -webkit-border-radius: 3px 0 0 3px; - -moz-border-radius: 3px 0 0 3px; - border-radius: 3px 0 0 3px; + -moz-border-radius: 3px 0 0 3px; + border-radius: 3px 0 0 3px; } + .pagination li:last-child a { -webkit-border-radius: 0 3px 3px 0; - -moz-border-radius: 0 3px 3px 0; - border-radius: 0 3px 3px 0; + -moz-border-radius: 0 3px 3px 0; + border-radius: 0 3px 3px 0; } + .pagination-centered { text-align: center; } + .pagination-right { text-align: right; } + .pager { - margin-left: 0; margin-bottom: 18px; - list-style: none; + margin-left: 0; text-align: center; + list-style: none; *zoom: 1; } + .pager:before, .pager:after { display: table; content: ""; } + .pager:after { clear: both; } + .pager li { display: inline; } + .pager a { display: inline-block; padding: 5px 14px; background-color: #fff; border: 1px solid #ddd; -webkit-border-radius: 15px; - -moz-border-radius: 15px; - border-radius: 15px; + -moz-border-radius: 15px; + border-radius: 15px; } + .pager a:hover { text-decoration: none; background-color: #f5f5f5; } + .pager .next a { float: right; } + .pager .previous a { float: left; } + .pager .disabled a, .pager .disabled a:hover { color: #999999; - background-color: #fff; cursor: default; + background-color: #fff; } + .modal-open .dropdown-menu { z-index: 2050; } + .modal-open .dropdown.open { *z-index: 2050; } + .modal-open .popover { z-index: 2060; } + .modal-open .tooltip { z-index: 2070; } + .modal-backdrop { position: fixed; top: 0; @@ -3263,64 +4155,72 @@ input[type="submit"].btn.btn-mini { z-index: 1040; background-color: #000000; } + .modal-backdrop.fade { opacity: 0; } + .modal-backdrop, .modal-backdrop.fade.in { opacity: 0.8; filter: alpha(opacity=80); } + .modal { position: fixed; top: 50%; left: 50%; z-index: 1050; - overflow: auto; width: 560px; margin: -250px 0 0 -280px; + overflow: auto; background-color: #ffffff; border: 1px solid #999; border: 1px solid rgba(0, 0, 0, 0.3); *border: 1px solid #999; - /* IE6-7 */ - -webkit-border-radius: 6px; - -moz-border-radius: 6px; - border-radius: 6px; + -moz-border-radius: 6px; + border-radius: 6px; -webkit-box-shadow: 0 3px 7px rgba(0, 0, 0, 0.3); - -moz-box-shadow: 0 3px 7px rgba(0, 0, 0, 0.3); - box-shadow: 0 3px 7px rgba(0, 0, 0, 0.3); + -moz-box-shadow: 0 3px 7px rgba(0, 0, 0, 0.3); + box-shadow: 0 3px 7px rgba(0, 0, 0, 0.3); -webkit-background-clip: padding-box; - -moz-background-clip: padding-box; - background-clip: padding-box; + -moz-background-clip: padding-box; + background-clip: padding-box; } + .modal.fade { - -webkit-transition: opacity .3s linear, top .3s ease-out; - -moz-transition: opacity .3s linear, top .3s ease-out; - -ms-transition: opacity .3s linear, top .3s ease-out; - -o-transition: opacity .3s linear, top .3s ease-out; - transition: opacity .3s linear, top .3s ease-out; top: -25%; + -webkit-transition: opacity 0.3s linear, top 0.3s ease-out; + -moz-transition: opacity 0.3s linear, top 0.3s ease-out; + -ms-transition: opacity 0.3s linear, top 0.3s ease-out; + -o-transition: opacity 0.3s linear, top 0.3s ease-out; + transition: opacity 0.3s linear, top 0.3s ease-out; } + .modal.fade.in { top: 50%; } + .modal-header { padding: 9px 15px; border-bottom: 1px solid #eee; } + .modal-header .close { margin-top: 2px; } + .modal-body { - overflow-y: auto; max-height: 400px; padding: 15px; + overflow-y: auto; } + .modal-form { margin-bottom: 0; } + .modal-footer { padding: 14px 15px 15px; margin-bottom: 0; @@ -3328,62 +4228,74 @@ input[type="submit"].btn.btn-mini { background-color: #f5f5f5; border-top: 1px solid #ddd; -webkit-border-radius: 0 0 6px 6px; - -moz-border-radius: 0 0 6px 6px; - border-radius: 0 0 6px 6px; - -webkit-box-shadow: inset 0 1px 0 #ffffff; - -moz-box-shadow: inset 0 1px 0 #ffffff; - box-shadow: inset 0 1px 0 #ffffff; + -moz-border-radius: 0 0 6px 6px; + border-radius: 0 0 6px 6px; *zoom: 1; + -webkit-box-shadow: inset 0 1px 0 #ffffff; + -moz-box-shadow: inset 0 1px 0 #ffffff; + box-shadow: inset 0 1px 0 #ffffff; } + .modal-footer:before, .modal-footer:after { display: table; content: ""; } + .modal-footer:after { clear: both; } + .modal-footer .btn + .btn { - margin-left: 5px; margin-bottom: 0; + margin-left: 5px; } + .modal-footer .btn-group .btn + .btn { margin-left: -1px; } + .tooltip { position: absolute; z-index: 1020; display: block; - visibility: visible; padding: 5px; font-size: 11px; opacity: 0; filter: alpha(opacity=0); + visibility: visible; } + .tooltip.in { opacity: 0.8; filter: alpha(opacity=80); } + .tooltip.top { margin-top: -2px; } + .tooltip.right { margin-left: 2px; } + .tooltip.bottom { margin-top: 2px; } + .tooltip.left { margin-left: -2px; } + .tooltip.top .tooltip-arrow { bottom: 0; left: 50%; margin-left: -5px; - border-left: 5px solid transparent; - border-right: 5px solid transparent; border-top: 5px solid #000000; + border-right: 5px solid transparent; + border-left: 5px solid transparent; } + .tooltip.left .tooltip-arrow { top: 50%; right: 0; @@ -3392,22 +4304,25 @@ input[type="submit"].btn.btn-mini { border-bottom: 5px solid transparent; border-left: 5px solid #000000; } + .tooltip.bottom .tooltip-arrow { top: 0; left: 50%; margin-left: -5px; - border-left: 5px solid transparent; border-right: 5px solid transparent; border-bottom: 5px solid #000000; + border-left: 5px solid transparent; } + .tooltip.right .tooltip-arrow { top: 50%; left: 0; margin-top: -5px; border-top: 5px solid transparent; - border-bottom: 5px solid transparent; border-right: 5px solid #000000; + border-bottom: 5px solid transparent; } + .tooltip-inner { max-width: 200px; padding: 3px 8px; @@ -3416,14 +4331,16 @@ input[type="submit"].btn.btn-mini { text-decoration: none; background-color: #000000; -webkit-border-radius: 4px; - -moz-border-radius: 4px; - border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; } + .tooltip-arrow { position: absolute; width: 0; height: 0; } + .popover { position: absolute; top: 0; @@ -3432,42 +4349,50 @@ input[type="submit"].btn.btn-mini { display: none; padding: 5px; } + .popover.top { margin-top: -5px; } + .popover.right { margin-left: 5px; } + .popover.bottom { margin-top: 5px; } + .popover.left { margin-left: -5px; } + .popover.top .arrow { bottom: 0; left: 50%; margin-left: -5px; - border-left: 5px solid transparent; - border-right: 5px solid transparent; border-top: 5px solid #000000; + border-right: 5px solid transparent; + border-left: 5px solid transparent; } + .popover.right .arrow { top: 50%; left: 0; margin-top: -5px; border-top: 5px solid transparent; - border-bottom: 5px solid transparent; border-right: 5px solid #000000; + border-bottom: 5px solid transparent; } + .popover.bottom .arrow { top: 0; left: 50%; margin-left: -5px; - border-left: 5px solid transparent; border-right: 5px solid transparent; border-bottom: 5px solid #000000; + border-left: 5px solid transparent; } + .popover.left .arrow { top: 50%; right: 0; @@ -3476,211 +4401,222 @@ input[type="submit"].btn.btn-mini { border-bottom: 5px solid transparent; border-left: 5px solid #000000; } + .popover .arrow { position: absolute; width: 0; height: 0; } + .popover-inner { - padding: 3px; width: 280px; + padding: 3px; overflow: hidden; background: #000000; background: rgba(0, 0, 0, 0.8); -webkit-border-radius: 6px; - -moz-border-radius: 6px; - border-radius: 6px; + -moz-border-radius: 6px; + border-radius: 6px; -webkit-box-shadow: 0 3px 7px rgba(0, 0, 0, 0.3); - -moz-box-shadow: 0 3px 7px rgba(0, 0, 0, 0.3); - box-shadow: 0 3px 7px rgba(0, 0, 0, 0.3); + -moz-box-shadow: 0 3px 7px rgba(0, 0, 0, 0.3); + box-shadow: 0 3px 7px rgba(0, 0, 0, 0.3); } + .popover-title { padding: 9px 15px; line-height: 1; background-color: #f5f5f5; border-bottom: 1px solid #eee; -webkit-border-radius: 3px 3px 0 0; - -moz-border-radius: 3px 3px 0 0; - border-radius: 3px 3px 0 0; + -moz-border-radius: 3px 3px 0 0; + border-radius: 3px 3px 0 0; } + .popover-content { padding: 14px; background-color: #ffffff; -webkit-border-radius: 0 0 3px 3px; - -moz-border-radius: 0 0 3px 3px; - border-radius: 0 0 3px 3px; + -moz-border-radius: 0 0 3px 3px; + border-radius: 0 0 3px 3px; -webkit-background-clip: padding-box; - -moz-background-clip: padding-box; - background-clip: padding-box; + -moz-background-clip: padding-box; + background-clip: padding-box; } + .popover-content p, .popover-content ul, .popover-content ol { margin-bottom: 0; } + .thumbnails { margin-left: -20px; list-style: none; *zoom: 1; } + .thumbnails:before, .thumbnails:after { display: table; content: ""; } + .thumbnails:after { clear: both; } + +.row-fluid .thumbnails { + margin-left: 0; +} + .thumbnails > li { float: left; - margin: 0 0 18px 20px; + margin-bottom: 18px; + margin-left: 20px; } + .thumbnail { display: block; padding: 4px; line-height: 1; border: 1px solid #ddd; -webkit-border-radius: 4px; - -moz-border-radius: 4px; - border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; -webkit-box-shadow: 0 1px 1px rgba(0, 0, 0, 0.075); - -moz-box-shadow: 0 1px 1px rgba(0, 0, 0, 0.075); - box-shadow: 0 1px 1px rgba(0, 0, 0, 0.075); + -moz-box-shadow: 0 1px 1px rgba(0, 0, 0, 0.075); + box-shadow: 0 1px 1px rgba(0, 0, 0, 0.075); } + a.thumbnail:hover { border-color: #0088cc; -webkit-box-shadow: 0 1px 4px rgba(0, 105, 214, 0.25); - -moz-box-shadow: 0 1px 4px rgba(0, 105, 214, 0.25); - box-shadow: 0 1px 4px rgba(0, 105, 214, 0.25); + -moz-box-shadow: 0 1px 4px rgba(0, 105, 214, 0.25); + box-shadow: 0 1px 4px rgba(0, 105, 214, 0.25); } + .thumbnail > img { display: block; max-width: 100%; - margin-left: auto; margin-right: auto; + margin-left: auto; } + .thumbnail .caption { padding: 9px; } -.label { - padding: 1px 4px 2px; + +.label, +.badge { font-size: 10.998px; font-weight: bold; - line-height: 13px; + line-height: 14px; color: #ffffff; - vertical-align: middle; - white-space: nowrap; text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.25); + white-space: nowrap; + vertical-align: baseline; background-color: #999999; +} + +.label { + padding: 1px 4px 2px; -webkit-border-radius: 3px; - -moz-border-radius: 3px; - border-radius: 3px; -} -.label:hover { - color: #ffffff; - text-decoration: none; -} -.label-important { - background-color: #b94a48; -} -.label-important:hover { - background-color: #953b39; -} -.label-warning { - background-color: #f89406; -} -.label-warning:hover { - background-color: #c67605; -} -.label-success { - background-color: #468847; -} -.label-success:hover { - background-color: #356635; -} -.label-info { - background-color: #3a87ad; -} -.label-info:hover { - background-color: #2d6987; -} -.label-inverse { - background-color: #333333; -} -.label-inverse:hover { - background-color: #1a1a1a; + -moz-border-radius: 3px; + border-radius: 3px; } + .badge { padding: 1px 9px 2px; - font-size: 12.025px; - font-weight: bold; - white-space: nowrap; - color: #ffffff; - background-color: #999999; -webkit-border-radius: 9px; - -moz-border-radius: 9px; - border-radius: 9px; + -moz-border-radius: 9px; + border-radius: 9px; } -.badge:hover { + +a.label:hover, +a.badge:hover { color: #ffffff; text-decoration: none; cursor: pointer; } -.badge-error { + +.label-important, +.badge-important { background-color: #b94a48; } -.badge-error:hover { + +.label-important[href], +.badge-important[href] { background-color: #953b39; } + +.label-warning, .badge-warning { background-color: #f89406; } -.badge-warning:hover { + +.label-warning[href], +.badge-warning[href] { background-color: #c67605; } + +.label-success, .badge-success { background-color: #468847; } -.badge-success:hover { + +.label-success[href], +.badge-success[href] { background-color: #356635; } + +.label-info, .badge-info { background-color: #3a87ad; } -.badge-info:hover { + +.label-info[href], +.badge-info[href] { background-color: #2d6987; } + +.label-inverse, .badge-inverse { background-color: #333333; } -.badge-inverse:hover { + +.label-inverse[href], +.badge-inverse[href] { background-color: #1a1a1a; } + @-webkit-keyframes progress-bar-stripes { from { - background-position: 0 0; - } - to { background-position: 40px 0; } + to { + background-position: 0 0; + } } + @-moz-keyframes progress-bar-stripes { from { - background-position: 0 0; - } - to { background-position: 40px 0; } + to { + background-position: 0 0; + } } + @-ms-keyframes progress-bar-stripes { from { - background-position: 0 0; - } - to { background-position: 40px 0; } + to { + background-position: 0 0; + } } -@keyframes progress-bar-stripes { + +@-o-keyframes progress-bar-stripes { from { background-position: 0 0; } @@ -3688,10 +4624,20 @@ a.thumbnail:hover { background-position: 40px 0; } } + +@keyframes progress-bar-stripes { + from { + background-position: 40px 0; + } + to { + background-position: 0 0; + } +} + .progress { - overflow: hidden; height: 18px; margin-bottom: 18px; + overflow: hidden; background-color: #f7f7f7; background-image: -moz-linear-gradient(top, #f5f5f5, #f9f9f9); background-image: -ms-linear-gradient(top, #f5f5f5, #f9f9f9); @@ -3700,61 +4646,67 @@ a.thumbnail:hover { background-image: -o-linear-gradient(top, #f5f5f5, #f9f9f9); background-image: linear-gradient(top, #f5f5f5, #f9f9f9); background-repeat: repeat-x; - filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#f5f5f5', endColorstr='#f9f9f9', GradientType=0); - -webkit-box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.1); - -moz-box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.1); - box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.1); -webkit-border-radius: 4px; - -moz-border-radius: 4px; - border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; + filter: progid:dximagetransform.microsoft.gradient(startColorstr='#f5f5f5', endColorstr='#f9f9f9', GradientType=0); + -webkit-box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.1); + -moz-box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.1); + box-shadow: inset 0 1px 2px rgba(0, 0, 0, 0.1); } + .progress .bar { - width: 0%; + width: 0; height: 18px; - color: #ffffff; font-size: 12px; + color: #ffffff; text-align: center; text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.25); background-color: #0e90d2; background-image: -moz-linear-gradient(top, #149bdf, #0480be); - background-image: -ms-linear-gradient(top, #149bdf, #0480be); background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#149bdf), to(#0480be)); background-image: -webkit-linear-gradient(top, #149bdf, #0480be); background-image: -o-linear-gradient(top, #149bdf, #0480be); background-image: linear-gradient(top, #149bdf, #0480be); + background-image: -ms-linear-gradient(top, #149bdf, #0480be); background-repeat: repeat-x; - filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#149bdf', endColorstr='#0480be', GradientType=0); + filter: progid:dximagetransform.microsoft.gradient(startColorstr='#149bdf', endColorstr='#0480be', GradientType=0); -webkit-box-shadow: inset 0 -1px 0 rgba(0, 0, 0, 0.15); - -moz-box-shadow: inset 0 -1px 0 rgba(0, 0, 0, 0.15); - box-shadow: inset 0 -1px 0 rgba(0, 0, 0, 0.15); + -moz-box-shadow: inset 0 -1px 0 rgba(0, 0, 0, 0.15); + box-shadow: inset 0 -1px 0 rgba(0, 0, 0, 0.15); -webkit-box-sizing: border-box; - -moz-box-sizing: border-box; - -ms-box-sizing: border-box; - box-sizing: border-box; + -moz-box-sizing: border-box; + -ms-box-sizing: border-box; + box-sizing: border-box; -webkit-transition: width 0.6s ease; - -moz-transition: width 0.6s ease; - -ms-transition: width 0.6s ease; - -o-transition: width 0.6s ease; - transition: width 0.6s ease; + -moz-transition: width 0.6s ease; + -ms-transition: width 0.6s ease; + -o-transition: width 0.6s ease; + transition: width 0.6s ease; } + .progress-striped .bar { background-color: #149bdf; - background-image: -webkit-gradient(linear, 0 100%, 100% 0, color-stop(0.25, rgba(255, 255, 255, 0.15)), color-stop(0.25, transparent), color-stop(0.5, transparent), color-stop(0.5, rgba(255, 255, 255, 0.15)), color-stop(0.75, rgba(255, 255, 255, 0.15)), color-stop(0.75, transparent), to(transparent)); + background-image: -o-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); background-image: -webkit-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); background-image: -moz-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); background-image: -ms-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); - background-image: -o-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); + background-image: -webkit-gradient(linear, 0 100%, 100% 0, color-stop(0.25, rgba(255, 255, 255, 0.15)), color-stop(0.25, transparent), color-stop(0.5, transparent), color-stop(0.5, rgba(255, 255, 255, 0.15)), color-stop(0.75, rgba(255, 255, 255, 0.15)), color-stop(0.75, transparent), to(transparent)); background-image: linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); -webkit-background-size: 40px 40px; - -moz-background-size: 40px 40px; - -o-background-size: 40px 40px; - background-size: 40px 40px; + -moz-background-size: 40px 40px; + -o-background-size: 40px 40px; + background-size: 40px 40px; } + .progress.active .bar { -webkit-animation: progress-bar-stripes 2s linear infinite; - -moz-animation: progress-bar-stripes 2s linear infinite; - animation: progress-bar-stripes 2s linear infinite; + -moz-animation: progress-bar-stripes 2s linear infinite; + -ms-animation: progress-bar-stripes 2s linear infinite; + -o-animation: progress-bar-stripes 2s linear infinite; + animation: progress-bar-stripes 2s linear infinite; } + .progress-danger .bar { background-color: #dd514c; background-image: -moz-linear-gradient(top, #ee5f5b, #c43c35); @@ -3764,8 +4716,9 @@ a.thumbnail:hover { background-image: -o-linear-gradient(top, #ee5f5b, #c43c35); background-image: linear-gradient(top, #ee5f5b, #c43c35); background-repeat: repeat-x; - filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#ee5f5b', endColorstr='#c43c35', GradientType=0); + filter: progid:dximagetransform.microsoft.gradient(startColorstr='#ee5f5b', endColorstr='#c43c35', GradientType=0); } + .progress-danger.progress-striped .bar { background-color: #ee5f5b; background-image: -webkit-gradient(linear, 0 100%, 100% 0, color-stop(0.25, rgba(255, 255, 255, 0.15)), color-stop(0.25, transparent), color-stop(0.5, transparent), color-stop(0.5, rgba(255, 255, 255, 0.15)), color-stop(0.75, rgba(255, 255, 255, 0.15)), color-stop(0.75, transparent), to(transparent)); @@ -3775,6 +4728,7 @@ a.thumbnail:hover { background-image: -o-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); background-image: linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); } + .progress-success .bar { background-color: #5eb95e; background-image: -moz-linear-gradient(top, #62c462, #57a957); @@ -3784,8 +4738,9 @@ a.thumbnail:hover { background-image: -o-linear-gradient(top, #62c462, #57a957); background-image: linear-gradient(top, #62c462, #57a957); background-repeat: repeat-x; - filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#62c462', endColorstr='#57a957', GradientType=0); + filter: progid:dximagetransform.microsoft.gradient(startColorstr='#62c462', endColorstr='#57a957', GradientType=0); } + .progress-success.progress-striped .bar { background-color: #62c462; background-image: -webkit-gradient(linear, 0 100%, 100% 0, color-stop(0.25, rgba(255, 255, 255, 0.15)), color-stop(0.25, transparent), color-stop(0.5, transparent), color-stop(0.5, rgba(255, 255, 255, 0.15)), color-stop(0.75, rgba(255, 255, 255, 0.15)), color-stop(0.75, transparent), to(transparent)); @@ -3795,6 +4750,7 @@ a.thumbnail:hover { background-image: -o-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); background-image: linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); } + .progress-info .bar { background-color: #4bb1cf; background-image: -moz-linear-gradient(top, #5bc0de, #339bb9); @@ -3804,8 +4760,9 @@ a.thumbnail:hover { background-image: -o-linear-gradient(top, #5bc0de, #339bb9); background-image: linear-gradient(top, #5bc0de, #339bb9); background-repeat: repeat-x; - filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#5bc0de', endColorstr='#339bb9', GradientType=0); + filter: progid:dximagetransform.microsoft.gradient(startColorstr='#5bc0de', endColorstr='#339bb9', GradientType=0); } + .progress-info.progress-striped .bar { background-color: #5bc0de; background-image: -webkit-gradient(linear, 0 100%, 100% 0, color-stop(0.25, rgba(255, 255, 255, 0.15)), color-stop(0.25, transparent), color-stop(0.5, transparent), color-stop(0.5, rgba(255, 255, 255, 0.15)), color-stop(0.75, rgba(255, 255, 255, 0.15)), color-stop(0.75, transparent), to(transparent)); @@ -3815,6 +4772,7 @@ a.thumbnail:hover { background-image: -o-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); background-image: linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); } + .progress-warning .bar { background-color: #faa732; background-image: -moz-linear-gradient(top, #fbb450, #f89406); @@ -3824,8 +4782,9 @@ a.thumbnail:hover { background-image: -o-linear-gradient(top, #fbb450, #f89406); background-image: linear-gradient(top, #fbb450, #f89406); background-repeat: repeat-x; - filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#fbb450', endColorstr='#f89406', GradientType=0); + filter: progid:dximagetransform.microsoft.gradient(startColorstr='#fbb450', endColorstr='#f89406', GradientType=0); } + .progress-warning.progress-striped .bar { background-color: #fbb450; background-image: -webkit-gradient(linear, 0 100%, 100% 0, color-stop(0.25, rgba(255, 255, 255, 0.15)), color-stop(0.25, transparent), color-stop(0.5, transparent), color-stop(0.5, rgba(255, 255, 255, 0.15)), color-stop(0.75, rgba(255, 255, 255, 0.15)), color-stop(0.75, transparent), to(transparent)); @@ -3835,80 +4794,102 @@ a.thumbnail:hover { background-image: -o-linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); background-image: linear-gradient(-45deg, rgba(255, 255, 255, 0.15) 25%, transparent 25%, transparent 50%, rgba(255, 255, 255, 0.15) 50%, rgba(255, 255, 255, 0.15) 75%, transparent 75%, transparent); } + .accordion { margin-bottom: 18px; } + .accordion-group { margin-bottom: 2px; border: 1px solid #e5e5e5; -webkit-border-radius: 4px; - -moz-border-radius: 4px; - border-radius: 4px; + -moz-border-radius: 4px; + border-radius: 4px; } + .accordion-heading { border-bottom: 0; } + .accordion-heading .accordion-toggle { display: block; padding: 8px 15px; } + +.accordion-toggle { + cursor: pointer; +} + .accordion-inner { padding: 9px 15px; border-top: 1px solid #e5e5e5; } + .carousel { position: relative; margin-bottom: 18px; line-height: 1; } + .carousel-inner { - overflow: hidden; + position: relative; width: 100%; - position: relative; + overflow: hidden; } + .carousel .item { - display: none; position: relative; + display: none; -webkit-transition: 0.6s ease-in-out left; - -moz-transition: 0.6s ease-in-out left; - -ms-transition: 0.6s ease-in-out left; - -o-transition: 0.6s ease-in-out left; - transition: 0.6s ease-in-out left; + -moz-transition: 0.6s ease-in-out left; + -ms-transition: 0.6s ease-in-out left; + -o-transition: 0.6s ease-in-out left; + transition: 0.6s ease-in-out left; } + .carousel .item > img { display: block; line-height: 1; } + .carousel .active, .carousel .next, .carousel .prev { display: block; } + .carousel .active { left: 0; } + .carousel .next, .carousel .prev { position: absolute; top: 0; width: 100%; } + .carousel .next { left: 100%; } + .carousel .prev { left: -100%; } + .carousel .next.left, .carousel .prev.right { left: 0; } + .carousel .active.left { left: -100%; } + .carousel .active.right { left: 100%; } + .carousel-control { position: absolute; top: 40%; @@ -3924,67 +4905,79 @@ a.thumbnail:hover { background: #222222; border: 3px solid #ffffff; -webkit-border-radius: 23px; - -moz-border-radius: 23px; - border-radius: 23px; + -moz-border-radius: 23px; + border-radius: 23px; opacity: 0.5; filter: alpha(opacity=50); } + .carousel-control.right { - left: auto; right: 15px; + left: auto; } + .carousel-control:hover { color: #ffffff; text-decoration: none; opacity: 0.9; filter: alpha(opacity=90); } + .carousel-caption { position: absolute; - left: 0; right: 0; bottom: 0; + left: 0; padding: 10px 15px 5px; background: #333333; background: rgba(0, 0, 0, 0.75); } + .carousel-caption h4, .carousel-caption p { color: #ffffff; } + .hero-unit { padding: 60px; margin-bottom: 30px; background-color: #eeeeee; -webkit-border-radius: 6px; - -moz-border-radius: 6px; - border-radius: 6px; + -moz-border-radius: 6px; + border-radius: 6px; } + .hero-unit h1 { margin-bottom: 0; font-size: 60px; line-height: 1; - color: inherit; letter-spacing: -1px; + color: inherit; } + .hero-unit p { font-size: 18px; font-weight: 200; line-height: 27px; color: inherit; } + .pull-right { float: right; } + .pull-left { float: left; } + .hide { display: none; } + .show { display: block; } + .invisible { visibility: hidden; } From 02ec8ea01254637facb30f77b7cb74be3b735c0d Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Fri, 27 Jul 2012 15:33:24 -0400 Subject: [PATCH 139/331] much better webapp startup of the assistant This avoids forking another process, avoids polling, fixes a race, and avoids a rare forkProcess thread hang that I saw once time when starting the webapp. --- Assistant.hs | 9 ++++---- Assistant/Threads/WebApp.hs | 8 ++++--- Command/Watch.hs | 2 +- Command/WebApp.hs | 43 ++++++++++++------------------------- Utility/WebApp.hs | 5 +++-- 5 files changed, 27 insertions(+), 40 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index 6b155a4a67..ca428988fe 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -124,8 +124,8 @@ import Utility.ThreadScheduler import Control.Concurrent -startDaemon :: Bool -> Bool -> Annex () -startDaemon assistant foreground +startDaemon :: Bool -> Bool -> Maybe (IO ()) -> Annex () +startDaemon assistant foreground webappwaiter | foreground = do showStart (if assistant then "assistant" else "watch") "." go id @@ -157,12 +157,11 @@ startDaemon assistant foreground , mountWatcherThread st dstatus scanremotes , transferScannerThread st scanremotes transferqueue #ifdef WITH_WEBAPP - , webAppThread st dstatus transferqueue + , webAppThread st dstatus transferqueue webappwaiter #endif , watchThread st dstatus transferqueue changechan ] - debug "assistant" - ["all git-annex assistant threads started"] + debug "Assistant" ["all threads started"] waitForTermination stopDaemon :: Annex () diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 171c7fd9c4..f0acaeb22b 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -145,15 +145,17 @@ getConfigR = defaultLayout $ do setTitle "configuration" [whamlet|<a href="@{HomeR}">main|] -webAppThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> IO () -webAppThread st dstatus transferqueue = do +webAppThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> Maybe (IO ()) -> IO () +webAppThread st dstatus transferqueue onstartup = do webapp <- mkWebApp app <- toWaiAppPlain webapp app' <- ifM debugEnabled ( return $ httpDebugLogger app , return app ) - runWebApp app' $ \port -> runThreadState st $ writeHtmlShim webapp port + runWebApp app' $ \port -> do + runThreadState st $ writeHtmlShim webapp port + maybe noop id onstartup where mkWebApp = do dir <- absPath =<< runThreadState st (fromRepo repoPath) diff --git a/Command/Watch.hs b/Command/Watch.hs index 744844c4dc..61c859106f 100644 --- a/Command/Watch.hs +++ b/Command/Watch.hs @@ -34,5 +34,5 @@ start :: Bool -> Bool -> Bool -> CommandStart start assistant foreground stopdaemon = notBareRepo $ do if stopdaemon then stopDaemon - else startDaemon assistant foreground -- does not return + else startDaemon assistant foreground Nothing -- does not return stop diff --git a/Command/WebApp.hs b/Command/WebApp.hs index 7d0a310d40..1635ac0442 100644 --- a/Command/WebApp.hs +++ b/Command/WebApp.hs @@ -12,12 +12,8 @@ import Command import Assistant import Utility.WebApp import Utility.Daemon (checkDaemon) -import qualified Annex import Option -import Control.Concurrent -import System.Posix.Process - def :: [Command] def = [withOptions [restartOption] $ command "webapp" paramNothing seek "launch webapp"] @@ -34,31 +30,20 @@ start restart = notBareRepo $ do if restart then do stopDaemon - nuke =<< fromRepo gitAnnexPidFile + void $ liftIO . nukeFile =<< fromRepo gitAnnexPidFile startassistant f - else unlessM (checkpid f) $ - startassistant f - let url = "file://" ++ f - ifM (liftIO $ runBrowser url) - ( stop - , error $ "failed to start web browser on url " ++ url - ) + else ifM (checkpid <&&> checkshim f) $ + ( liftIO $ go f + , startassistant f + ) + stop where - nuke f = void $ liftIO $ catchMaybeIO $ removeFile f - checkpid f = do + checkpid = do pidfile <- fromRepo gitAnnexPidFile - liftIO $ - doesFileExist f <&&> (isJust <$> checkDaemon pidfile) - startassistant f = do - nuke f - {- Fork a separate process to run the assistant, - - with a copy of the Annex state. -} - state <- Annex.getState id - liftIO $ void $ forkProcess $ - Annex.eval state $ startDaemon True False - waitdaemon f (1000 :: Int) - waitdaemon _ 0 = error "failed to start git-annex assistant" - waitdaemon f n = unlessM (checkpid f) $ do - -- wait 0.1 seconds before retry - liftIO $ threadDelay 100000 - waitdaemon f (n - 1) + liftIO $ isJust <$> checkDaemon pidfile + checkshim f = liftIO $ doesFileExist f + startassistant = startDaemon True False . Just . go + go f = unlessM (runBrowser url) $ + error $ "failed to start web browser on url " ++ url + where + url = "file://" ++ f diff --git a/Utility/WebApp.hs b/Utility/WebApp.hs index 69864dc6d3..75e8dde9ec 100644 --- a/Utility/WebApp.hs +++ b/Utility/WebApp.hs @@ -32,6 +32,7 @@ import Blaze.ByteString.Builder.Char.Utf8 (fromText) import Blaze.ByteString.Builder (Builder) import Data.Monoid import Control.Arrow ((***)) +import Control.Concurrent localhost :: String localhost = "localhost" @@ -52,12 +53,12 @@ runBrowser url = boolSystem cmd [Param url] - - An IO action can also be run, to do something with the port number, - such as start a web browser to view the webapp. - -} + -} runWebApp :: Application -> (PortNumber -> IO ()) -> IO () runWebApp app observer = do sock <- localSocket + void $ forkIO $ runSettingsSocket defaultSettings sock app observer =<< socketPort sock - runSettingsSocket defaultSettings sock app {- Binds to a local socket, selecting any free port. - From adae40a292cf3192659f0edef486756431cf97da Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Fri, 27 Jul 2012 15:40:52 -0400 Subject: [PATCH 140/331] now the webapp has the same options as the assistant --- Command/WebApp.hs | 34 +++++++++++++++------------------- 1 file changed, 15 insertions(+), 19 deletions(-) diff --git a/Command/WebApp.hs b/Command/WebApp.hs index 1635ac0442..ee1274f97d 100644 --- a/Command/WebApp.hs +++ b/Command/WebApp.hs @@ -12,37 +12,33 @@ import Command import Assistant import Utility.WebApp import Utility.Daemon (checkDaemon) -import Option +import qualified Command.Watch def :: [Command] -def = [withOptions [restartOption] $ +def = [withOptions [Command.Watch.foregroundOption, Command.Watch.stopOption] $ command "webapp" paramNothing seek "launch webapp"] -restartOption :: Option -restartOption = Option.flag [] "restart" "restart the assistant daemon" - seek :: [CommandSeek] -seek = [withFlag restartOption $ \restart -> withNothing $ start restart] +seek = [withFlag Command.Watch.stopOption $ \stopdaemon -> + withFlag Command.Watch.foregroundOption $ \foreground -> + withNothing $ start foreground stopdaemon] -start :: Bool -> CommandStart -start restart = notBareRepo $ do - f <- liftIO . absPath =<< fromRepo gitAnnexHtmlShim - if restart - then do - stopDaemon - void $ liftIO . nukeFile =<< fromRepo gitAnnexPidFile - startassistant f - else ifM (checkpid <&&> checkshim f) $ - ( liftIO $ go f - , startassistant f - ) +start :: Bool -> Bool -> CommandStart +start foreground stopdaemon = notBareRepo $ do + if stopdaemon + then stopDaemon + else do + f <- liftIO . absPath =<< fromRepo gitAnnexHtmlShim + ifM (checkpid <&&> checkshim f) $ + ( liftIO $ go f + , startDaemon True foreground $ Just $ go f + ) stop where checkpid = do pidfile <- fromRepo gitAnnexPidFile liftIO $ isJust <$> checkDaemon pidfile checkshim f = liftIO $ doesFileExist f - startassistant = startDaemon True False . Just . go go f = unlessM (runBrowser url) $ error $ "failed to start web browser on url " ++ url where From 7717501fee57b614e0e86d4d46356ba26f5f5247 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Fri, 27 Jul 2012 16:28:00 -0400 Subject: [PATCH 141/331] add alert close buttons --- Assistant/Threads/WebApp.hs | 1 + static/js/bootstrap-alert.js | 94 ++++++++++++++++++++++++++++++++++++ templates/bootstrap.hamlet | 3 ++ 3 files changed, 98 insertions(+) create mode 100644 static/js/bootstrap-alert.js diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index f0acaeb22b..71ce317583 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -63,6 +63,7 @@ instance Yesod WebApp where addStylesheet $ StaticR css_bootstrap_responsive_css addScript $ StaticR jquery_full_js addScript $ StaticR js_bootstrap_dropdown_js + addScript $ StaticR js_bootstrap_alert_js $(widgetFile "default-layout") hamletToRepHtml $(hamletFile $ hamletTemplate "bootstrap") diff --git a/static/js/bootstrap-alert.js b/static/js/bootstrap-alert.js new file mode 100644 index 0000000000..d17f44e150 --- /dev/null +++ b/static/js/bootstrap-alert.js @@ -0,0 +1,94 @@ +/* ========================================================== + * bootstrap-alert.js v2.0.2 + * http://twitter.github.com/bootstrap/javascript.html#alerts + * ========================================================== + * Copyright 2012 Twitter, Inc. + * + * Licensed under the Apache License, Version 2.0 (the "License"); + * you may not use this file except in compliance with the License. + * You may obtain a copy of the License at + * + * http://www.apache.org/licenses/LICENSE-2.0 + * + * Unless required by applicable law or agreed to in writing, software + * distributed under the License is distributed on an "AS IS" BASIS, + * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. + * See the License for the specific language governing permissions and + * limitations under the License. + * ========================================================== */ + + +!function( $ ){ + + "use strict" + + /* ALERT CLASS DEFINITION + * ====================== */ + + var dismiss = '[data-dismiss="alert"]' + , Alert = function ( el ) { + $(el).on('click', dismiss, this.close) + } + + Alert.prototype = { + + constructor: Alert + + , close: function ( e ) { + var $this = $(this) + , selector = $this.attr('data-target') + , $parent + + if (!selector) { + selector = $this.attr('href') + selector = selector && selector.replace(/.*(?=#[^\s]*$)/, '') //strip for ie7 + } + + $parent = $(selector) + $parent.trigger('close') + + e && e.preventDefault() + + $parent.length || ($parent = $this.hasClass('alert') ? $this : $this.parent()) + + $parent + .trigger('close') + .removeClass('in') + + function removeElement() { + $parent + .trigger('closed') + .remove() + } + + $.support.transition && $parent.hasClass('fade') ? + $parent.on($.support.transition.end, removeElement) : + removeElement() + } + + } + + + /* ALERT PLUGIN DEFINITION + * ======================= */ + + $.fn.alert = function ( option ) { + return this.each(function () { + var $this = $(this) + , data = $this.data('alert') + if (!data) $this.data('alert', (data = new Alert(this))) + if (typeof option == 'string') data[option].call($this) + }) + } + + $.fn.alert.Constructor = Alert + + + /* ALERT DATA-API + * ============== */ + + $(function () { + $('body').on('click.alert.data-api', dismiss, Alert.prototype.close) + }) + +}( window.jQuery ); \ No newline at end of file diff --git a/templates/bootstrap.hamlet b/templates/bootstrap.hamlet index c03c459a64..6697283b4f 100644 --- a/templates/bootstrap.hamlet +++ b/templates/bootstrap.hamlet @@ -40,12 +40,15 @@ $doctype 5 <div class="span3"> <div class="sidebar-nav"> <div class="alert alert-info"> + <a class="close" data-dismiss="alert" href="#">×</a> <b>This is just a demo.</b> If this were not just a demo, I'd not be filling this sidebar with silly alerts. <div class="alert alert-success"> + <a class="close" data-dismiss="alert" href="#">×</a> <b>Well done!</b> You successfully read this important alert message. <div class="alert alert-error"> + <a class="close" data-dismiss="alert" href="#">×</a> <b>Whoops!</b> Unable to connect to blah blah.. <div class="span9"> From ecd63e29818c009bfc96d7a011bb8a2f1304e0ae Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Fri, 27 Jul 2012 20:25:28 -0400 Subject: [PATCH 142/331] template cleanup use julius's nice #id and .class things --- Assistant/Threads/WebApp.hs | 1 + static/css/webapp.css | 7 +++++ templates/bootstrap.hamlet | 54 ++++++++++++++++--------------------- templates/status.hamlet | 14 +++++----- 4 files changed, 38 insertions(+), 38 deletions(-) create mode 100644 static/css/webapp.css diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 71ce317583..5407ed1954 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -61,6 +61,7 @@ instance Yesod WebApp where page <- widgetToPageContent $ do addStylesheet $ StaticR css_bootstrap_css addStylesheet $ StaticR css_bootstrap_responsive_css + addStylesheet $ StaticR css_webapp_css addScript $ StaticR jquery_full_js addScript $ StaticR js_bootstrap_dropdown_js addScript $ StaticR js_bootstrap_alert_js diff --git a/static/css/webapp.css b/static/css/webapp.css new file mode 100644 index 0000000000..ba309effa6 --- /dev/null +++ b/static/css/webapp.css @@ -0,0 +1,7 @@ +body { + padding-top: 60px; + padding-bottom: 40px; +} +.sidebar-nav { + padding: 9px 0; +} diff --git a/templates/bootstrap.hamlet b/templates/bootstrap.hamlet index 6697283b4f..360b3d686d 100644 --- a/templates/bootstrap.hamlet +++ b/templates/bootstrap.hamlet @@ -4,52 +4,44 @@ $doctype 5 <title>#{baseTitle webapp} #{pageTitle page} <link rel="icon" href=@{StaticR favicon_ico} type="image/x-icon"> <meta name="viewport" content="width=device-width,initial-scale=1.0"> - <style type="text/css"> - body { - padding-top: 60px; - padding-bottom: 40px; - } - .sidebar-nav { - padding: 9px 0; - } ^{pageHead page} <body> - <div class="navbar navbar-fixed-top"> - <div class="navbar-inner"> - <div class="container"> - <a class="brand" href="#"> + <div .navbar .navbar-fixed-top> + <div .navbar-inner> + <div .container> + <a .brand href="#"> git-annex - <ul class="nav"> - <li class="active"> + <ul .nav> + <li .active> <a href="#">Dashboard</a> <li> <a href="@{ConfigR}">Config</a> - <ul class="nav pull-right"> - <li class="dropdown" id="menu1"> - <a class="dropdown-toggle" data-toggle="dropdown" href="#menu1"> + <ul .nav .pull-right> + <li .dropdown #menu1> + <a .dropdown-toggle data-toggle="dropdown" href="#menu1"> Current Repository: #{baseTitle webapp} - <b class="caret"></b> - <ul class="dropdown-menu"> + <b .caret></b> + <ul .dropdown-menu> <li><a href="#">#{baseTitle webapp}</a></li> - <li class="divider"></li> + <li .divider></li> <li><a href="#">Add new repository</a></li> - <div class="container-fluid"> - <div class="row-fluid"> - <div class="span3"> - <div class="sidebar-nav"> - <div class="alert alert-info"> - <a class="close" data-dismiss="alert" href="#">×</a> + <div .container-fluid> + <div .row-fluid> + <div .span3> + <div .sidebar-nav> + <div .alert .alert-info> + <a .close data-dismiss="alert" href="#">×</a> <b>This is just a demo.</b> If this were not just a demo, I'd not be filling this sidebar with silly alerts. - <div class="alert alert-success"> - <a class="close" data-dismiss="alert" href="#">×</a> + <div .alert .alert-success> + <a .close data-dismiss="alert" href="#">×</a> <b>Well done!</b> You successfully read this important alert message. - <div class="alert alert-error"> - <a class="close" data-dismiss="alert" href="#">×</a> + <div .alert .alert-error> + <a .close data-dismiss="alert" href="#">×</a> <b>Whoops!</b> Unable to connect to blah blah.. - <div class="span9"> + <div .span9> ^{pageBody page} diff --git a/templates/status.hamlet b/templates/status.hamlet index 9b9b0f7d18..2ccea1f1af 100644 --- a/templates/status.hamlet +++ b/templates/status.hamlet @@ -1,12 +1,12 @@ -<span id="#{updating}"> - <div class="span9"> +<span ##{updating}> + <div .span9> $if null transfers <h2>No current transfers $else <h2>Transfers $forall (transfer, info) <- transfers $with percent <- maybe "unknown" (showPercentage 0) $ percentComplete transfer info - <div class="row-fluid"> + <div .row-fluid> <h3> $maybe file <- associatedFile info #{file} @@ -20,11 +20,11 @@ <small>#{maybe "unknown" Remote.name $ transferRemote info}</small> $with size <- maybe "unknown" (roughSize dataUnits True) $ keySize $ transferKey transfer $if isJust $ startedTime info - <small class="pull-right"><b>#{percent} of #{size}</b></small> + <small .pull-right><b>#{percent} of #{size}</b></small> $else - <small class="pull-right">queued (#{size})</small> - <div class="progress progress-striped"> - <div class="bar" style="width: #{percent};"> + <small .pull-right>queued (#{size})</small> + <div .progress .progress-striped> + <div .bar style="width: #{percent};"> <footer> <span> polled at #{time} From c0ca6f44ac2cbe6d1cbb82bc73e2d2ead7695770 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Fri, 27 Jul 2012 20:47:48 -0400 Subject: [PATCH 143/331] template reorg --- Assistant/Threads/WebApp.hs | 3 +-- static/css/webapp.css | 7 ------ templates/bootstrap.hamlet | 40 +------------------------------ templates/default-layout.hamlet | 3 --- templates/page.cassius | 5 ++++ templates/page.hamlet | 42 +++++++++++++++++++++++++++++++++ 6 files changed, 49 insertions(+), 51 deletions(-) delete mode 100644 static/css/webapp.css delete mode 100644 templates/default-layout.hamlet create mode 100644 templates/page.cassius create mode 100644 templates/page.hamlet diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 5407ed1954..92f7ff2535 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -61,11 +61,10 @@ instance Yesod WebApp where page <- widgetToPageContent $ do addStylesheet $ StaticR css_bootstrap_css addStylesheet $ StaticR css_bootstrap_responsive_css - addStylesheet $ StaticR css_webapp_css addScript $ StaticR jquery_full_js addScript $ StaticR js_bootstrap_dropdown_js addScript $ StaticR js_bootstrap_alert_js - $(widgetFile "default-layout") + $(widgetFile "page") hamletToRepHtml $(hamletFile $ hamletTemplate "bootstrap") {- Require an auth token be set when accessing any (non-static route) -} diff --git a/static/css/webapp.css b/static/css/webapp.css deleted file mode 100644 index ba309effa6..0000000000 --- a/static/css/webapp.css +++ /dev/null @@ -1,7 +0,0 @@ -body { - padding-top: 60px; - padding-bottom: 40px; -} -.sidebar-nav { - padding: 9px 0; -} diff --git a/templates/bootstrap.hamlet b/templates/bootstrap.hamlet index 360b3d686d..389895df74 100644 --- a/templates/bootstrap.hamlet +++ b/templates/bootstrap.hamlet @@ -6,42 +6,4 @@ $doctype 5 <meta name="viewport" content="width=device-width,initial-scale=1.0"> ^{pageHead page} <body> - - <div .navbar .navbar-fixed-top> - <div .navbar-inner> - <div .container> - <a .brand href="#"> - git-annex - <ul .nav> - <li .active> - <a href="#">Dashboard</a> - <li> - <a href="@{ConfigR}">Config</a> - <ul .nav .pull-right> - <li .dropdown #menu1> - <a .dropdown-toggle data-toggle="dropdown" href="#menu1"> - Current Repository: #{baseTitle webapp} - <b .caret></b> - <ul .dropdown-menu> - <li><a href="#">#{baseTitle webapp}</a></li> - <li .divider></li> - <li><a href="#">Add new repository</a></li> - - <div .container-fluid> - <div .row-fluid> - <div .span3> - <div .sidebar-nav> - <div .alert .alert-info> - <a .close data-dismiss="alert" href="#">×</a> - <b>This is just a demo.</b> If this were not just a demo, - I'd not be filling this sidebar with silly alerts. - <div .alert .alert-success> - <a .close data-dismiss="alert" href="#">×</a> - <b>Well done!</b> - You successfully read this important alert message. - <div .alert .alert-error> - <a .close data-dismiss="alert" href="#">×</a> - <b>Whoops!</b> - Unable to connect to blah blah.. - <div .span9> - ^{pageBody page} + ^{pageBody page} diff --git a/templates/default-layout.hamlet b/templates/default-layout.hamlet deleted file mode 100644 index 3701e3c42f..0000000000 --- a/templates/default-layout.hamlet +++ /dev/null @@ -1,3 +0,0 @@ -$maybe msg <- mmsg - <div #message>#{msg} -^{widget} diff --git a/templates/page.cassius b/templates/page.cassius new file mode 100644 index 0000000000..39decd03a4 --- /dev/null +++ b/templates/page.cassius @@ -0,0 +1,5 @@ +body + padding-top: 60px + padding-bottom: 40px +.sidebar-nav + padding: 9px 0 diff --git a/templates/page.hamlet b/templates/page.hamlet new file mode 100644 index 0000000000..ae80bb05d5 --- /dev/null +++ b/templates/page.hamlet @@ -0,0 +1,42 @@ +<div .navbar .navbar-fixed-top> + <div .navbar-inner> + <div .container> + <a .brand href="#"> + git-annex + <ul .nav> + <li .active> + <a href="#">Dashboard</a> + <li> + <a href="@{ConfigR}">Config</a> + <ul .nav .pull-right> + <li .dropdown #menu1> + <a .dropdown-toggle data-toggle="dropdown" href="#menu1"> + Current Repository: #{baseTitle webapp} + <b .caret></b> + <ul .dropdown-menu> + <li><a href="#">#{baseTitle webapp}</a></li> + <li .divider></li> + <li><a href="#">Add new repository</a></li> + +<div .container-fluid> + <div .row-fluid> + <div .span3> + <div .sidebar-nav> + <div .alert .alert-info> + <a .close data-dismiss="alert" href="#">×</a> + <b>This is just a demo.</b> If this were not just a demo, + I'd not be filling this sidebar with silly alerts. + <div .alert .alert-success> + <a .close data-dismiss="alert" href="#">×</a> + <b>Well done!</b> + You successfully read this important alert message. + <div .alert .alert-error> + <a .close data-dismiss="alert" href="#">×</a> + <b>Whoops!</b> + Unable to connect to blah blah.. + <div .span9> + $maybe msg <- mmsg + <div .alert .alert-info> + <a .close data-dismiss="alert" href="#">×</a> + #{msg} + ^{widget} From ca478b7bcb48fee0d1a97340e6ea5da8e97074f0 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sat, 28 Jul 2012 15:41:49 -0400 Subject: [PATCH 144/331] Focus today was writing a notification broadcaster. This is a way to send a notification to a set of clients, any of which can be blocked waiting for a new notification to arrive. A complication is that any number of clients may be be dead, and we don't want stale notifications for those clients to pile up and leak memory. It took me 3 tries to find the solution, which turns out to be simple: An array of SampleVars, one per client. Using SampleVars means that clients only see the most recent notification, but when the notification is just "the assistant's state changed somehow; display a refreshed rendering of it", that's sufficient. --- Utility/NotificationBroadcaster.hs | 75 ++++++++++++++++++++++++++++++ 1 file changed, 75 insertions(+) create mode 100644 Utility/NotificationBroadcaster.hs diff --git a/Utility/NotificationBroadcaster.hs b/Utility/NotificationBroadcaster.hs new file mode 100644 index 0000000000..51b321752b --- /dev/null +++ b/Utility/NotificationBroadcaster.hs @@ -0,0 +1,75 @@ +{- notification broadcaster + - + - This is used to allow clients to block until there is a new notification + - that some thing occurred. It does not communicate what the change is, + - it only provides blocking reads to wait on notifications. + - + - Multiple clients are supported. Each has a unique id. + - + - Copyright 2012 Joey Hess <joey@kitenet.net> + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Assistant.NotificationBroadCaster ( + NotificationBroadCaster, + NotificationHandle, + newNotificationBroadCaster, + newNotificationHandle, + notificationHandleToId, + notificationHandleFromId, + sendNotification, + waitNotification, +) where + +import Common + +import Control.Concurrent.STM +import Control.Concurrent.SampleVar + +{- One SampleVar per client. The TMVar is never empty, so never blocks. -} +type NotificationBroadCaster = TMVar [SampleVar ()] + +{- Handle given out to an individual client. -} +data NotificationHandle = NotificationHandle NotificationBroadCaster Int + +newNotificationBroadCaster :: IO NotificationBroadCaster +newNotificationBroadCaster = atomically (newTMVar []) + +{- Allocates a notification handle for a client to use. -} +newNotificationHandle :: NotificationBroadCaster -> IO NotificationHandle +newNotificationHandle b = NotificationHandle + <$> pure b + <*> addclient b + where + addclient b = do + s <- newEmptySampleVar + atomically $ do + l <- readTMVar b + putTMVar b $ l ++ [s] + return $ length l + +{- Extracts the Int identifier from a notification handle. + - This can be used to eg, pass the identifier through to a WebApp. -} +notificationHandleToId :: NotificationHandle -> Int +notificationHandleToId (NotificationHandle _ i) = i + +{- Given a NotificationBroadCaster, and an Int identifier, recreates the + - NotificationHandle. -} +notificationHandleFromId :: NotificationBroadCaster -> Int -> NotificationHandle +notificationHandleFromId = NotificationHandle + +{- Sends a notification to all clients. -} +sendNotification :: NotificationBroadCaster -> IO () +sendNotification b = do + l <- atomically $ readTMVar b + mapM_ notify l + where + notify s = writeSampleVar s () + +{- Used by a client to block until a new notification is available since + - the last time it tried. -} +waitNotification :: NotificationHandle -> IO () +waitNotification (NotificationHandle b i) = do + l <- atomically $ readTMVar b + readSampleVar (l !! i) From a17fde22fabdb706086ac945bc331e32527b58bd Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sat, 28 Jul 2012 16:01:50 -0400 Subject: [PATCH 145/331] add a NotificationBroadcaster to DaemonStatus First use of it is to make the status checkpointer thread block until there is really a change to the status. --- Assistant/DaemonStatus.hs | 54 ++++++++++++++++++++---------- Utility/NotificationBroadcaster.hs | 26 +++++++------- 2 files changed, 50 insertions(+), 30 deletions(-) diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs index 88306a6363..84a3662f0c 100644 --- a/Assistant/DaemonStatus.hs +++ b/Assistant/DaemonStatus.hs @@ -11,6 +11,7 @@ import Common.Annex import Assistant.ThreadedMonad import Utility.ThreadScheduler import Utility.TempFile +import Utility.NotificationBroadcaster import Logs.Transfer import qualified Command.Sync @@ -34,31 +35,43 @@ data DaemonStatus = DaemonStatus , currentTransfers :: TransferMap -- Ordered list of remotes to talk to. , knownRemotes :: [Remote] + -- Clients can use this to wait on changes to the DaemonStatus + , notificationBroadcaster :: NotificationBroadcaster } - deriving (Show) type TransferMap = M.Map Transfer TransferInfo type DaemonStatusHandle = MVar DaemonStatus -newDaemonStatus :: DaemonStatus -newDaemonStatus = DaemonStatus - { scanComplete = False - , lastRunning = Nothing - , sanityCheckRunning = False - , lastSanityCheck = Nothing - , currentTransfers = M.empty - , knownRemotes = [] - } +newDaemonStatus :: IO DaemonStatus +newDaemonStatus = do + nb <- newNotificationBroadcaster + return $ DaemonStatus + { scanComplete = False + , lastRunning = Nothing + , sanityCheckRunning = False + , lastSanityCheck = Nothing + , currentTransfers = M.empty + , knownRemotes = [] + , notificationBroadcaster = nb + } getDaemonStatus :: DaemonStatusHandle -> Annex DaemonStatus getDaemonStatus = liftIO . readMVar modifyDaemonStatus_ :: DaemonStatusHandle -> (DaemonStatus -> DaemonStatus) -> Annex () -modifyDaemonStatus_ handle a = liftIO $ modifyMVar_ handle (return . a) +modifyDaemonStatus_ handle a = do + nb <- liftIO $ modifyMVar handle $ \s -> return + (a s, notificationBroadcaster s) + liftIO $ sendNotification nb modifyDaemonStatus :: DaemonStatusHandle -> (DaemonStatus -> (DaemonStatus, b)) -> Annex b -modifyDaemonStatus handle a = liftIO $ modifyMVar handle (return . a) +modifyDaemonStatus handle a = do + (b, nb) <- liftIO $ modifyMVar handle $ \s -> do + let (s', b) = a s + return $ (s', (b, notificationBroadcaster s)) + liftIO $ sendNotification nb + return b {- Updates the cached ordered list of remotes from the list in Annex - state. -} @@ -74,7 +87,7 @@ startDaemonStatus :: Annex DaemonStatusHandle startDaemonStatus = do file <- fromRepo gitAnnexDaemonStatusFile status <- liftIO $ - catchDefaultIO (readDaemonStatusFile file) newDaemonStatus + catchDefaultIO (readDaemonStatusFile file) =<< newDaemonStatus transfers <- M.fromList <$> getTransfers remotes <- Command.Sync.syncRemotes [] liftIO $ newMVar status @@ -84,11 +97,18 @@ startDaemonStatus = do , knownRemotes = remotes } -{- This thread wakes up periodically and writes the daemon status to disk. -} +{- This writes the daemon status to disk, when it changes, but no more + - frequently than once every ten minutes. + -} daemonStatusThread :: ThreadState -> DaemonStatusHandle -> IO () daemonStatusThread st handle = do + bhandle <- runThreadState st $ + liftIO . newNotificationHandle + =<< notificationBroadcaster <$> getDaemonStatus handle checkpoint - runEvery (Seconds tenMinutes) checkpoint + runEvery (Seconds tenMinutes) $ do + liftIO $ waitNotification bhandle + checkpoint where checkpoint = runThreadState st $ do file <- fromRepo gitAnnexDaemonStatusFile @@ -109,9 +129,9 @@ writeDaemonStatusFile file status = ] readDaemonStatusFile :: FilePath -> IO DaemonStatus -readDaemonStatusFile file = parse <$> readFile file +readDaemonStatusFile file = parse <$> newDaemonStatus <*> readFile file where - parse = foldr parseline newDaemonStatus . lines + parse status = foldr parseline status . lines parseline line status | key == "lastRunning" = parseval readtime $ \v -> status { lastRunning = Just v } diff --git a/Utility/NotificationBroadcaster.hs b/Utility/NotificationBroadcaster.hs index 51b321752b..caa13bbacf 100644 --- a/Utility/NotificationBroadcaster.hs +++ b/Utility/NotificationBroadcaster.hs @@ -11,10 +11,10 @@ - Licensed under the GNU GPL version 3 or higher. -} -module Assistant.NotificationBroadCaster ( - NotificationBroadCaster, +module Utility.NotificationBroadcaster ( + NotificationBroadcaster, NotificationHandle, - newNotificationBroadCaster, + newNotificationBroadcaster, newNotificationHandle, notificationHandleToId, notificationHandleFromId, @@ -28,21 +28,21 @@ import Control.Concurrent.STM import Control.Concurrent.SampleVar {- One SampleVar per client. The TMVar is never empty, so never blocks. -} -type NotificationBroadCaster = TMVar [SampleVar ()] +type NotificationBroadcaster = TMVar [SampleVar ()] {- Handle given out to an individual client. -} -data NotificationHandle = NotificationHandle NotificationBroadCaster Int +data NotificationHandle = NotificationHandle NotificationBroadcaster Int -newNotificationBroadCaster :: IO NotificationBroadCaster -newNotificationBroadCaster = atomically (newTMVar []) +newNotificationBroadcaster :: IO NotificationBroadcaster +newNotificationBroadcaster = atomically (newTMVar []) {- Allocates a notification handle for a client to use. -} -newNotificationHandle :: NotificationBroadCaster -> IO NotificationHandle +newNotificationHandle :: NotificationBroadcaster -> IO NotificationHandle newNotificationHandle b = NotificationHandle <$> pure b - <*> addclient b + <*> addclient where - addclient b = do + addclient = do s <- newEmptySampleVar atomically $ do l <- readTMVar b @@ -54,13 +54,13 @@ newNotificationHandle b = NotificationHandle notificationHandleToId :: NotificationHandle -> Int notificationHandleToId (NotificationHandle _ i) = i -{- Given a NotificationBroadCaster, and an Int identifier, recreates the +{- Given a NotificationBroadcaster, and an Int identifier, recreates the - NotificationHandle. -} -notificationHandleFromId :: NotificationBroadCaster -> Int -> NotificationHandle +notificationHandleFromId :: NotificationBroadcaster -> Int -> NotificationHandle notificationHandleFromId = NotificationHandle {- Sends a notification to all clients. -} -sendNotification :: NotificationBroadCaster -> IO () +sendNotification :: NotificationBroadcaster -> IO () sendNotification b = do l <- atomically $ readTMVar b mapM_ notify l From 3cc18857936e5a09e033439971dc9c43e6ccbaa2 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sat, 28 Jul 2012 18:02:11 -0400 Subject: [PATCH 146/331] move DaemonStatus manipulation out of the Annex monad to IO I've convinced myself that nothing in DaemonStatus can deadlock, as it always keepts the TMVar full. That was the only reason it was in the Annex monad. --- Assistant.hs | 6 ++-- Assistant/DaemonStatus.hs | 50 +++++++++++++--------------- Assistant/Threads/Pusher.hs | 3 +- Assistant/Threads/SanityChecker.hs | 24 ++++++------- Assistant/Threads/TransferWatcher.hs | 9 +++-- Assistant/Threads/Transferrer.hs | 4 +-- Assistant/Threads/Watcher.hs | 9 +++-- Assistant/Threads/WebApp.hs | 2 +- Assistant/TransferQueue.hs | 2 +- 9 files changed, 49 insertions(+), 60 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index ca428988fe..6b25c3c6f1 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -65,10 +65,8 @@ - Annex monad in IO actions run by the watcher and committer - threads. Thus, a single state is shared amoung the threads, and - only one at a time can access it. - - DaemonStatusHandle: (MVar) - - The daemon's current status. This MVar should only be manipulated - - from inside the Annex monad, which ensures it's accessed only - - after the ThreadState MVar. + - DaemonStatusHandle: (STM TMVar) + - The daemon's current status. - ChangeChan: (STM TChan) - Changes are indicated by writing to this channel. The committer - reads from it. diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs index 84a3662f0c..52165138e6 100644 --- a/Assistant/DaemonStatus.hs +++ b/Assistant/DaemonStatus.hs @@ -15,7 +15,7 @@ import Utility.NotificationBroadcaster import Logs.Transfer import qualified Command.Sync -import Control.Concurrent +import Control.Concurrent.STM import System.Posix.Types import Data.Time.Clock.POSIX import Data.Time @@ -41,7 +41,8 @@ data DaemonStatus = DaemonStatus type TransferMap = M.Map Transfer TransferInfo -type DaemonStatusHandle = MVar DaemonStatus +{- This TMVar is never left empty, so accessing it will never block. -} +type DaemonStatusHandle = TMVar DaemonStatus newDaemonStatus :: IO DaemonStatus newDaemonStatus = do @@ -56,21 +57,19 @@ newDaemonStatus = do , notificationBroadcaster = nb } -getDaemonStatus :: DaemonStatusHandle -> Annex DaemonStatus -getDaemonStatus = liftIO . readMVar +getDaemonStatus :: DaemonStatusHandle -> IO DaemonStatus +getDaemonStatus = atomically . readTMVar -modifyDaemonStatus_ :: DaemonStatusHandle -> (DaemonStatus -> DaemonStatus) -> Annex () -modifyDaemonStatus_ handle a = do - nb <- liftIO $ modifyMVar handle $ \s -> return - (a s, notificationBroadcaster s) - liftIO $ sendNotification nb +modifyDaemonStatus_ :: DaemonStatusHandle -> (DaemonStatus -> DaemonStatus) -> IO () +modifyDaemonStatus_ handle a = modifyDaemonStatus handle $ \s -> (a s, ()) -modifyDaemonStatus :: DaemonStatusHandle -> (DaemonStatus -> (DaemonStatus, b)) -> Annex b +modifyDaemonStatus :: DaemonStatusHandle -> (DaemonStatus -> (DaemonStatus, b)) -> IO b modifyDaemonStatus handle a = do - (b, nb) <- liftIO $ modifyMVar handle $ \s -> do - let (s', b) = a s - return $ (s', (b, notificationBroadcaster s)) - liftIO $ sendNotification nb + (b, nb) <- atomically $ do + (s, b) <- a <$> takeTMVar handle + putTMVar handle s + return $ (b, notificationBroadcaster s) + sendNotification nb return b {- Updates the cached ordered list of remotes from the list in Annex @@ -78,10 +77,10 @@ modifyDaemonStatus handle a = do updateKnownRemotes :: DaemonStatusHandle -> Annex () updateKnownRemotes dstatus = do remotes <- Command.Sync.syncRemotes [] - modifyDaemonStatus_ dstatus $ + liftIO $ modifyDaemonStatus_ dstatus $ \s -> s { knownRemotes = remotes } -{- Load any previous daemon status file, and store it in the MVar for this +{- Load any previous daemon status file, and store it in a MVar for this - process to use as its DaemonStatus. Also gets current transfer status. -} startDaemonStatus :: Annex DaemonStatusHandle startDaemonStatus = do @@ -90,7 +89,7 @@ startDaemonStatus = do catchDefaultIO (readDaemonStatusFile file) =<< newDaemonStatus transfers <- M.fromList <$> getTransfers remotes <- Command.Sync.syncRemotes [] - liftIO $ newMVar status + liftIO $ atomically $ newTMVar status { scanComplete = False , sanityCheckRunning = False , currentTransfers = transfers @@ -102,18 +101,17 @@ startDaemonStatus = do -} daemonStatusThread :: ThreadState -> DaemonStatusHandle -> IO () daemonStatusThread st handle = do - bhandle <- runThreadState st $ - liftIO . newNotificationHandle - =<< notificationBroadcaster <$> getDaemonStatus handle + bhandle <- newNotificationHandle + =<< notificationBroadcaster <$> getDaemonStatus handle checkpoint runEvery (Seconds tenMinutes) $ do - liftIO $ waitNotification bhandle + waitNotification bhandle checkpoint where - checkpoint = runThreadState st $ do - file <- fromRepo gitAnnexDaemonStatusFile + checkpoint = do status <- getDaemonStatus handle - liftIO $ writeDaemonStatusFile file status + file <- runThreadState st $ fromRepo gitAnnexDaemonStatusFile + writeDaemonStatusFile file status {- Don't just dump out the structure, because it will change over time, - and parts of it are not relevant. -} @@ -167,12 +165,12 @@ tenMinutes :: Int tenMinutes = 10 * 60 {- Mutates the transfer map. -} -adjustTransfers :: DaemonStatusHandle -> (TransferMap -> TransferMap) -> Annex () +adjustTransfers :: DaemonStatusHandle -> (TransferMap -> TransferMap) -> IO () adjustTransfers dstatus a = modifyDaemonStatus_ dstatus $ \s -> s { currentTransfers = a (currentTransfers s) } {- Removes a transfer from the map, and returns its info. -} -removeTransfer :: DaemonStatusHandle -> Transfer -> Annex (Maybe TransferInfo) +removeTransfer :: DaemonStatusHandle -> Transfer -> IO (Maybe TransferInfo) removeTransfer dstatus t = modifyDaemonStatus dstatus go where go s = diff --git a/Assistant/Threads/Pusher.hs b/Assistant/Threads/Pusher.hs index cba53af233..3762c48368 100644 --- a/Assistant/Threads/Pusher.hs +++ b/Assistant/Threads/Pusher.hs @@ -51,8 +51,7 @@ pushThread st daemonstatus commitchan pushmap = do now <- getCurrentTime if shouldPush now commits then do - remotes <- runThreadState st $ - knownRemotes <$> getDaemonStatus daemonstatus + remotes <- knownRemotes <$> getDaemonStatus daemonstatus pushToRemotes thisThread now st (Just pushmap) remotes else do debug thisThread diff --git a/Assistant/Threads/SanityChecker.hs b/Assistant/Threads/SanityChecker.hs index 09aee0797c..5e27246a02 100644 --- a/Assistant/Threads/SanityChecker.hs +++ b/Assistant/Threads/SanityChecker.hs @@ -26,32 +26,28 @@ thisThread = "SanityChecker" {- This thread wakes up occasionally to make sure the tree is in good shape. -} sanityCheckerThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> ChangeChan -> IO () sanityCheckerThread st status transferqueue changechan = forever $ do - waitForNextCheck st status + waitForNextCheck status debug thisThread ["starting sanity check"] - runThreadState st $ - modifyDaemonStatus_ status $ \s -> s - { sanityCheckRunning = True } + modifyDaemonStatus_ status $ \s -> s + { sanityCheckRunning = True } now <- getPOSIXTime -- before check started catchIO (check st status transferqueue changechan) (runThreadState st . warning . show) - runThreadState st $ do - modifyDaemonStatus_ status $ \s -> s - { sanityCheckRunning = False - , lastSanityCheck = Just now - } + modifyDaemonStatus_ status $ \s -> s + { sanityCheckRunning = False + , lastSanityCheck = Just now + } debug thisThread ["sanity check complete"] - {- Only run one check per day, from the time of the last check. -} -waitForNextCheck :: ThreadState -> DaemonStatusHandle -> IO () -waitForNextCheck st status = do - v <- runThreadState st $ - lastSanityCheck <$> getDaemonStatus status +waitForNextCheck :: DaemonStatusHandle -> IO () +waitForNextCheck status = do + v <- lastSanityCheck <$> getDaemonStatus status now <- getPOSIXTime threadDelaySeconds $ Seconds $ calcdelay now v where diff --git a/Assistant/Threads/TransferWatcher.hs b/Assistant/Threads/TransferWatcher.hs index be520aaf93..447ff2264f 100644 --- a/Assistant/Threads/TransferWatcher.hs +++ b/Assistant/Threads/TransferWatcher.hs @@ -55,12 +55,11 @@ onErr _ _ msg _ = error msg onAdd :: Handler onAdd st dstatus file _ = case parseTransferFile file of Nothing -> noop - Just t -> do - runThreadState st $ go t =<< checkTransfer t + Just t -> go t =<< runThreadState st (checkTransfer t) where go _ Nothing = noop -- transfer already finished go t (Just info) = do - liftIO $ debug thisThread + debug thisThread [ "transfer starting:" , show t ] @@ -71,11 +70,11 @@ onAdd st dstatus file _ = case parseTransferFile file of {- Called when a transfer information file is removed. -} onDel :: Handler -onDel st dstatus file _ = case parseTransferFile file of +onDel _ dstatus file _ = case parseTransferFile file of Nothing -> noop Just t -> do debug thisThread [ "transfer finishing:" , show t ] - void $ runThreadState st $ removeTransfer dstatus t + void $ removeTransfer dstatus t diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs index d8a1469484..30802f7428 100644 --- a/Assistant/Threads/Transferrer.hs +++ b/Assistant/Threads/Transferrer.hs @@ -48,7 +48,7 @@ transfererThread st dstatus transferqueue slots = go - being uploaded to isn't known to have the file. -} shouldTransfer :: DaemonStatusHandle -> Transfer -> TransferInfo -> Annex Bool shouldTransfer dstatus t info = - go =<< currentTransfers <$> getDaemonStatus dstatus + go =<< currentTransfers <$> liftIO (getDaemonStatus dstatus) where go m | M.member t m = return False @@ -84,7 +84,7 @@ transferThread st dstatus slots t info = case (transferRemote info, associatedFi tid <- inTransferSlot slots st $ transferprocess remote file now <- getCurrentTime - runThreadState st $ adjustTransfers dstatus $ + adjustTransfers dstatus $ M.insertWith' const t info { startedTime = Just $ utcTimeToPOSIXSeconds now , transferTid = Just tid diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs index 31025361be..ab57bf04a0 100644 --- a/Assistant/Threads/Watcher.hs +++ b/Assistant/Threads/Watcher.hs @@ -76,8 +76,7 @@ statupScan st dstatus scanner = do runThreadState st $ showAction "scanning" r <- scanner - runThreadState st $ - modifyDaemonStatus_ dstatus $ \s -> s { scanComplete = True } + modifyDaemonStatus_ dstatus $ \s -> s { scanComplete = True } -- Notice any files that were deleted before watching was started. runThreadState st $ do @@ -132,7 +131,7 @@ runHandler threadname st dstatus transferqueue changechan handler file filestatu onAdd :: Handler onAdd threadname file filestatus dstatus _ | maybe False isRegularFile filestatus = do - ifM (scanComplete <$> getDaemonStatus dstatus) + ifM (scanComplete <$> liftIO (getDaemonStatus dstatus)) ( go , ifM (null <$> inRepo (Git.LsFiles.notInRepo False [file])) ( noChange @@ -156,7 +155,7 @@ onAddSymlink threadname file filestatus dstatus transferqueue = go =<< Backend.l link <- calcGitLink file key ifM ((==) link <$> liftIO (readSymbolicLink file)) ( do - s <- getDaemonStatus dstatus + s <- liftIO $ getDaemonStatus dstatus checkcontent key s ensurestaged link s , do @@ -167,7 +166,7 @@ onAddSymlink threadname file filestatus dstatus transferqueue = go =<< Backend.l ) go Nothing = do -- other symlink link <- liftIO (readSymbolicLink file) - ensurestaged link =<< getDaemonStatus dstatus + ensurestaged link =<< liftIO (getDaemonStatus dstatus) {- This is often called on symlinks that are already - staged correctly. A symlink may have been deleted diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 92f7ff2535..6e895ccf63 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -115,7 +115,7 @@ statusDisplay = do current <- liftIO $ runThreadState (threadState webapp) $ M.toList . currentTransfers - <$> getDaemonStatus (daemonStatus webapp) + <$> liftIO (getDaemonStatus $ daemonStatus webapp) queued <- liftIO $ getTransferQueue $ transferQueue webapp let transfers = current ++ queued diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs index 414a1f9bee..2f09813eb0 100644 --- a/Assistant/TransferQueue.hs +++ b/Assistant/TransferQueue.hs @@ -59,7 +59,7 @@ stubInfo f r = TransferInfo {- Adds transfers to queue for some of the known remotes. -} queueTransfers :: Schedule -> TransferQueue -> DaemonStatusHandle -> Key -> AssociatedFile -> Direction -> Annex () queueTransfers schedule q daemonstatus k f direction = do - rs <- knownRemotes <$> getDaemonStatus daemonstatus + rs <- knownRemotes <$> liftIO (getDaemonStatus daemonstatus) mapM_ go =<< sufficientremotes rs where sufficientremotes rs From e31277d38aa5d9b07395d05a6f1646b5eb3d48c2 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sat, 28 Jul 2012 18:47:24 -0400 Subject: [PATCH 147/331] send notifications when the TransferQueue is changed The fun part was making it move things from TransferQueue to currentTransfers entirely atomically. Which will avoid inconsistent display if the WebApp renders the current status at just the wrong time. STM to the rescue! --- Assistant.hs | 2 +- Assistant/DaemonStatus.hs | 18 ++++++++- Assistant/Threads/TransferScanner.hs | 13 ++++--- Assistant/Threads/Transferrer.hs | 10 ++++- Assistant/TransferQueue.hs | 56 +++++++++++++++++----------- 5 files changed, 67 insertions(+), 32 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index 6b25c3c6f1..1f41a9398f 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -153,7 +153,7 @@ startDaemon assistant foreground webappwaiter , daemonStatusThread st dstatus , sanityCheckerThread st dstatus transferqueue changechan , mountWatcherThread st dstatus scanremotes - , transferScannerThread st scanremotes transferqueue + , transferScannerThread st dstatus scanremotes transferqueue #ifdef WITH_WEBAPP , webAppThread st dstatus transferqueue webappwaiter #endif diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs index 52165138e6..3610c2fdad 100644 --- a/Assistant/DaemonStatus.hs +++ b/Assistant/DaemonStatus.hs @@ -36,6 +36,7 @@ data DaemonStatus = DaemonStatus -- Ordered list of remotes to talk to. , knownRemotes :: [Remote] -- Clients can use this to wait on changes to the DaemonStatus + -- and other related things like the TransferQueue. , notificationBroadcaster :: NotificationBroadcaster } @@ -72,6 +73,12 @@ modifyDaemonStatus handle a = do sendNotification nb return b +{- Can be used to send a notification that the daemon status, or other + - associated thing, like the TransferQueue, has changed. -} +notifyDaemonStatusChange :: DaemonStatusHandle -> IO () +notifyDaemonStatusChange handle = sendNotification + =<< notificationBroadcaster <$> atomically (readTMVar handle) + {- Updates the cached ordered list of remotes from the list in Annex - state. -} updateKnownRemotes :: DaemonStatusHandle -> Annex () @@ -164,7 +171,16 @@ afterLastDaemonRun timestamp status = maybe False (< t) (lastRunning status) tenMinutes :: Int tenMinutes = 10 * 60 -{- Mutates the transfer map. -} +{- Mutates the transfer map. Runs in STM so that the transfer map can + - be modified in the same transaction that modifies the transfer queue. + - Note that this does not send a notification of the change; that's left + - to the caller. -} +adjustTransfersSTM :: DaemonStatusHandle -> (TransferMap -> TransferMap) -> STM () +adjustTransfersSTM dstatus a = do + s <- takeTMVar dstatus + putTMVar dstatus $ s { currentTransfers = a (currentTransfers s) } + +{- Variant that does send notifications. -} adjustTransfers :: DaemonStatusHandle -> (TransferMap -> TransferMap) -> IO () adjustTransfers dstatus a = modifyDaemonStatus_ dstatus $ \s -> s { currentTransfers = a (currentTransfers s) } diff --git a/Assistant/Threads/TransferScanner.hs b/Assistant/Threads/TransferScanner.hs index e76cbe81d3..e6a078907b 100644 --- a/Assistant/Threads/TransferScanner.hs +++ b/Assistant/Threads/TransferScanner.hs @@ -11,6 +11,7 @@ import Assistant.Common import Assistant.ScanRemotes import Assistant.TransferQueue import Assistant.ThreadedMonad +import Assistant.DaemonStatus import Logs.Transfer import Logs.Location import qualified Remote @@ -25,20 +26,20 @@ thisThread = "TransferScanner" {- This thread waits until a remote needs to be scanned, to find transfers - that need to be made, to keep data in sync. -} -transferScannerThread :: ThreadState -> ScanRemoteMap -> TransferQueue -> IO () -transferScannerThread st scanremotes transferqueue = do +transferScannerThread :: ThreadState -> DaemonStatusHandle -> ScanRemoteMap -> TransferQueue -> IO () +transferScannerThread st dstatus scanremotes transferqueue = do runEvery (Seconds 2) $ do r <- getScanRemote scanremotes liftIO $ debug thisThread ["starting scan of", show r] - scan st transferqueue r + scan st dstatus transferqueue r liftIO $ debug thisThread ["finished scan of", show r] where {- This is a naive scan through the git work tree. - - The scan is blocked when the transfer queue gets too large. -} -scan :: ThreadState -> TransferQueue -> Remote -> IO () -scan st transferqueue r = do +scan :: ThreadState -> DaemonStatusHandle -> TransferQueue -> Remote -> IO () +scan st dstatus transferqueue r = do g <- runThreadState st $ fromRepo id files <- LsFiles.inRepo [] g go files @@ -63,7 +64,7 @@ scan st transferqueue r = do | otherwise = return Nothing u = Remote.uuid r - enqueue f t = queueTransferAt smallsize Later transferqueue (Just f) t r + enqueue f t = queueTransferAt smallsize Later transferqueue dstatus (Just f) t r smallsize = 10 {- Look directly in remote for the key when it's cheap; diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs index 30802f7428..f011ff0363 100644 --- a/Assistant/Threads/Transferrer.hs +++ b/Assistant/Threads/Transferrer.hs @@ -34,12 +34,18 @@ transfererThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> Transf transfererThread st dstatus transferqueue slots = go where go = do - (t, info) <- getNextTransfer transferqueue + (t, info) <- getNextTransfer transferqueue dstatus ifM (runThreadState st $ shouldTransfer dstatus t info) ( do debug thisThread [ "Transferring:" , show t ] + notifyDaemonStatusChange dstatus transferThread st dstatus slots t info - , debug thisThread [ "Skipping unnecessary transfer:" , show t ] + , do + debug thisThread [ "Skipping unnecessary transfer:" , show t ] + -- getNextTransfer added t to the + -- daemonstatus's transfer map. + void $ removeTransfer dstatus t + notifyDaemonStatusChange dstatus ) go diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs index 2f09813eb0..51ed5c9c78 100644 --- a/Assistant/TransferQueue.hs +++ b/Assistant/TransferQueue.hs @@ -23,6 +23,7 @@ import Types.Remote import qualified Remote import Control.Concurrent.STM +import qualified Data.Map as M {- The transfer queue consists of a channel listing the transfers to make; - the size of the queue is also tracked, and a list is maintained @@ -58,8 +59,8 @@ stubInfo f r = TransferInfo {- Adds transfers to queue for some of the known remotes. -} queueTransfers :: Schedule -> TransferQueue -> DaemonStatusHandle -> Key -> AssociatedFile -> Direction -> Annex () -queueTransfers schedule q daemonstatus k f direction = do - rs <- knownRemotes <$> liftIO (getDaemonStatus daemonstatus) +queueTransfers schedule q dstatus k f direction = do + rs <- knownRemotes <$> liftIO (getDaemonStatus dstatus) mapM_ go =<< sufficientremotes rs where sufficientremotes rs @@ -80,37 +81,48 @@ queueTransfers schedule q daemonstatus k f direction = do , transferKey = k , transferUUID = Remote.uuid r } - go r = liftIO $ atomically $ - enqueue schedule q (gentransfer r) (stubInfo f r) + go r = liftIO $ + enqueue schedule q dstatus (gentransfer r) (stubInfo f r) -enqueue :: Schedule -> TransferQueue -> Transfer -> TransferInfo -> STM () -enqueue schedule q t info +enqueue :: Schedule -> TransferQueue -> DaemonStatusHandle -> Transfer -> TransferInfo -> IO () +enqueue schedule q dstatus t info | schedule == Next = go unGetTChan (new:) | otherwise = go writeTChan (\l -> l++[new]) where new = (t, info) go modqueue modlist = do - void $ modqueue (queue q) new - void $ modifyTVar' (queuesize q) succ - void $ modifyTVar' (queuelist q) modlist + atomically $ do + void $ modqueue (queue q) new + void $ modifyTVar' (queuesize q) succ + void $ modifyTVar' (queuelist q) modlist + void $ notifyDaemonStatusChange dstatus {- Adds a transfer to the queue. -} -queueTransfer :: Schedule -> TransferQueue -> AssociatedFile -> Transfer -> Remote -> IO () -queueTransfer schedule q f t remote = atomically $ - enqueue schedule q t (stubInfo f remote) +queueTransfer :: Schedule -> TransferQueue -> DaemonStatusHandle -> AssociatedFile -> Transfer -> Remote -> IO () +queueTransfer schedule q dstatus f t remote = + enqueue schedule q dstatus t (stubInfo f remote) {- Blocks until the queue is no larger than a given size, and then adds a - transfer to the queue. -} -queueTransferAt :: Integer -> Schedule -> TransferQueue -> AssociatedFile -> Transfer -> Remote -> IO () -queueTransferAt wantsz schedule q f t remote = atomically $ do - sz <- readTVar (queuesize q) - if sz <= wantsz - then enqueue schedule q t (stubInfo f remote) - else retry -- blocks until queuesize changes +queueTransferAt :: Integer -> Schedule -> TransferQueue -> DaemonStatusHandle -> AssociatedFile -> Transfer -> Remote -> IO () +queueTransferAt wantsz schedule q dstatus f t remote = do + atomically $ do + sz <- readTVar (queuesize q) + if sz <= wantsz + then return () + else retry -- blocks until queuesize changes + enqueue schedule q dstatus t (stubInfo f remote) -{- Blocks until a pending transfer is available from the queue. -} -getNextTransfer :: TransferQueue -> IO (Transfer, TransferInfo) -getNextTransfer q = atomically $ do +{- Blocks until a pending transfer is available from the queue. + - The transfer is removed from the transfer queue, and added to + - the daemon status currentTransfers map. This is done in a single STM + - transaction, so there is no window where an observer sees an + - inconsistent status. -} +getNextTransfer :: TransferQueue -> DaemonStatusHandle -> IO (Transfer, TransferInfo) +getNextTransfer q dstatus = atomically $ do void $ modifyTVar' (queuesize q) pred void $ modifyTVar' (queuelist q) (drop 1) - readTChan (queue q) + r@(t, info) <- readTChan (queue q) + adjustTransfersSTM dstatus $ + M.insertWith' const t info + return r From 109dc122da2c2fb1efdb83e5e361fe95fc4f1b16 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sat, 28 Jul 2012 20:30:46 -0400 Subject: [PATCH 148/331] add a newtype --- Utility/NotificationBroadcaster.hs | 19 +++++++++++-------- 1 file changed, 11 insertions(+), 8 deletions(-) diff --git a/Utility/NotificationBroadcaster.hs b/Utility/NotificationBroadcaster.hs index caa13bbacf..1b05329e29 100644 --- a/Utility/NotificationBroadcaster.hs +++ b/Utility/NotificationBroadcaster.hs @@ -30,8 +30,13 @@ import Control.Concurrent.SampleVar {- One SampleVar per client. The TMVar is never empty, so never blocks. -} type NotificationBroadcaster = TMVar [SampleVar ()] +newtype NotificationId = NotificationId Int + +instance Show NotificationId where + show (NotificationId i) = show i + {- Handle given out to an individual client. -} -data NotificationHandle = NotificationHandle NotificationBroadcaster Int +data NotificationHandle = NotificationHandle NotificationBroadcaster NotificationId newNotificationBroadcaster :: IO NotificationBroadcaster newNotificationBroadcaster = atomically (newTMVar []) @@ -47,16 +52,14 @@ newNotificationHandle b = NotificationHandle atomically $ do l <- readTMVar b putTMVar b $ l ++ [s] - return $ length l + return $ NotificationId $ length l -{- Extracts the Int identifier from a notification handle. +{- Extracts the identifier from a notification handle. - This can be used to eg, pass the identifier through to a WebApp. -} -notificationHandleToId :: NotificationHandle -> Int +notificationHandleToId :: NotificationHandle -> NotificationId notificationHandleToId (NotificationHandle _ i) = i -{- Given a NotificationBroadcaster, and an Int identifier, recreates the - - NotificationHandle. -} -notificationHandleFromId :: NotificationBroadcaster -> Int -> NotificationHandle +notificationHandleFromId :: NotificationBroadcaster -> NotificationId -> NotificationHandle notificationHandleFromId = NotificationHandle {- Sends a notification to all clients. -} @@ -70,6 +73,6 @@ sendNotification b = do {- Used by a client to block until a new notification is available since - the last time it tried. -} waitNotification :: NotificationHandle -> IO () -waitNotification (NotificationHandle b i) = do +waitNotification (NotificationHandle b (NotificationId i)) = do l <- atomically $ readTMVar b readSampleVar (l !! i) From 5be5cb219f1d277fbc7c8b0a33a9012fcd219a00 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sat, 28 Jul 2012 21:11:40 -0400 Subject: [PATCH 149/331] add derives needed for use with Yesod, and fix a bug --- Utility/NotificationBroadcaster.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/Utility/NotificationBroadcaster.hs b/Utility/NotificationBroadcaster.hs index 1b05329e29..c811152ff5 100644 --- a/Utility/NotificationBroadcaster.hs +++ b/Utility/NotificationBroadcaster.hs @@ -14,6 +14,7 @@ module Utility.NotificationBroadcaster ( NotificationBroadcaster, NotificationHandle, + NotificationId, newNotificationBroadcaster, newNotificationHandle, notificationHandleToId, @@ -31,6 +32,7 @@ import Control.Concurrent.SampleVar type NotificationBroadcaster = TMVar [SampleVar ()] newtype NotificationId = NotificationId Int + deriving (Read, Eq, Ord) instance Show NotificationId where show (NotificationId i) = show i @@ -39,7 +41,7 @@ instance Show NotificationId where data NotificationHandle = NotificationHandle NotificationBroadcaster NotificationId newNotificationBroadcaster :: IO NotificationBroadcaster -newNotificationBroadcaster = atomically (newTMVar []) +newNotificationBroadcaster = atomically $ newTMVar [] {- Allocates a notification handle for a client to use. -} newNotificationHandle :: NotificationBroadcaster -> IO NotificationHandle @@ -50,7 +52,7 @@ newNotificationHandle b = NotificationHandle addclient = do s <- newEmptySampleVar atomically $ do - l <- readTMVar b + l <- takeTMVar b putTMVar b $ l ++ [s] return $ NotificationId $ length l From 6a9abf652612af149be806ba8055879141929475 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sat, 28 Jul 2012 21:21:22 -0400 Subject: [PATCH 150/331] add NotificationID to StatusR, and use it to block --- Assistant/Threads/WebApp.hs | 27 ++++++++++++++++++++++----- Utility/NotificationBroadcaster.hs | 5 +---- 2 files changed, 23 insertions(+), 9 deletions(-) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 6e895ccf63..430e6f50cb 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -6,6 +6,7 @@ -} {-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings #-} +{-# OPTIONS_GHC -fno-warn-orphans #-} module Assistant.Threads.WebApp where @@ -13,6 +14,7 @@ import Assistant.Common import Assistant.ThreadedMonad import Assistant.DaemonStatus import Assistant.TransferQueue +import Utility.NotificationBroadcaster import Utility.WebApp import Utility.Yesod import Utility.FileMode @@ -49,11 +51,15 @@ staticFiles "static" mkYesod "WebApp" [parseRoutes| / HomeR GET -/status StatusR GET +/status/#NotificationId StatusR GET /config ConfigR GET /static StaticR Static getStatic |] +instance PathPiece NotificationId where + toPathPiece = pack . show + fromPathPiece = readish . unpack + instance Yesod WebApp where defaultLayout widget = do mmsg <- getMessage @@ -107,7 +113,7 @@ autoUpdate updating gethtml home ms_delay ms_startdelay = do ms_to_seconds :: Int -> Int ms_to_seconds ms = ceiling ((fromIntegral ms :: Double) / 1000) -{- Continually updating status display. -} +{- A dynamically updating status display. -} statusDisplay :: Widget statusDisplay = do webapp <- lift getYesod @@ -122,7 +128,13 @@ statusDisplay = do updating <- lift newIdent $(widgetFile "status") - autoUpdate updating StatusR HomeR (3000 :: Int) (40 :: Int) + nid <- liftIO $ notificationHandleToId <$> + (newNotificationHandle =<< getNotificationBroadcaster webapp) + autoUpdate updating (StatusR nid) HomeR (3000 :: Int) (40 :: Int) + +getNotificationBroadcaster :: WebApp -> IO NotificationBroadcaster +getNotificationBroadcaster webapp = notificationBroadcaster + <$> getDaemonStatus (daemonStatus webapp) getHomeR :: Handler RepHtml getHomeR = defaultLayout statusDisplay @@ -136,8 +148,13 @@ getHomeR = defaultLayout statusDisplay - body is. To get the widget head content, the widget is also - inserted onto the getHomeR page. -} -getStatusR :: Handler RepHtml -getStatusR = do +getStatusR :: NotificationId -> Handler RepHtml +getStatusR nid = do + {- Block until there is an updated status to display. -} + webapp <- getYesod + b <- liftIO $ getNotificationBroadcaster webapp + liftIO $ waitNotification $ notificationHandleFromId b nid + page <- widgetToPageContent statusDisplay hamletToRepHtml $ [hamlet|^{pageBody page}|] diff --git a/Utility/NotificationBroadcaster.hs b/Utility/NotificationBroadcaster.hs index c811152ff5..accc35fe18 100644 --- a/Utility/NotificationBroadcaster.hs +++ b/Utility/NotificationBroadcaster.hs @@ -32,10 +32,7 @@ import Control.Concurrent.SampleVar type NotificationBroadcaster = TMVar [SampleVar ()] newtype NotificationId = NotificationId Int - deriving (Read, Eq, Ord) - -instance Show NotificationId where - show (NotificationId i) = show i + deriving (Read, Show, Eq, Ord) {- Handle given out to an individual client. -} data NotificationHandle = NotificationHandle NotificationBroadcaster NotificationId From 9b18dc2a394560d6a6f39b61e1155b8bb512caec Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sat, 28 Jul 2012 21:25:56 -0400 Subject: [PATCH 151/331] tune javascript refresh delays WebApp now shows changes with no delay. Comparing a running git-annex get and the webapp side-by-side, they both show each new transfer at the same time. --- Assistant/Threads/WebApp.hs | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 430e6f50cb..28d1a48827 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -95,14 +95,14 @@ instance Yesod WebApp where - Or, the home route is used if the whole page has to be refreshed to - update. - - - ms_delay is how long to delay between updates. - - ms_startdelay is how long to delay before updating the widget at the - - state. + - ms_delay is how long to delay between AJAX updates + - ms_startdelay is how long to delay before updating with AJAX at the start + - ms_refreshdelay is how long to delay between refreshes, when not using AJAX -} -autoUpdate :: Text -> Route WebApp -> Route WebApp -> Int -> Int -> Widget -autoUpdate updating gethtml home ms_delay ms_startdelay = do +autoUpdate :: Text -> Route WebApp -> Route WebApp -> Int -> Int -> Int -> Widget +autoUpdate updating gethtml home ms_delay ms_startdelay ms_refreshdelay = do {- Fallback refreshing is provided for non-javascript browsers. -} - let delayseconds = show $ ms_to_seconds ms_delay + let delayseconds = show $ ms_to_seconds ms_refreshdelay toWidgetHead $(hamletFile $ hamletTemplate "metarefresh") {- Use long polling to update the status display. -} @@ -130,7 +130,7 @@ statusDisplay = do nid <- liftIO $ notificationHandleToId <$> (newNotificationHandle =<< getNotificationBroadcaster webapp) - autoUpdate updating (StatusR nid) HomeR (3000 :: Int) (40 :: Int) + autoUpdate updating (StatusR nid) HomeR (10 :: Int) (10 :: Int) (3000 :: Int) getNotificationBroadcaster :: WebApp -> IO NotificationBroadcaster getNotificationBroadcaster webapp = notificationBroadcaster From a498be7f98927370ad29221a170530a6de01b928 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sat, 28 Jul 2012 23:55:41 -0400 Subject: [PATCH 152/331] renamed /status to /transfers Also fixed a bug; the ident for the div was regnerated each time /status was called. This only was the same as the original ident due to luck. --- Assistant/Threads/WebApp.hs | 49 ++++++++++--------- git-annex.cabal | 2 +- templates/longpolling.julius | 4 +- templates/{status.hamlet => transfers.hamlet} | 5 +- 4 files changed, 29 insertions(+), 31 deletions(-) rename templates/{status.hamlet => transfers.hamlet} (94%) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 28d1a48827..4da48ae046 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -32,7 +32,6 @@ import Text.Hamlet import Network.Socket (PortNumber) import Text.Blaze.Renderer.String import Data.Text (Text, pack, unpack) -import Data.Time.Clock import qualified Data.Map as M thisThread :: String @@ -51,7 +50,7 @@ staticFiles "static" mkYesod "WebApp" [parseRoutes| / HomeR GET -/status/#NotificationId StatusR GET +/transfers/#NotificationId TransfersR GET /config ConfigR GET /static StaticR Static getStatic |] @@ -88,7 +87,7 @@ instance Yesod WebApp where {- Add to any widget to make it auto-update. - - - The widget should have a html element with id=updating, which will be + - The widget should have a html element with an id=ident, which will be - replaced when it's updated. - - Updating is done by getting html from the gethtml route. @@ -100,12 +99,12 @@ instance Yesod WebApp where - ms_refreshdelay is how long to delay between refreshes, when not using AJAX -} autoUpdate :: Text -> Route WebApp -> Route WebApp -> Int -> Int -> Int -> Widget -autoUpdate updating gethtml home ms_delay ms_startdelay ms_refreshdelay = do +autoUpdate ident gethtml home ms_delay ms_startdelay ms_refreshdelay = do {- Fallback refreshing is provided for non-javascript browsers. -} let delayseconds = show $ ms_to_seconds ms_refreshdelay toWidgetHead $(hamletFile $ hamletTemplate "metarefresh") - {- Use long polling to update the status display. -} + {- Use long polling to update the transfers display. -} let delay = show ms_delay let startdelay = show ms_startdelay $(widgetFile "longpolling") @@ -113,49 +112,51 @@ autoUpdate updating gethtml home ms_delay ms_startdelay ms_refreshdelay = do ms_to_seconds :: Int -> Int ms_to_seconds ms = ceiling ((fromIntegral ms :: Double) / 1000) -{- A dynamically updating status display. -} -statusDisplay :: Widget -statusDisplay = do +{- A display of currently running and queued transfers. -} +transfersDisplay :: Widget +transfersDisplay = do webapp <- lift getYesod - time <- show <$> liftIO getCurrentTime - current <- liftIO $ runThreadState (threadState webapp) $ M.toList . currentTransfers <$> liftIO (getDaemonStatus $ daemonStatus webapp) queued <- liftIO $ getTransferQueue $ transferQueue webapp let transfers = current ++ queued + let ident = transfersDisplayIdent + $(widgetFile "transfers") - updating <- lift newIdent - $(widgetFile "status") - - nid <- liftIO $ notificationHandleToId <$> - (newNotificationHandle =<< getNotificationBroadcaster webapp) - autoUpdate updating (StatusR nid) HomeR (10 :: Int) (10 :: Int) (3000 :: Int) +transfersDisplayIdent :: Text +transfersDisplayIdent = "transfers" getNotificationBroadcaster :: WebApp -> IO NotificationBroadcaster getNotificationBroadcaster webapp = notificationBroadcaster <$> getDaemonStatus (daemonStatus webapp) getHomeR :: Handler RepHtml -getHomeR = defaultLayout statusDisplay +getHomeR = defaultLayout $ do + {- Set up automatic updates for the transfers display. -} + webapp <- lift getYesod + nid <- liftIO $ notificationHandleToId <$> + (newNotificationHandle =<< getNotificationBroadcaster webapp) + autoUpdate transfersDisplayIdent (TransfersR nid) HomeR + (10 :: Int) (10 :: Int) (3000 :: Int) + transfersDisplay -{- Called by client to poll for a new webapp status display. +{- Called by client to get a display of currently in process transfers. - - - Should block until the status has changed, and then return a div - - containing the new status, which will be inserted into the calling page. + - Returns a div, which will be inserted into the calling page. - - Note that the head of the widget is not included, only its - body is. To get the widget head content, the widget is also - inserted onto the getHomeR page. -} -getStatusR :: NotificationId -> Handler RepHtml -getStatusR nid = do - {- Block until there is an updated status to display. -} +getTransfersR :: NotificationId -> Handler RepHtml +getTransfersR nid = do + {- Block until there is a change from last time. -} webapp <- getYesod b <- liftIO $ getNotificationBroadcaster webapp liftIO $ waitNotification $ notificationHandleFromId b nid - page <- widgetToPageContent statusDisplay + page <- widgetToPageContent transfersDisplay hamletToRepHtml $ [hamlet|^{pageBody page}|] getConfigR :: Handler RepHtml diff --git a/git-annex.cabal b/git-annex.cabal index 24e0df9c99..afa8814253 100644 --- a/git-annex.cabal +++ b/git-annex.cabal @@ -1,5 +1,5 @@ Name: git-annex -Version: 3.20120721 +Version: 3.20120722 Cabal-Version: >= 1.8 License: GPL Maintainer: Joey Hess <joey@kitenet.net> diff --git a/templates/longpolling.julius b/templates/longpolling.julius index eff8d3f444..945ef1251f 100644 --- a/templates/longpolling.julius +++ b/templates/longpolling.julius @@ -1,5 +1,5 @@ -// Uses long-polling to update a div with id=#{updating} +// Uses long-polling to update a div with id=#{ident} // The gethtml route should return a new div, with the same id. // // Maximum update frequency is controlled by #{startdelay} @@ -16,7 +16,7 @@ $.LongPoll = (function() { 'url': '@{gethtml}', 'dataType': 'html', 'success': function(data, status, jqxhr) { - $('##{updating}').replaceWith(data); + $('##{ident}').replaceWith(data); setTimeout($.LongPoll.send, #{delay}); numerrs=0; }, diff --git a/templates/status.hamlet b/templates/transfers.hamlet similarity index 94% rename from templates/status.hamlet rename to templates/transfers.hamlet index 2ccea1f1af..154e8d58b3 100644 --- a/templates/status.hamlet +++ b/templates/transfers.hamlet @@ -1,4 +1,4 @@ -<span ##{updating}> +<span ##{ident}> <div .span9> $if null transfers <h2>No current transfers @@ -25,6 +25,3 @@ <small .pull-right>queued (#{size})</small> <div .progress .progress-striped> <div .bar style="width: #{percent};"> - <footer> - <span> - polled at #{time} From 376f8443c1786a1acbaaf24fc7c4f8a662f0ef38 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 00:08:14 -0400 Subject: [PATCH 153/331] add a separate page for noscript browsers This may be customised differently than the main page later on, but for now the important thing is that this constantly refreshed page does not allocate a new NotificationHandle each time it's loaded. --- Assistant/Threads/WebApp.hs | 18 ++++++++++++++++-- templates/metarefresh.hamlet | 2 +- 2 files changed, 17 insertions(+), 3 deletions(-) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 4da48ae046..d9d98e1bf3 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -50,6 +50,7 @@ staticFiles "static" mkYesod "WebApp" [parseRoutes| / HomeR GET +/noscript NoScriptR GET /transfers/#NotificationId TransfersR GET /config ConfigR GET /static StaticR Static getStatic @@ -101,7 +102,7 @@ instance Yesod WebApp where autoUpdate :: Text -> Route WebApp -> Route WebApp -> Int -> Int -> Int -> Widget autoUpdate ident gethtml home ms_delay ms_startdelay ms_refreshdelay = do {- Fallback refreshing is provided for non-javascript browsers. -} - let delayseconds = show $ ms_to_seconds ms_refreshdelay + let delayseconds = ms_to_seconds ms_refreshdelay toWidgetHead $(hamletFile $ hamletTemplate "metarefresh") {- Use long polling to update the transfers display. -} @@ -131,6 +132,9 @@ getNotificationBroadcaster :: WebApp -> IO NotificationBroadcaster getNotificationBroadcaster webapp = notificationBroadcaster <$> getDaemonStatus (daemonStatus webapp) +dashboard :: Widget +dashboard = transfersDisplay + getHomeR :: Handler RepHtml getHomeR = defaultLayout $ do {- Set up automatic updates for the transfers display. -} @@ -139,7 +143,17 @@ getHomeR = defaultLayout $ do (newNotificationHandle =<< getNotificationBroadcaster webapp) autoUpdate transfersDisplayIdent (TransfersR nid) HomeR (10 :: Int) (10 :: Int) (3000 :: Int) - transfersDisplay + + dashboard + +{- Same as HomeR, except with no javascript, so it doesn't allocate + - new resources each time the page is refreshed. -} +getNoScriptR :: Handler RepHtml +getNoScriptR = defaultLayout $ do + let ident = NoScriptR + let delayseconds = 3 :: Int + toWidgetHead $(hamletFile $ hamletTemplate "metarefresh") + dashboard {- Called by client to get a display of currently in process transfers. - diff --git a/templates/metarefresh.hamlet b/templates/metarefresh.hamlet index be22aa8992..ddbd225fe2 100644 --- a/templates/metarefresh.hamlet +++ b/templates/metarefresh.hamlet @@ -1,2 +1,2 @@ <noscript> - <meta http-equiv="refresh" content="#{delayseconds}; URL=@{home}"> + <meta http-equiv="refresh" content="#{show delayseconds}; URL=@{NoScriptR}"> From 38ade1af70a08d278a56bcec4f7a9e32b09f4336 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 00:55:22 -0400 Subject: [PATCH 154/331] better noscript UI --- Assistant/Threads/WebApp.hs | 44 +++++++++++++++++------------------- templates/longpolling.julius | 6 ++--- templates/metarefresh.hamlet | 2 +- templates/transfers.hamlet | 13 +++++++++++ 4 files changed, 38 insertions(+), 27 deletions(-) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index d9d98e1bf3..e47ee9fdac 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -51,6 +51,7 @@ staticFiles "static" mkYesod "WebApp" [parseRoutes| / HomeR GET /noscript NoScriptR GET +/noscriptauto NoScriptAutoR GET /transfers/#NotificationId TransfersR GET /config ConfigR GET /static StaticR Static getStatic @@ -86,7 +87,7 @@ instance Yesod WebApp where makeSessionBackend = webAppSessionBackend jsLoader _ = BottomOfHeadBlocking -{- Add to any widget to make it auto-update. +{- Add to any widget to make it auto-update using long polling. - - The widget should have a html element with an id=ident, which will be - replaced when it's updated. @@ -97,25 +98,16 @@ instance Yesod WebApp where - - ms_delay is how long to delay between AJAX updates - ms_startdelay is how long to delay before updating with AJAX at the start - - ms_refreshdelay is how long to delay between refreshes, when not using AJAX -} -autoUpdate :: Text -> Route WebApp -> Route WebApp -> Int -> Int -> Int -> Widget -autoUpdate ident gethtml home ms_delay ms_startdelay ms_refreshdelay = do - {- Fallback refreshing is provided for non-javascript browsers. -} - let delayseconds = ms_to_seconds ms_refreshdelay - toWidgetHead $(hamletFile $ hamletTemplate "metarefresh") - - {- Use long polling to update the transfers display. -} +autoUpdate :: Text -> Route WebApp -> Route WebApp -> Int -> Int -> Widget +autoUpdate ident gethtml home ms_delay ms_startdelay = do let delay = show ms_delay let startdelay = show ms_startdelay $(widgetFile "longpolling") - where - ms_to_seconds :: Int -> Int - ms_to_seconds ms = ceiling ((fromIntegral ms :: Double) / 1000) {- A display of currently running and queued transfers. -} -transfersDisplay :: Widget -transfersDisplay = do +transfersDisplay :: Bool -> Widget +transfersDisplay warnNoScript = do webapp <- lift getYesod current <- liftIO $ runThreadState (threadState webapp) $ M.toList . currentTransfers @@ -132,8 +124,8 @@ getNotificationBroadcaster :: WebApp -> IO NotificationBroadcaster getNotificationBroadcaster webapp = notificationBroadcaster <$> getDaemonStatus (daemonStatus webapp) -dashboard :: Widget -dashboard = transfersDisplay +dashboard :: Bool -> Widget +dashboard warnNoScript = transfersDisplay warnNoScript getHomeR :: Handler RepHtml getHomeR = defaultLayout $ do @@ -142,18 +134,24 @@ getHomeR = defaultLayout $ do nid <- liftIO $ notificationHandleToId <$> (newNotificationHandle =<< getNotificationBroadcaster webapp) autoUpdate transfersDisplayIdent (TransfersR nid) HomeR - (10 :: Int) (10 :: Int) (3000 :: Int) + (10 :: Int) (10 :: Int) - dashboard + dashboard True {- Same as HomeR, except with no javascript, so it doesn't allocate - - new resources each time the page is refreshed. -} -getNoScriptR :: Handler RepHtml -getNoScriptR = defaultLayout $ do + - new resources each time the page is refreshed, and with autorefreshing + - via meta refresh. -} +getNoScriptAutoR :: Handler RepHtml +getNoScriptAutoR = defaultLayout $ do let ident = NoScriptR let delayseconds = 3 :: Int + let this = NoScriptAutoR toWidgetHead $(hamletFile $ hamletTemplate "metarefresh") - dashboard + dashboard False + +getNoScriptR :: Handler RepHtml +getNoScriptR = defaultLayout $ + dashboard True {- Called by client to get a display of currently in process transfers. - @@ -170,7 +168,7 @@ getTransfersR nid = do b <- liftIO $ getNotificationBroadcaster webapp liftIO $ waitNotification $ notificationHandleFromId b nid - page <- widgetToPageContent transfersDisplay + page <- widgetToPageContent $ transfersDisplay False hamletToRepHtml $ [hamlet|^{pageBody page}|] getConfigR :: Handler RepHtml diff --git a/templates/longpolling.julius b/templates/longpolling.julius index 945ef1251f..926249a35d 100644 --- a/templates/longpolling.julius +++ b/templates/longpolling.julius @@ -17,7 +17,7 @@ $.LongPoll = (function() { 'dataType': 'html', 'success': function(data, status, jqxhr) { $('##{ident}').replaceWith(data); - setTimeout($.LongPoll.send, #{delay}); + setTimeout($.LongPoll.send, #{show delay}); numerrs=0; }, 'error': function(jqxhr, msg, e) { @@ -26,7 +26,7 @@ $.LongPoll = (function() { window.close(); } else { - setTimeout($.LongPoll.send, #{delay}); + setTimeout($.LongPoll.send, #{show delay}); } }, }); @@ -35,7 +35,7 @@ $.LongPoll = (function() { }()); $(document).bind('ready.app', function() { - setTimeout($.LongPoll.send, #{startdelay}); + setTimeout($.LongPoll.send, #{show startdelay}); }); })( jQuery ); diff --git a/templates/metarefresh.hamlet b/templates/metarefresh.hamlet index ddbd225fe2..89a2e0b2c6 100644 --- a/templates/metarefresh.hamlet +++ b/templates/metarefresh.hamlet @@ -1,2 +1,2 @@ <noscript> - <meta http-equiv="refresh" content="#{show delayseconds}; URL=@{NoScriptR}"> + <meta http-equiv="refresh" content="#{show delayseconds}; URL=@{this}"> diff --git a/templates/transfers.hamlet b/templates/transfers.hamlet index 154e8d58b3..5df4533154 100644 --- a/templates/transfers.hamlet +++ b/templates/transfers.hamlet @@ -1,4 +1,17 @@ <span ##{ident}> + $if warnNoScript + <noscript> + <div .alert .alert-block> + <h4 .alert-heading>Javascript is disabled + <p> + This display cannot update in real-time without Javascript. # + Can you turn it on? + <p> + Otherwise, there are two options: + <p> + <div .btn-group> + <a .btn href="@{NoScriptAutoR}">Auto-refresh every 3 seconds # + <a .btn href="@{NoScriptR}">Manually refresh <div .span9> $if null transfers <h2>No current transfers From e96107caf3745d658a36e0ad7716dd07a57657a2 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 01:09:29 -0400 Subject: [PATCH 155/331] move noscript UI to bottom navbar --- templates/transfers.hamlet | 22 +++++++++------------- 1 file changed, 9 insertions(+), 13 deletions(-) diff --git a/templates/transfers.hamlet b/templates/transfers.hamlet index 5df4533154..417ba3d62a 100644 --- a/templates/transfers.hamlet +++ b/templates/transfers.hamlet @@ -1,17 +1,4 @@ <span ##{ident}> - $if warnNoScript - <noscript> - <div .alert .alert-block> - <h4 .alert-heading>Javascript is disabled - <p> - This display cannot update in real-time without Javascript. # - Can you turn it on? - <p> - Otherwise, there are two options: - <p> - <div .btn-group> - <a .btn href="@{NoScriptAutoR}">Auto-refresh every 3 seconds # - <a .btn href="@{NoScriptR}">Manually refresh <div .span9> $if null transfers <h2>No current transfers @@ -38,3 +25,12 @@ <small .pull-right>queued (#{size})</small> <div .progress .progress-striped> <div .bar style="width: #{percent};"> + $if warnNoScript + <noscript> + <div .navbar .navbar-fixed-bottom> + <div .navbar-inner> + <div .container> + Javascript is disabled; cannot update in real-time. + <div .btn-group> + <a .btn .btn-primary href="@{NoScriptAutoR}">Auto-refresh every 3 seconds # + <a .btn .btn-primary href="@{NoScriptR}">Manually refresh From 62dac858807da8fb62ce55adbed84cfe582367b2 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 03:23:17 -0400 Subject: [PATCH 156/331] update the sidebar by long polling Needs to use a different NotificationBroadcaster, and not replace the whole sidebar div, but instead add in new content. However, it's 3:30 am. --- Assistant/Threads/WebApp.hs | 110 ++++++++++++++++++++++------------- templates/longpolling.julius | 8 +-- templates/page.hamlet | 21 +------ templates/sidebar.hamlet | 18 ++++++ templates/transfers.hamlet | 53 +++++++++-------- 5 files changed, 120 insertions(+), 90 deletions(-) create mode 100644 templates/sidebar.hamlet diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index e47ee9fdac..500297693b 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -33,6 +33,7 @@ import Network.Socket (PortNumber) import Text.Blaze.Renderer.String import Data.Text (Text, pack, unpack) import qualified Data.Map as M +import Data.Time.Clock thisThread :: String thisThread = "WebApp" @@ -46,6 +47,10 @@ data WebApp = WebApp , getStatic :: Static } +getNotificationBroadcaster :: WebApp -> IO NotificationBroadcaster +getNotificationBroadcaster webapp = notificationBroadcaster + <$> getDaemonStatus (daemonStatus webapp) + staticFiles "static" mkYesod "WebApp" [parseRoutes| @@ -53,6 +58,7 @@ mkYesod "WebApp" [parseRoutes| /noscript NoScriptR GET /noscriptauto NoScriptAutoR GET /transfers/#NotificationId TransfersR GET +/sidebar/#NotificationId SideBarR GET /config ConfigR GET /static StaticR Static getStatic |] @@ -62,8 +68,7 @@ instance PathPiece NotificationId where fromPathPiece = readish . unpack instance Yesod WebApp where - defaultLayout widget = do - mmsg <- getMessage + defaultLayout content = do webapp <- getYesod page <- widgetToPageContent $ do addStylesheet $ StaticR css_bootstrap_css @@ -93,14 +98,12 @@ instance Yesod WebApp where - replaced when it's updated. - - Updating is done by getting html from the gethtml route. - - Or, the home route is used if the whole page has to be refreshed to - - update. - - ms_delay is how long to delay between AJAX updates - ms_startdelay is how long to delay before updating with AJAX at the start -} -autoUpdate :: Text -> Route WebApp -> Route WebApp -> Int -> Int -> Widget -autoUpdate ident gethtml home ms_delay ms_startdelay = do +autoUpdate :: Text -> Route WebApp -> Int -> Int -> Widget +autoUpdate ident gethtml ms_delay ms_startdelay = do let delay = show ms_delay let startdelay = show ms_startdelay $(widgetFile "longpolling") @@ -120,39 +123,6 @@ transfersDisplay warnNoScript = do transfersDisplayIdent :: Text transfersDisplayIdent = "transfers" -getNotificationBroadcaster :: WebApp -> IO NotificationBroadcaster -getNotificationBroadcaster webapp = notificationBroadcaster - <$> getDaemonStatus (daemonStatus webapp) - -dashboard :: Bool -> Widget -dashboard warnNoScript = transfersDisplay warnNoScript - -getHomeR :: Handler RepHtml -getHomeR = defaultLayout $ do - {- Set up automatic updates for the transfers display. -} - webapp <- lift getYesod - nid <- liftIO $ notificationHandleToId <$> - (newNotificationHandle =<< getNotificationBroadcaster webapp) - autoUpdate transfersDisplayIdent (TransfersR nid) HomeR - (10 :: Int) (10 :: Int) - - dashboard True - -{- Same as HomeR, except with no javascript, so it doesn't allocate - - new resources each time the page is refreshed, and with autorefreshing - - via meta refresh. -} -getNoScriptAutoR :: Handler RepHtml -getNoScriptAutoR = defaultLayout $ do - let ident = NoScriptR - let delayseconds = 3 :: Int - let this = NoScriptAutoR - toWidgetHead $(hamletFile $ hamletTemplate "metarefresh") - dashboard False - -getNoScriptR :: Handler RepHtml -getNoScriptR = defaultLayout $ - dashboard True - {- Called by client to get a display of currently in process transfers. - - Returns a div, which will be inserted into the calling page. @@ -171,8 +141,70 @@ getTransfersR nid = do page <- widgetToPageContent $ transfersDisplay False hamletToRepHtml $ [hamlet|^{pageBody page}|] +sideBarDisplay :: Bool -> Widget +sideBarDisplay noScript = do + date <- liftIO $ show <$> getCurrentTime + ident <- lift newIdent + mmsg <- lift getMessage + $(widgetFile "sidebar") + unless noScript $ do + {- Set up automatic updates of the sidebar. -} + webapp <- lift getYesod + nid <- liftIO $ notificationHandleToId <$> + (newNotificationHandle =<< getNotificationBroadcaster webapp) + autoUpdate ident (SideBarR nid) (10 :: Int) (10 :: Int) + +{- Called by client to get a sidebar display. + - + - Returns a div, which will be inserted into the calling page. + - + - Note that the head of the widget is not included, only its + - body is. To get the widget head content, the widget is also + - inserted onto all pages. + -} +getSideBarR :: NotificationId -> Handler RepHtml +getSideBarR nid = do + {- Block until there is a change from last time. -} + webapp <- getYesod + b <- liftIO $ getNotificationBroadcaster webapp + liftIO $ waitNotification $ notificationHandleFromId b nid + + page <- widgetToPageContent $ sideBarDisplay True + hamletToRepHtml $ [hamlet|^{pageBody page}|] + +dashboard :: Bool -> Bool -> Widget +dashboard noScript warnNoScript = do + sideBarDisplay noScript + transfersDisplay warnNoScript + +getHomeR :: Handler RepHtml +getHomeR = defaultLayout $ do + {- Set up automatic updates for the transfers display. -} + webapp <- lift getYesod + nid <- liftIO $ notificationHandleToId <$> + (newNotificationHandle =<< getNotificationBroadcaster webapp) + autoUpdate transfersDisplayIdent (TransfersR nid) (10 :: Int) (10 :: Int) + + dashboard False True + +{- Same as HomeR, except with no javascript, so it doesn't allocate + - new resources each time the page is refreshed, and with autorefreshing + - via meta refresh. -} +getNoScriptAutoR :: Handler RepHtml +getNoScriptAutoR = defaultLayout $ do + let ident = NoScriptR + let delayseconds = 3 :: Int + let this = NoScriptAutoR + toWidgetHead $(hamletFile $ hamletTemplate "metarefresh") + dashboard True False + +getNoScriptR :: Handler RepHtml +getNoScriptR = defaultLayout $ + dashboard True True + getConfigR :: Handler RepHtml getConfigR = defaultLayout $ do + sideBarDisplay False setTitle "configuration" [whamlet|<a href="@{HomeR}">main|] diff --git a/templates/longpolling.julius b/templates/longpolling.julius index 926249a35d..95425d615a 100644 --- a/templates/longpolling.julius +++ b/templates/longpolling.julius @@ -9,7 +9,7 @@ numerrs=0; -$.LongPoll = (function() { +$.LongPoll#{ident} = (function() { return { send : function() { $.ajax({ @@ -17,7 +17,7 @@ $.LongPoll = (function() { 'dataType': 'html', 'success': function(data, status, jqxhr) { $('##{ident}').replaceWith(data); - setTimeout($.LongPoll.send, #{show delay}); + setTimeout($.LongPoll#{ident}.send, #{show delay}); numerrs=0; }, 'error': function(jqxhr, msg, e) { @@ -26,7 +26,7 @@ $.LongPoll = (function() { window.close(); } else { - setTimeout($.LongPoll.send, #{show delay}); + setTimeout($.LongPoll#{ident}.send, #{show delay}); } }, }); @@ -35,7 +35,7 @@ $.LongPoll = (function() { }()); $(document).bind('ready.app', function() { - setTimeout($.LongPoll.send, #{show startdelay}); + setTimeout($.LongPoll#{ident}.send, #{show startdelay}); }); })( jQuery ); diff --git a/templates/page.hamlet b/templates/page.hamlet index ae80bb05d5..c397d248c2 100644 --- a/templates/page.hamlet +++ b/templates/page.hamlet @@ -20,23 +20,4 @@ <div .container-fluid> <div .row-fluid> - <div .span3> - <div .sidebar-nav> - <div .alert .alert-info> - <a .close data-dismiss="alert" href="#">×</a> - <b>This is just a demo.</b> If this were not just a demo, - I'd not be filling this sidebar with silly alerts. - <div .alert .alert-success> - <a .close data-dismiss="alert" href="#">×</a> - <b>Well done!</b> - You successfully read this important alert message. - <div .alert .alert-error> - <a .close data-dismiss="alert" href="#">×</a> - <b>Whoops!</b> - Unable to connect to blah blah.. - <div .span9> - $maybe msg <- mmsg - <div .alert .alert-info> - <a .close data-dismiss="alert" href="#">×</a> - #{msg} - ^{widget} + ^{content} diff --git a/templates/sidebar.hamlet b/templates/sidebar.hamlet new file mode 100644 index 0000000000..3b5048151b --- /dev/null +++ b/templates/sidebar.hamlet @@ -0,0 +1,18 @@ +<div .span3 ##{ident}> + <div .sidebar-nav> + $maybe msg <- mmsg + <div .alert .alert-info> + <a .close data-dismiss="alert" href="#">×</a> + #{msg} + <div .alert .alert-info> + <a .close data-dismiss="alert" href="#">×</a> + <b>This is just a demo.</b> If this were not just a demo, + I'd not be filling this sidebar with silly alerts. + <div .alert .alert-success> + <a .close data-dismiss="alert" href="#">×</a> + <b>Well done!</b> + You successfully read this important alert message. + <div .alert .alert-error> + <a .close data-dismiss="alert" href="#">×</a> + <b>Whoops!</b> + Unable to connect to blah blah.. #{date} diff --git a/templates/transfers.hamlet b/templates/transfers.hamlet index 417ba3d62a..bc69d7f876 100644 --- a/templates/transfers.hamlet +++ b/templates/transfers.hamlet @@ -1,30 +1,29 @@ -<span ##{ident}> - <div .span9> - $if null transfers - <h2>No current transfers - $else - <h2>Transfers - $forall (transfer, info) <- transfers - $with percent <- maybe "unknown" (showPercentage 0) $ percentComplete transfer info - <div .row-fluid> - <h3> - $maybe file <- associatedFile info - #{file} - $nothing - #{show $ transferKey transfer} - $case transferDirection transfer - $of Upload - → - $of Download - ← - <small>#{maybe "unknown" Remote.name $ transferRemote info}</small> - $with size <- maybe "unknown" (roughSize dataUnits True) $ keySize $ transferKey transfer - $if isJust $ startedTime info - <small .pull-right><b>#{percent} of #{size}</b></small> - $else - <small .pull-right>queued (#{size})</small> - <div .progress .progress-striped> - <div .bar style="width: #{percent};"> +<div .span9 ##{ident}> + $if null transfers + <h2>No current transfers + $else + <h2>Transfers + $forall (transfer, info) <- transfers + $with percent <- maybe "unknown" (showPercentage 0) $ percentComplete transfer info + <div .row-fluid> + <h3> + $maybe file <- associatedFile info + #{file} + $nothing + #{show $ transferKey transfer} + $case transferDirection transfer + $of Upload + → + $of Download + ← + <small>#{maybe "unknown" Remote.name $ transferRemote info}</small> + $with size <- maybe "unknown" (roughSize dataUnits True) $ keySize $ transferKey transfer + $if isJust $ startedTime info + <small .pull-right><b>#{percent} of #{size}</b></small> + $else + <small .pull-right>queued (#{size})</small> + <div .progress .progress-striped> + <div .bar style="width: #{percent};"> $if warnNoScript <noscript> <div .navbar .navbar-fixed-bottom> From 57203e39811e4e769a6feb576a8779707664c40d Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 08:52:57 -0400 Subject: [PATCH 157/331] refactor --- Assistant/DaemonStatus.hs | 47 ++++++++++++++++++-------------- Assistant/Threads/Transferrer.hs | 3 +- Assistant/Threads/WebApp.hs | 37 +++++++++++++------------ Assistant/TransferQueue.hs | 2 +- 4 files changed, 47 insertions(+), 42 deletions(-) diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs index 3610c2fdad..958a816c0b 100644 --- a/Assistant/DaemonStatus.hs +++ b/Assistant/DaemonStatus.hs @@ -35,9 +35,10 @@ data DaemonStatus = DaemonStatus , currentTransfers :: TransferMap -- Ordered list of remotes to talk to. , knownRemotes :: [Remote] - -- Clients can use this to wait on changes to the DaemonStatus - -- and other related things like the TransferQueue. - , notificationBroadcaster :: NotificationBroadcaster + -- Broadcasts notifications about all changes to the DaemonStatus + , changeNotifier :: NotificationBroadcaster + -- Broadcasts notifications when queued or running transfers change. + , transferNotifier :: NotificationBroadcaster } type TransferMap = M.Map Transfer TransferInfo @@ -47,7 +48,8 @@ type DaemonStatusHandle = TMVar DaemonStatus newDaemonStatus :: IO DaemonStatus newDaemonStatus = do - nb <- newNotificationBroadcaster + cn <- newNotificationBroadcaster + tn <- newNotificationBroadcaster return $ DaemonStatus { scanComplete = False , lastRunning = Nothing @@ -55,7 +57,8 @@ newDaemonStatus = do , lastSanityCheck = Nothing , currentTransfers = M.empty , knownRemotes = [] - , notificationBroadcaster = nb + , changeNotifier = cn + , transferNotifier = tn } getDaemonStatus :: DaemonStatusHandle -> IO DaemonStatus @@ -66,19 +69,13 @@ modifyDaemonStatus_ handle a = modifyDaemonStatus handle $ \s -> (a s, ()) modifyDaemonStatus :: DaemonStatusHandle -> (DaemonStatus -> (DaemonStatus, b)) -> IO b modifyDaemonStatus handle a = do - (b, nb) <- atomically $ do - (s, b) <- a <$> takeTMVar handle + (s, b) <- atomically $ do + r@(s, _) <- a <$> takeTMVar handle putTMVar handle s - return $ (b, notificationBroadcaster s) - sendNotification nb + return r + sendNotification $ changeNotifier s return b -{- Can be used to send a notification that the daemon status, or other - - associated thing, like the TransferQueue, has changed. -} -notifyDaemonStatusChange :: DaemonStatusHandle -> IO () -notifyDaemonStatusChange handle = sendNotification - =<< notificationBroadcaster <$> atomically (readTMVar handle) - {- Updates the cached ordered list of remotes from the list in Annex - state. -} updateKnownRemotes :: DaemonStatusHandle -> Annex () @@ -108,11 +105,11 @@ startDaemonStatus = do -} daemonStatusThread :: ThreadState -> DaemonStatusHandle -> IO () daemonStatusThread st handle = do - bhandle <- newNotificationHandle - =<< notificationBroadcaster <$> getDaemonStatus handle + notifier <- newNotificationHandle + =<< changeNotifier <$> getDaemonStatus handle checkpoint runEvery (Seconds tenMinutes) $ do - waitNotification bhandle + waitNotification notifier checkpoint where checkpoint = do @@ -182,15 +179,23 @@ adjustTransfersSTM dstatus a = do {- Variant that does send notifications. -} adjustTransfers :: DaemonStatusHandle -> (TransferMap -> TransferMap) -> IO () -adjustTransfers dstatus a = modifyDaemonStatus_ dstatus $ - \s -> s { currentTransfers = a (currentTransfers s) } +adjustTransfers dstatus a = + notifyTransfer dstatus `after` modifyDaemonStatus_ dstatus go + where + go s = s { currentTransfers = a (currentTransfers s) } {- Removes a transfer from the map, and returns its info. -} removeTransfer :: DaemonStatusHandle -> Transfer -> IO (Maybe TransferInfo) -removeTransfer dstatus t = modifyDaemonStatus dstatus go +removeTransfer dstatus t = + notifyTransfer dstatus `after` modifyDaemonStatus dstatus go where go s = let (info, ts) = M.updateLookupWithKey (\_k _v -> Nothing) t (currentTransfers s) in (s { currentTransfers = ts }, info) + +{- Send a notification when a transfer is changed. -} +notifyTransfer :: DaemonStatusHandle -> IO () +notifyTransfer handle = sendNotification + =<< transferNotifier <$> atomically (readTMVar handle) diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs index f011ff0363..a801556dbd 100644 --- a/Assistant/Threads/Transferrer.hs +++ b/Assistant/Threads/Transferrer.hs @@ -38,14 +38,13 @@ transfererThread st dstatus transferqueue slots = go ifM (runThreadState st $ shouldTransfer dstatus t info) ( do debug thisThread [ "Transferring:" , show t ] - notifyDaemonStatusChange dstatus + notifyTransfer dstatus transferThread st dstatus slots t info , do debug thisThread [ "Skipping unnecessary transfer:" , show t ] -- getNextTransfer added t to the -- daemonstatus's transfer map. void $ removeTransfer dstatus t - notifyDaemonStatusChange dstatus ) go diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 500297693b..3db5f368c7 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -5,7 +5,7 @@ - Licensed under the GNU GPL version 3 or higher. -} -{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings #-} +{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Assistant.Threads.WebApp where @@ -47,9 +47,20 @@ data WebApp = WebApp , getStatic :: Static } -getNotificationBroadcaster :: WebApp -> IO NotificationBroadcaster -getNotificationBroadcaster webapp = notificationBroadcaster - <$> getDaemonStatus (daemonStatus webapp) +waitNotifier :: forall sub. (DaemonStatus -> NotificationBroadcaster) -> NotificationId -> GHandler sub WebApp () +waitNotifier selector nid = do + notifier <- getNotifier selector + liftIO $ waitNotification $ notificationHandleFromId notifier nid + +newNotifier :: forall sub. (DaemonStatus -> NotificationBroadcaster) -> GHandler sub WebApp NotificationId +newNotifier selector = do + notifier <- getNotifier selector + liftIO $ notificationHandleToId <$> newNotificationHandle notifier + +getNotifier :: forall sub. (DaemonStatus -> NotificationBroadcaster) -> GHandler sub WebApp NotificationBroadcaster +getNotifier selector = do + webapp <- getYesod + liftIO $ selector <$> getDaemonStatus (daemonStatus webapp) staticFiles "static" @@ -133,10 +144,7 @@ transfersDisplayIdent = "transfers" -} getTransfersR :: NotificationId -> Handler RepHtml getTransfersR nid = do - {- Block until there is a change from last time. -} - webapp <- getYesod - b <- liftIO $ getNotificationBroadcaster webapp - liftIO $ waitNotification $ notificationHandleFromId b nid + waitNotifier transferNotifier nid page <- widgetToPageContent $ transfersDisplay False hamletToRepHtml $ [hamlet|^{pageBody page}|] @@ -149,9 +157,7 @@ sideBarDisplay noScript = do $(widgetFile "sidebar") unless noScript $ do {- Set up automatic updates of the sidebar. -} - webapp <- lift getYesod - nid <- liftIO $ notificationHandleToId <$> - (newNotificationHandle =<< getNotificationBroadcaster webapp) + nid <- lift $ newNotifier transferNotifier autoUpdate ident (SideBarR nid) (10 :: Int) (10 :: Int) {- Called by client to get a sidebar display. @@ -164,10 +170,7 @@ sideBarDisplay noScript = do -} getSideBarR :: NotificationId -> Handler RepHtml getSideBarR nid = do - {- Block until there is a change from last time. -} - webapp <- getYesod - b <- liftIO $ getNotificationBroadcaster webapp - liftIO $ waitNotification $ notificationHandleFromId b nid + waitNotifier transferNotifier nid page <- widgetToPageContent $ sideBarDisplay True hamletToRepHtml $ [hamlet|^{pageBody page}|] @@ -180,9 +183,7 @@ dashboard noScript warnNoScript = do getHomeR :: Handler RepHtml getHomeR = defaultLayout $ do {- Set up automatic updates for the transfers display. -} - webapp <- lift getYesod - nid <- liftIO $ notificationHandleToId <$> - (newNotificationHandle =<< getNotificationBroadcaster webapp) + nid <- lift $ newNotifier transferNotifier autoUpdate transfersDisplayIdent (TransfersR nid) (10 :: Int) (10 :: Int) dashboard False True diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs index 51ed5c9c78..01c159b08a 100644 --- a/Assistant/TransferQueue.hs +++ b/Assistant/TransferQueue.hs @@ -95,7 +95,7 @@ enqueue schedule q dstatus t info void $ modqueue (queue q) new void $ modifyTVar' (queuesize q) succ void $ modifyTVar' (queuelist q) modlist - void $ notifyDaemonStatusChange dstatus + void $ notifyTransfer dstatus {- Adds a transfer to the queue. -} queueTransfer :: Schedule -> TransferQueue -> DaemonStatusHandle -> AssociatedFile -> Transfer -> Remote -> IO () From 5271d699d22f9addb35f2374a2a70da59897bb1d Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 09:35:01 -0400 Subject: [PATCH 158/331] add alerts to DaemonStatus --- Assistant/Alert.hs | 25 ++++++++++++ Assistant/DaemonStatus.hs | 80 ++++++++++++++++++++++++++++----------- 2 files changed, 82 insertions(+), 23 deletions(-) create mode 100644 Assistant/Alert.hs diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs new file mode 100644 index 0000000000..c8bfa48fd7 --- /dev/null +++ b/Assistant/Alert.hs @@ -0,0 +1,25 @@ +{- git-annex assistant alerts + - + - Copyright 2012 Joey Hess <joey@kitenet.net> + - + - Licensed under the GNU GPL version 3 or higher. + -} + +{-# LANGUAGE RankNTypes #-} + +module Assistant.Alert where + +import Yesod + +type Widget = forall sub master. GWidget sub master () + +{- Different classes of alerts are displayed differently. -} +data AlertClass = Activity | Warning | Error | Message + +{- An alert can be a simple message, or a Yesod Widget -} +data AlertMessage = StringAlert String | WidgetAlert Widget + +data Alert = Alert + { alertClass :: AlertClass + , alertMessage :: AlertMessage + } diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs index 958a816c0b..62cf2ea2ac 100644 --- a/Assistant/DaemonStatus.hs +++ b/Assistant/DaemonStatus.hs @@ -9,6 +9,7 @@ module Assistant.DaemonStatus where import Common.Annex import Assistant.ThreadedMonad +import Assistant.Alert import Utility.ThreadScheduler import Utility.TempFile import Utility.NotificationBroadcaster @@ -21,6 +22,7 @@ import Data.Time.Clock.POSIX import Data.Time import System.Locale import qualified Data.Map as M +import Control.Exception data DaemonStatus = DaemonStatus -- False when the daemon is performing its startup scan @@ -33,45 +35,52 @@ data DaemonStatus = DaemonStatus , lastSanityCheck :: Maybe POSIXTime -- Currently running file content transfers , currentTransfers :: TransferMap + -- Messages to display to the user. + , alertMap :: AlertMap + , alertMax :: AlertId -- Ordered list of remotes to talk to. , knownRemotes :: [Remote] -- Broadcasts notifications about all changes to the DaemonStatus , changeNotifier :: NotificationBroadcaster - -- Broadcasts notifications when queued or running transfers change. + -- Broadcasts notifications when queued or current transfers change. , transferNotifier :: NotificationBroadcaster + -- Broadcasts notifications when there's a change to the alerts + , alertNotifier :: NotificationBroadcaster } type TransferMap = M.Map Transfer TransferInfo +type AlertMap = M.Map AlertId Alert +type AlertId = Integer + {- This TMVar is never left empty, so accessing it will never block. -} type DaemonStatusHandle = TMVar DaemonStatus newDaemonStatus :: IO DaemonStatus -newDaemonStatus = do - cn <- newNotificationBroadcaster - tn <- newNotificationBroadcaster - return $ DaemonStatus - { scanComplete = False - , lastRunning = Nothing - , sanityCheckRunning = False - , lastSanityCheck = Nothing - , currentTransfers = M.empty - , knownRemotes = [] - , changeNotifier = cn - , transferNotifier = tn - } +newDaemonStatus = DaemonStatus + <$> pure False + <*> pure Nothing + <*> pure False + <*> pure Nothing + <*> pure M.empty + <*> pure M.empty + <*> pure 0 + <*> pure [] + <*> newNotificationBroadcaster + <*> newNotificationBroadcaster + <*> newNotificationBroadcaster getDaemonStatus :: DaemonStatusHandle -> IO DaemonStatus getDaemonStatus = atomically . readTMVar modifyDaemonStatus_ :: DaemonStatusHandle -> (DaemonStatus -> DaemonStatus) -> IO () -modifyDaemonStatus_ handle a = modifyDaemonStatus handle $ \s -> (a s, ()) +modifyDaemonStatus_ dstatus a = modifyDaemonStatus dstatus $ \s -> (a s, ()) modifyDaemonStatus :: DaemonStatusHandle -> (DaemonStatus -> (DaemonStatus, b)) -> IO b -modifyDaemonStatus handle a = do +modifyDaemonStatus dstatus a = do (s, b) <- atomically $ do - r@(s, _) <- a <$> takeTMVar handle - putTMVar handle s + r@(s, _) <- a <$> takeTMVar dstatus + putTMVar dstatus s return r sendNotification $ changeNotifier s return b @@ -104,16 +113,16 @@ startDaemonStatus = do - frequently than once every ten minutes. -} daemonStatusThread :: ThreadState -> DaemonStatusHandle -> IO () -daemonStatusThread st handle = do +daemonStatusThread st dstatus = do notifier <- newNotificationHandle - =<< changeNotifier <$> getDaemonStatus handle + =<< changeNotifier <$> getDaemonStatus dstatus checkpoint runEvery (Seconds tenMinutes) $ do waitNotification notifier checkpoint where checkpoint = do - status <- getDaemonStatus handle + status <- getDaemonStatus dstatus file <- runThreadState st $ fromRepo gitAnnexDaemonStatusFile writeDaemonStatusFile file status @@ -197,5 +206,30 @@ removeTransfer dstatus t = {- Send a notification when a transfer is changed. -} notifyTransfer :: DaemonStatusHandle -> IO () -notifyTransfer handle = sendNotification - =<< transferNotifier <$> atomically (readTMVar handle) +notifyTransfer dstatus = sendNotification + =<< transferNotifier <$> atomically (readTMVar dstatus) + +{- Send a notification when alerts are changed. -} +notifyAlert :: DaemonStatusHandle -> IO () +notifyAlert dstatus = sendNotification + =<< alertNotifier <$> atomically (readTMVar dstatus) + +{- Returns the alert's identifier, which can be used to remove it. -} +addAlert :: DaemonStatusHandle -> Alert -> IO AlertId +addAlert dstatus alert = notifyAlert dstatus `after` modifyDaemonStatus dstatus go + where + go s = (s { alertMax = i, alertMap = m }, i) + where + i = alertMax s + 1 + m = M.insertWith' const i alert (alertMap s) + +removeAlert :: DaemonStatusHandle -> AlertId -> IO () +removeAlert dstatus i = notifyAlert dstatus `after` modifyDaemonStatus_ dstatus go + where + go s = s { alertMap = M.delete i (alertMap s) } + +{- Displays an alert while performing an activity, then removes it. -} +alertWhile :: DaemonStatusHandle -> Alert -> IO a -> IO a +alertWhile dstatus alert a = do + let alert' = alert { alertClass = Activity } + bracket (addAlert dstatus alert') (removeAlert dstatus) (const a) From c2f3e66d8c65e46046f83221996b3a180bd49657 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 11:31:06 -0400 Subject: [PATCH 159/331] show alerts in the sidebar This has a bug -- it seems long polling can only wait on one page at a time. Need to re-unify the notifiers. --- Assistant/Alert.hs | 15 ++++++++++-- Assistant/Threads/Watcher.hs | 10 ++++---- Assistant/Threads/WebApp.hs | 44 ++++++++++++++++++++++++++++++++---- templates/sidebar.hamlet | 17 +------------- 4 files changed, 59 insertions(+), 27 deletions(-) diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs index c8bfa48fd7..f4220eea9a 100644 --- a/Assistant/Alert.hs +++ b/Assistant/Alert.hs @@ -14,12 +14,23 @@ import Yesod type Widget = forall sub master. GWidget sub master () {- Different classes of alerts are displayed differently. -} -data AlertClass = Activity | Warning | Error | Message +data AlertClass = Activity | Warning | Error | Success | Message + deriving (Eq) -{- An alert can be a simple message, or a Yesod Widget -} +{- An alert can be a simple message, or an arbitrary Yesod Widget -} data AlertMessage = StringAlert String | WidgetAlert Widget data Alert = Alert { alertClass :: AlertClass + , alertHeader :: Maybe String , alertMessage :: AlertMessage + , alertBlockDisplay :: Bool + } + +activityAlert :: Maybe String -> String -> Alert +activityAlert header message = Alert + { alertClass = Activity + , alertHeader = header + , alertMessage = StringAlert message + , alertBlockDisplay = False } diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs index ab57bf04a0..5086f95a23 100644 --- a/Assistant/Threads/Watcher.hs +++ b/Assistant/Threads/Watcher.hs @@ -19,6 +19,7 @@ import Assistant.ThreadedMonad import Assistant.DaemonStatus import Assistant.Changes import Assistant.TransferQueue +import Assistant.Alert import Logs.Transfer import Utility.DirWatcher import Utility.Types.DirWatcher @@ -60,7 +61,7 @@ watchThread st dstatus transferqueue changechan = do void $ watchDir "." ignored hooks startup debug thisThread [ "watching", "."] where - startup = statupScan st dstatus + startup = startupScan st dstatus hook a = Just $ runHandler thisThread st dstatus transferqueue changechan a hooks = WatchHooks { addHook = hook onAdd @@ -71,11 +72,12 @@ watchThread st dstatus transferqueue changechan = do } {- Initial scartup scan. The action should return once the scan is complete. -} -statupScan :: ThreadState -> DaemonStatusHandle -> IO a -> IO a -statupScan st dstatus scanner = do +startupScan :: ThreadState -> DaemonStatusHandle -> IO a -> IO a +startupScan st dstatus scanner = do runThreadState st $ showAction "scanning" - r <- scanner + let alert = activityAlert Nothing "Performing startup scan" + r <- alertWhile dstatus alert scanner modifyDaemonStatus_ dstatus $ \s -> s { scanComplete = True } -- Notice any files that were deleted before watching was started. diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 3db5f368c7..132aad22e8 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -14,6 +14,7 @@ import Assistant.Common import Assistant.ThreadedMonad import Assistant.DaemonStatus import Assistant.TransferQueue +import Assistant.Alert hiding (Widget) import Utility.NotificationBroadcaster import Utility.WebApp import Utility.Yesod @@ -33,7 +34,7 @@ import Network.Socket (PortNumber) import Text.Blaze.Renderer.String import Data.Text (Text, pack, unpack) import qualified Data.Map as M -import Data.Time.Clock +import Data.Function thisThread :: String thisThread = "WebApp" @@ -151,14 +152,47 @@ getTransfersR nid = do sideBarDisplay :: Bool -> Widget sideBarDisplay noScript = do - date <- liftIO $ show <$> getCurrentTime + let content = do + {- Any yesod message appears as the first alert. -} + maybe noop rendermessage =<< lift getMessage + + {- Add newest 10 alerts to the sidebar. -} + webapp <- lift getYesod + alerts <- M.toList . alertMap + <$> liftIO (getDaemonStatus $ daemonStatus webapp) + mapM_ renderalert $ + take 10 $ reverse $ sortBy (compare `on` fst) alerts ident <- lift newIdent - mmsg <- lift getMessage $(widgetFile "sidebar") + unless noScript $ do - {- Set up automatic updates of the sidebar. -} - nid <- lift $ newNotifier transferNotifier + {- Set up automatic updates of the sidebar + - when alerts come in. -} + nid <- lift $ newNotifier alertNotifier autoUpdate ident (SideBarR nid) (10 :: Int) (10 :: Int) + where + bootstrapclass Activity = "alert-info" + bootstrapclass Warning = "alert" + bootstrapclass Error = "alert-error" + bootstrapclass Success = "alert-success" + bootstrapclass Message = "alert-info" + + renderalert (alertid, alert) = addalert + (show alertid) + -- Activity alerts auto-close + (not noScript && alertClass alert /= Activity) + (alertBlockDisplay alert) + (bootstrapclass $ alertClass alert) + (alertHeader alert) + $ case alertMessage alert of + StringAlert s -> [whamlet|#{s}|] + WidgetAlert w -> w + + rendermessage msg = addalert "yesodmessage" True False + "alert-info" Nothing [whamlet|#{msg}|] + + addalert :: String -> Bool -> Bool -> Text -> Maybe String -> Widget -> Widget + addalert alertid closable block divclass heading widget = $(widgetFile "alert") {- Called by client to get a sidebar display. - diff --git a/templates/sidebar.hamlet b/templates/sidebar.hamlet index 3b5048151b..32900b920c 100644 --- a/templates/sidebar.hamlet +++ b/templates/sidebar.hamlet @@ -1,18 +1,3 @@ <div .span3 ##{ident}> <div .sidebar-nav> - $maybe msg <- mmsg - <div .alert .alert-info> - <a .close data-dismiss="alert" href="#">×</a> - #{msg} - <div .alert .alert-info> - <a .close data-dismiss="alert" href="#">×</a> - <b>This is just a demo.</b> If this were not just a demo, - I'd not be filling this sidebar with silly alerts. - <div .alert .alert-success> - <a .close data-dismiss="alert" href="#">×</a> - <b>Well done!</b> - You successfully read this important alert message. - <div .alert .alert-error> - <a .close data-dismiss="alert" href="#">×</a> - <b>Whoops!</b> - Unable to connect to blah blah.. #{date} + ^{content} From ea05ba893c1e7f56e24115a2641cd517bb3560a5 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 12:12:14 -0400 Subject: [PATCH 160/331] fix the auto token leak on auth error page issue permanantly --- Utility/WebApp.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/Utility/WebApp.hs b/Utility/WebApp.hs index 75e8dde9ec..971422e369 100644 --- a/Utility/WebApp.hs +++ b/Utility/WebApp.hs @@ -137,7 +137,11 @@ genRandomToken = do Right (s, _) -> showDigest $ sha512 $ L.fromChunks [s] {- A Yesod isAuthorized method, which checks the auth cgi parameter - - against a token extracted from the Yesod application. -} + - against a token extracted from the Yesod application. + - + - Note that the usual Yesod error page is bypassed on error, to avoid + - possibly leaking the auth token in urls on that page! + -} checkAuthToken :: forall t sub. (t -> T.Text) -> GHandler sub t AuthResult checkAuthToken extractToken = do webapp <- getYesod @@ -145,7 +149,7 @@ checkAuthToken extractToken = do let params = reqGetParams req if lookup "auth" params == Just (extractToken webapp) then return Authorized - else return AuthenticationRequired + else sendResponseStatus unauthorized401 () {- A Yesod joinPath method, which adds an auth cgi parameter to every - url matching a predicate, containing a token extracted from the From e1d4bfe6716f409f0ab400f532e48db2dfc98cf1 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 12:37:45 -0400 Subject: [PATCH 161/331] typo; was waiting on the wrong notifier for the sidebar! --- Assistant/Threads/WebApp.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 132aad22e8..3d42db8125 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -204,7 +204,7 @@ sideBarDisplay noScript = do -} getSideBarR :: NotificationId -> Handler RepHtml getSideBarR nid = do - waitNotifier transferNotifier nid + waitNotifier alertNotifier nid page <- widgetToPageContent $ sideBarDisplay True hamletToRepHtml $ [hamlet|^{pageBody page}|] From 2dc5697a0ac36fdfe21da79a721db3f086bce041 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 12:39:10 -0400 Subject: [PATCH 162/331] add --- templates/alert.hamlet | 9 +++++++++ 1 file changed, 9 insertions(+) create mode 100644 templates/alert.hamlet diff --git a/templates/alert.hamlet b/templates/alert.hamlet new file mode 100644 index 0000000000..2d0daf8418 --- /dev/null +++ b/templates/alert.hamlet @@ -0,0 +1,9 @@ +<div .alert .fade .in .#{divclass} :block:.alert-block ##{alertid}> + $if closable + <a .close data-dismiss="alert" href="#">×</a> + $maybe h <- heading + $if block + <h4 class="alert-heading">#{h}</h4> + $else + <strong>#{h}</strong> + ^{widget} From 09e77a0cf0ca6e6c76ead584f16818dcf04a94b6 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 13:22:08 -0400 Subject: [PATCH 163/331] add some alerts --- Assistant/Threads/MountWatcher.hs | 25 +++++++++++++++++++------ Assistant/Threads/TransferScanner.hs | 12 +++++++++++- Assistant/Threads/Watcher.hs | 7 ++++--- 3 files changed, 34 insertions(+), 10 deletions(-) diff --git a/Assistant/Threads/MountWatcher.hs b/Assistant/Threads/MountWatcher.hs index 853d96d51c..7d0ef5ae40 100644 --- a/Assistant/Threads/MountWatcher.hs +++ b/Assistant/Threads/MountWatcher.hs @@ -15,6 +15,7 @@ import Assistant.ThreadedMonad import Assistant.DaemonStatus import Assistant.ScanRemotes import Assistant.Threads.Pusher (pushToRemotes) +import Assistant.Alert import qualified Annex import qualified Git import Utility.ThreadScheduler @@ -158,17 +159,29 @@ handleMounts st dstatus scanremotes wasmounted nowmounted = mapM_ (handleMount s handleMount :: ThreadState -> DaemonStatusHandle -> ScanRemoteMap -> Mntent -> IO () handleMount st dstatus scanremotes mntent = do - debug thisThread ["detected mount of", mnt_dir mntent] + debug thisThread ["detected mount of", dir] rs <- remotesUnder st dstatus mntent unless (null rs) $ do branch <- runThreadState st $ Command.Sync.currentBranch let nonspecial = filter (Git.repoIsLocal . Remote.repo) rs - unless (null nonspecial) $ do - debug thisThread ["pulling from", show nonspecial] - runThreadState st $ manualPull branch nonspecial - now <- getCurrentTime - pushToRemotes thisThread now st Nothing nonspecial + unless (null nonspecial) $ + alertWhile dstatus (syncalert nonspecial) $ do + debug thisThread ["syncing with", show nonspecial] + runThreadState st $ manualPull branch nonspecial + now <- getCurrentTime + pushToRemotes thisThread now st Nothing nonspecial addScanRemotes scanremotes rs + where + dir = mnt_dir mntent + syncalert rs = Alert + { alertClass = Activity + , alertHeader = Just $ "Syncing with " ++ unwords (map Remote.name rs) + , alertMessage = StringAlert $ unwords + ["I noticed you plugged in", dir, + " -- let's get it in sync!"] + , alertBlockDisplay = True + } + {- Finds remotes located underneath the mount point. - diff --git a/Assistant/Threads/TransferScanner.hs b/Assistant/Threads/TransferScanner.hs index e6a078907b..1bf8b062fc 100644 --- a/Assistant/Threads/TransferScanner.hs +++ b/Assistant/Threads/TransferScanner.hs @@ -12,6 +12,7 @@ import Assistant.ScanRemotes import Assistant.TransferQueue import Assistant.ThreadedMonad import Assistant.DaemonStatus +import Assistant.Alert import Logs.Transfer import Logs.Location import qualified Remote @@ -31,9 +32,18 @@ transferScannerThread st dstatus scanremotes transferqueue = do runEvery (Seconds 2) $ do r <- getScanRemote scanremotes liftIO $ debug thisThread ["starting scan of", show r] - scan st dstatus transferqueue r + alertWhile dstatus (scanalert r) $ + scan st dstatus transferqueue r liftIO $ debug thisThread ["finished scan of", show r] where + scanalert r = Alert + { alertClass = Activity + , alertHeader = Just $ "Scanning " ++ Remote.name r + , alertMessage = StringAlert $ unwords + [ "Ensuring that ", Remote.name r + , "is fully in sync." ] + , alertBlockDisplay = True + } {- This is a naive scan through the git work tree. - diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs index 5086f95a23..ade26be19b 100644 --- a/Assistant/Threads/Watcher.hs +++ b/Assistant/Threads/Watcher.hs @@ -74,9 +74,7 @@ watchThread st dstatus transferqueue changechan = do {- Initial scartup scan. The action should return once the scan is complete. -} startupScan :: ThreadState -> DaemonStatusHandle -> IO a -> IO a startupScan st dstatus scanner = do - runThreadState st $ - showAction "scanning" - let alert = activityAlert Nothing "Performing startup scan" + runThreadState st $ showAction "scanning" r <- alertWhile dstatus alert scanner modifyDaemonStatus_ dstatus $ \s -> s { scanComplete = True } @@ -86,6 +84,9 @@ startupScan st dstatus scanner = do showAction "started" return r + + where + alert = activityAlert Nothing "Performing startup scan" ignored :: FilePath -> Bool ignored = ig . takeFileName From ebd8362d58036a75f8aaf4ad0b69ba57d3c77a0e Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 13:37:26 -0400 Subject: [PATCH 164/331] fix bug in transfer initiation checking Putting the transfer on the currentTransfers atomically introduced a bug: It checks to see if the transfer is in progress, and cancels it. Fixed by moving that check inside the STM transaction. --- Assistant/Threads/Transferrer.hs | 43 ++++++++++++++++---------------- Assistant/TransferQueue.hs | 26 +++++++++++-------- 2 files changed, 37 insertions(+), 32 deletions(-) diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs index a801556dbd..956e0fc9d1 100644 --- a/Assistant/Threads/Transferrer.hs +++ b/Assistant/Threads/Transferrer.hs @@ -33,9 +33,10 @@ maxTransfers = 1 transfererThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> TransferSlots -> IO () transfererThread st dstatus transferqueue slots = go where - go = do - (t, info) <- getNextTransfer transferqueue dstatus - ifM (runThreadState st $ shouldTransfer dstatus t info) + go = getNextTransfer transferqueue dstatus notrunning >>= handle + handle Nothing = go + handle (Just (t, info)) = do + ifM (runThreadState st $ shouldTransfer t info) ( do debug thisThread [ "Transferring:" , show t ] notifyTransfer dstatus @@ -47,28 +48,26 @@ transfererThread st dstatus transferqueue slots = go void $ removeTransfer dstatus t ) go + {- Skip transfers that are already running. -} + notrunning i = startedTime i == Nothing -{- Checks if the requested transfer is already running, or - - the file to download is already present, or the remote +{- Checks if the file to download is already present, or the remote - being uploaded to isn't known to have the file. -} -shouldTransfer :: DaemonStatusHandle -> Transfer -> TransferInfo -> Annex Bool -shouldTransfer dstatus t info = - go =<< currentTransfers <$> liftIO (getDaemonStatus dstatus) +shouldTransfer :: Transfer -> TransferInfo -> Annex Bool +shouldTransfer t info + | transferDirection t == Download = + not <$> inAnnex key + | transferDirection t == Upload = + {- Trust the location log to check if the + - remote already has the key. This avoids + - a roundtrip to the remote. -} + case transferRemote info of + Nothing -> return False + Just remote -> + notElem (Remote.uuid remote) + <$> loggedLocations key + | otherwise = return False where - go m - | M.member t m = return False - | transferDirection t == Download = - not <$> inAnnex key - | transferDirection t == Upload = - {- Trust the location log to check if the - - remote already has the key. This avoids - - a roundtrip to the remote. -} - case transferRemote info of - Nothing -> return False - Just remote -> - notElem (Remote.uuid remote) - <$> loggedLocations key - | otherwise = return False key = transferKey t {- A transfer is run in a separate thread, with a *copy* of the Annex diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs index 01c159b08a..40adc35206 100644 --- a/Assistant/TransferQueue.hs +++ b/Assistant/TransferQueue.hs @@ -113,16 +113,22 @@ queueTransferAt wantsz schedule q dstatus f t remote = do else retry -- blocks until queuesize changes enqueue schedule q dstatus t (stubInfo f remote) -{- Blocks until a pending transfer is available from the queue. - - The transfer is removed from the transfer queue, and added to - - the daemon status currentTransfers map. This is done in a single STM - - transaction, so there is no window where an observer sees an - - inconsistent status. -} -getNextTransfer :: TransferQueue -> DaemonStatusHandle -> IO (Transfer, TransferInfo) -getNextTransfer q dstatus = atomically $ do +{- Blocks until a pending transfer is available from the queue, + - and removes it. + - + - Checks that it's acceptable, before adding it to the + - the currentTransfers map. If it's not acceptable, it's discarded. + - + - This is done in a single STM transaction, so there is no window + - where an observer sees an inconsistent status. -} +getNextTransfer :: TransferQueue -> DaemonStatusHandle -> (TransferInfo -> Bool) -> IO (Maybe (Transfer, TransferInfo)) +getNextTransfer q dstatus acceptable = atomically $ do void $ modifyTVar' (queuesize q) pred void $ modifyTVar' (queuelist q) (drop 1) r@(t, info) <- readTChan (queue q) - adjustTransfersSTM dstatus $ - M.insertWith' const t info - return r + if acceptable info + then do + adjustTransfersSTM dstatus $ + M.insertWith' const t info + return $ Just r + else return Nothing From c4023f785834bc237e5fcdb69e275bbae10dd40b Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 13:55:07 -0400 Subject: [PATCH 165/331] probably fixes http://git-annex.branchable.com/bugs/lsof__47__committer_thread_loops_occassionally/ --- Assistant/Threads/Committer.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/Assistant/Threads/Committer.hs b/Assistant/Threads/Committer.hs index 33b92c7e53..b3258f7299 100644 --- a/Assistant/Threads/Committer.hs +++ b/Assistant/Threads/Committer.hs @@ -58,6 +58,7 @@ commitThread st changechan commitchan transferqueue dstatus = runEvery (Seconds else refill readychanges else refill changes where + refill [] = noop refill cs = do debug thisThread [ "delaying commit of" From ce7889ba86fc15e2892db8190114e291128e9c62 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 14:10:17 -0400 Subject: [PATCH 166/331] debuggery --- Assistant/Threads/Committer.hs | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/Assistant/Threads/Committer.hs b/Assistant/Threads/Committer.hs index b3258f7299..f236159f98 100644 --- a/Assistant/Threads/Committer.hs +++ b/Assistant/Threads/Committer.hs @@ -190,6 +190,13 @@ safeToAdd st changes = runThreadState st $ tmpdir <- fromRepo gitAnnexTmpDir openfiles <- S.fromList . map fst3 . filter openwrite <$> liftIO (Lsof.queryDir tmpdir) + + liftIO $ debug thisThread + [ "checking changes:" + , show changes + , "vs open files:" + , show openfiles + ] let checked = map (check openfiles) changes From b2dc8fdb06068276869df682b439348aa96e57f5 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 17:53:18 -0400 Subject: [PATCH 167/331] add more alerts Nearly all long-running actions now display an alert. --- Assistant.hs | 2 +- Assistant/Threads/Pusher.hs | 23 ++++++++---- Assistant/Threads/SanityChecker.hs | 57 +++++++++++++++++++----------- 3 files changed, 53 insertions(+), 29 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index 1f41a9398f..22a87fe8cc 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -146,7 +146,7 @@ startDaemon assistant foreground webappwaiter mapM_ forkIO [ commitThread st changechan commitchan transferqueue dstatus , pushThread st dstatus commitchan pushmap - , pushRetryThread st pushmap + , pushRetryThread st dstatus pushmap , mergeThread st , transferWatcherThread st dstatus , transfererThread st dstatus transferqueue transferslots diff --git a/Assistant/Threads/Pusher.hs b/Assistant/Threads/Pusher.hs index 3762c48368..27e95a7344 100644 --- a/Assistant/Threads/Pusher.hs +++ b/Assistant/Threads/Pusher.hs @@ -10,12 +10,14 @@ module Assistant.Threads.Pusher where import Assistant.Common import Assistant.Commits import Assistant.Pushes -import Assistant.DaemonStatus +import Assistant.Alert import Assistant.ThreadedMonad import Assistant.Threads.Merger +import Assistant.DaemonStatus import qualified Command.Sync import Utility.ThreadScheduler import Utility.Parallel +import qualified Remote import Data.Time.Clock import qualified Data.Map as M @@ -24,8 +26,8 @@ thisThread :: ThreadName thisThread = "Pusher" {- This thread retries pushes that failed before. -} -pushRetryThread :: ThreadState -> FailedPushMap -> IO () -pushRetryThread st pushmap = runEvery (Seconds halfhour) $ do +pushRetryThread :: ThreadState -> DaemonStatusHandle -> FailedPushMap -> IO () +pushRetryThread st dstatus pushmap = runEvery (Seconds halfhour) $ do -- We already waited half an hour, now wait until there are failed -- pushes to retry. topush <- getFailedPushesBefore pushmap (fromIntegral halfhour) @@ -36,13 +38,16 @@ pushRetryThread st pushmap = runEvery (Seconds halfhour) $ do , "failed pushes" ] now <- getCurrentTime - pushToRemotes thisThread now st (Just pushmap) topush + alertWhile dstatus (alert topush) $ + pushToRemotes thisThread now st (Just pushmap) topush where halfhour = 1800 + alert rs = activityAlert (Just "Retrying sync") $ + "with " ++ unwords (map Remote.name rs) ++ ", which failed earlier." {- This thread pushes git commits out to remotes soon after they are made. -} pushThread :: ThreadState -> DaemonStatusHandle -> CommitChan -> FailedPushMap -> IO () -pushThread st daemonstatus commitchan pushmap = do +pushThread st dstatus commitchan pushmap = do runEvery (Seconds 2) $ do -- We already waited two seconds as a simple rate limiter. -- Next, wait until at least one commit has been made @@ -51,8 +56,9 @@ pushThread st daemonstatus commitchan pushmap = do now <- getCurrentTime if shouldPush now commits then do - remotes <- knownRemotes <$> getDaemonStatus daemonstatus - pushToRemotes thisThread now st (Just pushmap) remotes + remotes <- knownRemotes <$> getDaemonStatus dstatus + alertWhile dstatus (syncalert remotes) $ + pushToRemotes thisThread now st (Just pushmap) remotes else do debug thisThread [ "delaying push of" @@ -60,6 +66,9 @@ pushThread st daemonstatus commitchan pushmap = do , "commits" ] refillCommits commitchan commits + where + syncalert rs = activityAlert Nothing $ + "Syncing with " ++ unwords (map Remote.name rs) {- Decide if now is a good time to push to remotes. - diff --git a/Assistant/Threads/SanityChecker.hs b/Assistant/Threads/SanityChecker.hs index 5e27246a02..69610c2a7b 100644 --- a/Assistant/Threads/SanityChecker.hs +++ b/Assistant/Threads/SanityChecker.hs @@ -13,6 +13,7 @@ import Assistant.Common import Assistant.DaemonStatus import Assistant.ThreadedMonad import Assistant.Changes +import Assistant.Alert import Assistant.TransferQueue import qualified Git.LsFiles import Utility.ThreadScheduler @@ -25,29 +26,34 @@ thisThread = "SanityChecker" {- This thread wakes up occasionally to make sure the tree is in good shape. -} sanityCheckerThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> ChangeChan -> IO () -sanityCheckerThread st status transferqueue changechan = forever $ do - waitForNextCheck status +sanityCheckerThread st dstatus transferqueue changechan = forever $ do + waitForNextCheck dstatus debug thisThread ["starting sanity check"] - modifyDaemonStatus_ status $ \s -> s - { sanityCheckRunning = True } - - now <- getPOSIXTime -- before check started - catchIO (check st status transferqueue changechan) - (runThreadState st . warning . show) - - modifyDaemonStatus_ status $ \s -> s - { sanityCheckRunning = False - , lastSanityCheck = Just now - } + alertWhile dstatus alert go debug thisThread ["sanity check complete"] + where + go = do + modifyDaemonStatus_ dstatus $ \s -> s + { sanityCheckRunning = True } + + now <- getPOSIXTime -- before check started + catchIO (check st dstatus transferqueue changechan) + (runThreadState st . warning . show) + + modifyDaemonStatus_ dstatus $ \s -> s + { sanityCheckRunning = False + , lastSanityCheck = Just now + } + alert = activityAlert (Just "Running daily sanity check") + "to make sure I've not missed anything." {- Only run one check per day, from the time of the last check. -} waitForNextCheck :: DaemonStatusHandle -> IO () -waitForNextCheck status = do - v <- lastSanityCheck <$> getDaemonStatus status +waitForNextCheck dstatus = do + v <- lastSanityCheck <$> getDaemonStatus dstatus now <- getPOSIXTime threadDelaySeconds $ Seconds $ calcdelay now v where @@ -64,10 +70,8 @@ oneDay = 24 * 60 * 60 - running potentially expensive parts of this check, since remaining in it - will block the watcher. -} check :: ThreadState -> DaemonStatusHandle -> TransferQueue -> ChangeChan -> IO () -check st status transferqueue changechan = do - g <- runThreadState st $ do - showSideAction "Running daily check" - fromRepo id +check st dstatus transferqueue changechan = do + g <- runThreadState st $ fromRepo id -- Find old unstaged symlinks, and add them to git. unstaged <- Git.LsFiles.notInRepo False ["."] g now <- getPOSIXTime @@ -81,9 +85,20 @@ check st status transferqueue changechan = do where toonew timestamp now = now < (realToFrac (timestamp + slop) :: POSIXTime) slop = fromIntegral tenMinutes - insanity m = runThreadState st $ warning m + insanity msg = do + runThreadState st $ warning msg + void $ addAlert dstatus $ Alert + { alertClass = Warning + , alertHeader = Just "Fixed a problem" + , alertMessage = StringAlert $ unwords + [ "The daily sanity check found and fixed a problem:" + , msg + , "If these problems persist, consider filing a bug report." + ] + , alertBlockDisplay = True + } addsymlink file s = do insanity $ "found unstaged symlink: " ++ file - Watcher.runHandler thisThread st status + Watcher.runHandler thisThread st dstatus transferqueue changechan Watcher.onAddSymlink file s From d52c93242450c0bd01e7d3c1fdae375806aa6e1f Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 18:07:45 -0400 Subject: [PATCH 168/331] moved all alert messages into one file Makes it easier to edit for consistent voice etc. --- Assistant/Alert.hs | 52 ++++++++++++++++++++++++++++ Assistant/Threads/MountWatcher.hs | 11 +----- Assistant/Threads/Pusher.hs | 10 ++---- Assistant/Threads/SanityChecker.hs | 17 ++------- Assistant/Threads/TransferScanner.hs | 11 +----- Assistant/Threads/Watcher.hs | 5 +-- 6 files changed, 60 insertions(+), 46 deletions(-) diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs index f4220eea9a..6b0804fd88 100644 --- a/Assistant/Alert.hs +++ b/Assistant/Alert.hs @@ -9,6 +9,9 @@ module Assistant.Alert where +import Common.Annex +import qualified Remote + import Yesod type Widget = forall sub master. GWidget sub master () @@ -34,3 +37,52 @@ activityAlert header message = Alert , alertMessage = StringAlert message , alertBlockDisplay = False } + +startupScanAlert :: Alert +startupScanAlert = activityAlert Nothing "Performing startup scan" + +pushAlert :: [Remote] -> Alert +pushAlert rs = activityAlert Nothing $ + "Syncing with " ++ unwords (map Remote.name rs) + +pushRetryAlert :: [Remote] -> Alert +pushRetryAlert rs = activityAlert (Just "Retrying sync") $ + "with " ++ unwords (map Remote.name rs) ++ ", which failed earlier." + +syncMountAlert :: FilePath -> [Remote] -> Alert +syncMountAlert dir rs = Alert + { alertClass = Activity + , alertHeader = Just $ "Syncing with " ++ unwords (map Remote.name rs) + , alertMessage = StringAlert $ unwords + ["I noticed you plugged in" + , dir + , " -- let's get it in sync!" + ] + , alertBlockDisplay = True + } + +scanAlert :: Remote -> Alert +scanAlert r = Alert + { alertClass = Activity + , alertHeader = Just $ "Scanning " ++ Remote.name r + , alertMessage = StringAlert $ unwords + [ "Ensuring that ", Remote.name r + , "is fully in sync." ] + , alertBlockDisplay = True + } + +sanityCheckAlert :: Alert +sanityCheckAlert = activityAlert (Just "Running daily sanity check") + "to make sure I've not missed anything." + +sanityCheckFixAlert :: String -> Alert +sanityCheckFixAlert msg = Alert + { alertClass = Warning + , alertHeader = Just "Fixed a problem" + , alertMessage = StringAlert $ unwords + [ "The daily sanity check found and fixed a problem:" + , msg + , "If these problems persist, consider filing a bug report." + ] + , alertBlockDisplay = True + } diff --git a/Assistant/Threads/MountWatcher.hs b/Assistant/Threads/MountWatcher.hs index 7d0ef5ae40..20862dac12 100644 --- a/Assistant/Threads/MountWatcher.hs +++ b/Assistant/Threads/MountWatcher.hs @@ -165,7 +165,7 @@ handleMount st dstatus scanremotes mntent = do branch <- runThreadState st $ Command.Sync.currentBranch let nonspecial = filter (Git.repoIsLocal . Remote.repo) rs unless (null nonspecial) $ - alertWhile dstatus (syncalert nonspecial) $ do + alertWhile dstatus (syncMountAlert dir nonspecial) $ do debug thisThread ["syncing with", show nonspecial] runThreadState st $ manualPull branch nonspecial now <- getCurrentTime @@ -173,15 +173,6 @@ handleMount st dstatus scanremotes mntent = do addScanRemotes scanremotes rs where dir = mnt_dir mntent - syncalert rs = Alert - { alertClass = Activity - , alertHeader = Just $ "Syncing with " ++ unwords (map Remote.name rs) - , alertMessage = StringAlert $ unwords - ["I noticed you plugged in", dir, - " -- let's get it in sync!"] - , alertBlockDisplay = True - } - {- Finds remotes located underneath the mount point. - diff --git a/Assistant/Threads/Pusher.hs b/Assistant/Threads/Pusher.hs index 27e95a7344..1b0420b9b3 100644 --- a/Assistant/Threads/Pusher.hs +++ b/Assistant/Threads/Pusher.hs @@ -17,7 +17,6 @@ import Assistant.DaemonStatus import qualified Command.Sync import Utility.ThreadScheduler import Utility.Parallel -import qualified Remote import Data.Time.Clock import qualified Data.Map as M @@ -38,12 +37,10 @@ pushRetryThread st dstatus pushmap = runEvery (Seconds halfhour) $ do , "failed pushes" ] now <- getCurrentTime - alertWhile dstatus (alert topush) $ + alertWhile dstatus (pushRetryAlert topush) $ pushToRemotes thisThread now st (Just pushmap) topush where halfhour = 1800 - alert rs = activityAlert (Just "Retrying sync") $ - "with " ++ unwords (map Remote.name rs) ++ ", which failed earlier." {- This thread pushes git commits out to remotes soon after they are made. -} pushThread :: ThreadState -> DaemonStatusHandle -> CommitChan -> FailedPushMap -> IO () @@ -57,7 +54,7 @@ pushThread st dstatus commitchan pushmap = do if shouldPush now commits then do remotes <- knownRemotes <$> getDaemonStatus dstatus - alertWhile dstatus (syncalert remotes) $ + alertWhile dstatus (pushAlert remotes) $ pushToRemotes thisThread now st (Just pushmap) remotes else do debug thisThread @@ -66,9 +63,6 @@ pushThread st dstatus commitchan pushmap = do , "commits" ] refillCommits commitchan commits - where - syncalert rs = activityAlert Nothing $ - "Syncing with " ++ unwords (map Remote.name rs) {- Decide if now is a good time to push to remotes. - diff --git a/Assistant/Threads/SanityChecker.hs b/Assistant/Threads/SanityChecker.hs index 69610c2a7b..cd5dc06446 100644 --- a/Assistant/Threads/SanityChecker.hs +++ b/Assistant/Threads/SanityChecker.hs @@ -31,7 +31,7 @@ sanityCheckerThread st dstatus transferqueue changechan = forever $ do debug thisThread ["starting sanity check"] - alertWhile dstatus alert go + alertWhile dstatus sanityCheckAlert go debug thisThread ["sanity check complete"] where @@ -47,8 +47,6 @@ sanityCheckerThread st dstatus transferqueue changechan = forever $ do { sanityCheckRunning = False , lastSanityCheck = Just now } - alert = activityAlert (Just "Running daily sanity check") - "to make sure I've not missed anything." {- Only run one check per day, from the time of the last check. -} waitForNextCheck :: DaemonStatusHandle -> IO () @@ -87,18 +85,9 @@ check st dstatus transferqueue changechan = do slop = fromIntegral tenMinutes insanity msg = do runThreadState st $ warning msg - void $ addAlert dstatus $ Alert - { alertClass = Warning - , alertHeader = Just "Fixed a problem" - , alertMessage = StringAlert $ unwords - [ "The daily sanity check found and fixed a problem:" - , msg - , "If these problems persist, consider filing a bug report." - ] - , alertBlockDisplay = True - } + void $ addAlert dstatus $ sanityCheckFixAlert msg addsymlink file s = do - insanity $ "found unstaged symlink: " ++ file Watcher.runHandler thisThread st dstatus transferqueue changechan Watcher.onAddSymlink file s + insanity $ "found unstaged symlink: " ++ file diff --git a/Assistant/Threads/TransferScanner.hs b/Assistant/Threads/TransferScanner.hs index 1bf8b062fc..1d91a65d48 100644 --- a/Assistant/Threads/TransferScanner.hs +++ b/Assistant/Threads/TransferScanner.hs @@ -32,18 +32,9 @@ transferScannerThread st dstatus scanremotes transferqueue = do runEvery (Seconds 2) $ do r <- getScanRemote scanremotes liftIO $ debug thisThread ["starting scan of", show r] - alertWhile dstatus (scanalert r) $ + alertWhile dstatus (scanAlert r) $ scan st dstatus transferqueue r liftIO $ debug thisThread ["finished scan of", show r] - where - scanalert r = Alert - { alertClass = Activity - , alertHeader = Just $ "Scanning " ++ Remote.name r - , alertMessage = StringAlert $ unwords - [ "Ensuring that ", Remote.name r - , "is fully in sync." ] - , alertBlockDisplay = True - } {- This is a naive scan through the git work tree. - diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs index ade26be19b..1c8d122d52 100644 --- a/Assistant/Threads/Watcher.hs +++ b/Assistant/Threads/Watcher.hs @@ -75,7 +75,7 @@ watchThread st dstatus transferqueue changechan = do startupScan :: ThreadState -> DaemonStatusHandle -> IO a -> IO a startupScan st dstatus scanner = do runThreadState st $ showAction "scanning" - r <- alertWhile dstatus alert scanner + r <- alertWhile dstatus startupScanAlert scanner modifyDaemonStatus_ dstatus $ \s -> s { scanComplete = True } -- Notice any files that were deleted before watching was started. @@ -84,9 +84,6 @@ startupScan st dstatus scanner = do showAction "started" return r - - where - alert = activityAlert Nothing "Performing startup scan" ignored :: FilePath -> Bool ignored = ig . takeFileName From d62b157194248402b566e96bbc92d19b8e1ce6e8 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 19:05:51 -0400 Subject: [PATCH 169/331] better ordering of alerts --- Assistant/Alert.hs | 41 ++++++++++++++++++++++++++++++++++-- Assistant/DaemonStatus.hs | 1 - Assistant/Threads/Watcher.hs | 17 +++++++++------ Assistant/Threads/WebApp.hs | 8 +++---- Utility/Misc.hs | 7 ++++++ templates/transfers.hamlet | 1 - 6 files changed, 60 insertions(+), 15 deletions(-) diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs index 6b0804fd88..648ea58546 100644 --- a/Assistant/Alert.hs +++ b/Assistant/Alert.hs @@ -17,8 +17,8 @@ import Yesod type Widget = forall sub master. GWidget sub master () {- Different classes of alerts are displayed differently. -} -data AlertClass = Activity | Warning | Error | Success | Message - deriving (Eq) +data AlertClass = Success | Message | Activity | Warning | Error + deriving (Eq, Ord) {- An alert can be a simple message, or an arbitrary Yesod Widget -} data AlertMessage = StringAlert String | WidgetAlert Widget @@ -28,19 +28,53 @@ data Alert = Alert , alertHeader :: Maybe String , alertMessage :: AlertMessage , alertBlockDisplay :: Bool + , alertPriority :: AlertPriority } +{- Higher AlertId indicates a more recent alert. -} +type AlertId = Integer + +type AlertPair = (AlertId, Alert) + +data AlertPriority = Low | Medium | High + deriving (Eq, Ord) + +{- The desired order is the reverse of: + - + - - High priority alerts, newest first + - - Medium priority Activity, newest first (mostly used for Activity) + - - Low priority alwerts, newest first + - - Ties are broken by the AlertClass, with Errors etc coming first. + -} +compareAlertPairs :: AlertPair -> AlertPair -> Ordering +compareAlertPairs + (aid, Alert {alertClass = aclass, alertPriority = aprio}) + (bid, Alert {alertClass = bclass, alertPriority = bprio}) + = compare aprio bprio + `thenOrd` compare aid bid + `thenOrd` compare aclass bclass + +sortAlertPairs :: [AlertPair] -> [AlertPair] +sortAlertPairs = reverse . sortBy compareAlertPairs + activityAlert :: Maybe String -> String -> Alert activityAlert header message = Alert { alertClass = Activity , alertHeader = header , alertMessage = StringAlert message , alertBlockDisplay = False + , alertPriority = Medium } startupScanAlert :: Alert startupScanAlert = activityAlert Nothing "Performing startup scan" +runningAlert :: Alert +runningAlert = (activityAlert Nothing "Running") + { alertClass = Success + , alertPriority = High -- pin above the other activity alerts + } + pushAlert :: [Remote] -> Alert pushAlert rs = activityAlert Nothing $ "Syncing with " ++ unwords (map Remote.name rs) @@ -59,6 +93,7 @@ syncMountAlert dir rs = Alert , " -- let's get it in sync!" ] , alertBlockDisplay = True + , alertPriority = Low } scanAlert :: Remote -> Alert @@ -69,6 +104,7 @@ scanAlert r = Alert [ "Ensuring that ", Remote.name r , "is fully in sync." ] , alertBlockDisplay = True + , alertPriority = Low } sanityCheckAlert :: Alert @@ -85,4 +121,5 @@ sanityCheckFixAlert msg = Alert , "If these problems persist, consider filing a bug report." ] , alertBlockDisplay = True + , alertPriority = High } diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs index 62cf2ea2ac..f1b3bdb9fe 100644 --- a/Assistant/DaemonStatus.hs +++ b/Assistant/DaemonStatus.hs @@ -51,7 +51,6 @@ data DaemonStatus = DaemonStatus type TransferMap = M.Map Transfer TransferInfo type AlertMap = M.Map AlertId Alert -type AlertId = Integer {- This TMVar is never left empty, so accessing it will never block. -} type DaemonStatusHandle = TMVar DaemonStatus diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs index 1c8d122d52..ddbd51655f 100644 --- a/Assistant/Threads/Watcher.hs +++ b/Assistant/Threads/Watcher.hs @@ -75,13 +75,18 @@ watchThread st dstatus transferqueue changechan = do startupScan :: ThreadState -> DaemonStatusHandle -> IO a -> IO a startupScan st dstatus scanner = do runThreadState st $ showAction "scanning" - r <- alertWhile dstatus startupScanAlert scanner - modifyDaemonStatus_ dstatus $ \s -> s { scanComplete = True } + r <- alertWhile dstatus startupScanAlert $ do + r <- scanner + modifyDaemonStatus_ dstatus $ \s -> s { scanComplete = True } - -- Notice any files that were deleted before watching was started. - runThreadState st $ do - inRepo $ Git.Command.run "add" [Param "--update"] - showAction "started" + -- Notice any files that were deleted before + -- watching was started. + runThreadState st $ do + inRepo $ Git.Command.run "add" [Param "--update"] + showAction "started" + return r + + void $ addAlert dstatus runningAlert return r diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 3d42db8125..4d37a941ad 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -34,7 +34,6 @@ import Network.Socket (PortNumber) import Text.Blaze.Renderer.String import Data.Text (Text, pack, unpack) import qualified Data.Map as M -import Data.Function thisThread :: String thisThread = "WebApp" @@ -158,10 +157,9 @@ sideBarDisplay noScript = do {- Add newest 10 alerts to the sidebar. -} webapp <- lift getYesod - alerts <- M.toList . alertMap + alertpairs <- M.toList . alertMap <$> liftIO (getDaemonStatus $ daemonStatus webapp) - mapM_ renderalert $ - take 10 $ reverse $ sortBy (compare `on` fst) alerts + mapM_ renderalert $ take 10 $ sortAlertPairs alertpairs ident <- lift newIdent $(widgetFile "sidebar") @@ -180,7 +178,7 @@ sideBarDisplay noScript = do renderalert (alertid, alert) = addalert (show alertid) -- Activity alerts auto-close - (not noScript && alertClass alert /= Activity) + (alertClass alert /= Activity) (alertBlockDisplay alert) (bootstrapclass $ alertClass alert) (alertHeader alert) diff --git a/Utility/Misc.hs b/Utility/Misc.hs index e11586467d..77ebb4f3d9 100644 --- a/Utility/Misc.hs +++ b/Utility/Misc.hs @@ -45,3 +45,10 @@ segment p l = map reverse $ go [] [] l go c r (i:is) | p i = go [] (c:r) is | otherwise = go (i:c) r is + +{- Given two orderings, returns the second if the first is EQ and returns + - the first otherwise. -} +thenOrd :: Ordering -> Ordering -> Ordering +thenOrd EQ x = x +thenOrd x _ = x +{-# INLINE thenOrd #-} diff --git a/templates/transfers.hamlet b/templates/transfers.hamlet index bc69d7f876..e79885fb54 100644 --- a/templates/transfers.hamlet +++ b/templates/transfers.hamlet @@ -1,6 +1,5 @@ <div .span9 ##{ident}> $if null transfers - <h2>No current transfers $else <h2>Transfers $forall (transfer, info) <- transfers From 0186f06744e6c379d41c482f42374853bd3c5539 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 19:41:17 -0400 Subject: [PATCH 170/331] tweak Alert closability and construction --- Assistant/Alert.hs | 35 ++++++++++++++++++++++------------- Assistant/Threads/WebApp.hs | 3 +-- 2 files changed, 23 insertions(+), 15 deletions(-) diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs index 648ea58546..78771b1ea7 100644 --- a/Assistant/Alert.hs +++ b/Assistant/Alert.hs @@ -28,6 +28,7 @@ data Alert = Alert , alertHeader :: Maybe String , alertMessage :: AlertMessage , alertBlockDisplay :: Bool + , alertClosable :: Bool , alertPriority :: AlertPriority } @@ -36,11 +37,12 @@ type AlertId = Integer type AlertPair = (AlertId, Alert) -data AlertPriority = Low | Medium | High +data AlertPriority = Low | Medium | High | Pinned deriving (Eq, Ord) {- The desired order is the reverse of: - + - - Pinned alerts - - High priority alerts, newest first - - Medium priority Activity, newest first (mostly used for Activity) - - Low priority alwerts, newest first @@ -57,22 +59,30 @@ compareAlertPairs sortAlertPairs :: [AlertPair] -> [AlertPair] sortAlertPairs = reverse . sortBy compareAlertPairs -activityAlert :: Maybe String -> String -> Alert -activityAlert header message = Alert +baseActivityAlert :: Alert +baseActivityAlert = Alert { alertClass = Activity - , alertHeader = header - , alertMessage = StringAlert message + , alertHeader = Nothing + , alertMessage = StringAlert "" , alertBlockDisplay = False + , alertClosable = False , alertPriority = Medium } +activityAlert :: Maybe String -> String -> Alert +activityAlert header message = baseActivityAlert + { alertHeader = header + , alertMessage = StringAlert message + } + startupScanAlert :: Alert startupScanAlert = activityAlert Nothing "Performing startup scan" runningAlert :: Alert -runningAlert = (activityAlert Nothing "Running") +runningAlert = baseActivityAlert { alertClass = Success - , alertPriority = High -- pin above the other activity alerts + , alertMessage = StringAlert "Running" + , alertPriority = Pinned } pushAlert :: [Remote] -> Alert @@ -84,9 +94,8 @@ pushRetryAlert rs = activityAlert (Just "Retrying sync") $ "with " ++ unwords (map Remote.name rs) ++ ", which failed earlier." syncMountAlert :: FilePath -> [Remote] -> Alert -syncMountAlert dir rs = Alert - { alertClass = Activity - , alertHeader = Just $ "Syncing with " ++ unwords (map Remote.name rs) +syncMountAlert dir rs = baseActivityAlert + { alertHeader = Just $ "Syncing with " ++ unwords (map Remote.name rs) , alertMessage = StringAlert $ unwords ["I noticed you plugged in" , dir @@ -97,9 +106,8 @@ syncMountAlert dir rs = Alert } scanAlert :: Remote -> Alert -scanAlert r = Alert - { alertClass = Activity - , alertHeader = Just $ "Scanning " ++ Remote.name r +scanAlert r = baseActivityAlert + { alertHeader = Just $ "Scanning " ++ Remote.name r , alertMessage = StringAlert $ unwords [ "Ensuring that ", Remote.name r , "is fully in sync." ] @@ -122,4 +130,5 @@ sanityCheckFixAlert msg = Alert ] , alertBlockDisplay = True , alertPriority = High + , alertClosable = True } diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 4d37a941ad..84b9bcd204 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -177,8 +177,7 @@ sideBarDisplay noScript = do renderalert (alertid, alert) = addalert (show alertid) - -- Activity alerts auto-close - (alertClass alert /= Activity) + (alertClosable alert) (alertBlockDisplay alert) (bootstrapclass $ alertClass alert) (alertHeader alert) From 326617ad2f6c1708bc2826ba75cb8f9c3064d6dc Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 21:54:23 -0400 Subject: [PATCH 171/331] add intro --- Assistant/Threads/WebApp.hs | 66 +++++++++++++++++++++++++++++++++---- Remote.hs | 10 ++++++ templates/bootstrap.hamlet | 2 +- templates/intro.hamlet | 23 +++++++++++++ templates/page.hamlet | 6 ++-- 5 files changed, 97 insertions(+), 10 deletions(-) create mode 100644 templates/intro.hamlet diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 84b9bcd204..daddbc28cb 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -26,6 +26,7 @@ import Utility.Percentage import Utility.DataUnits import Types.Key import qualified Remote +import Logs.Web (webUUID) import Yesod import Yesod.Static @@ -34,6 +35,7 @@ import Network.Socket (PortNumber) import Text.Blaze.Renderer.String import Data.Text (Text, pack, unpack) import qualified Data.Map as M +import Control.Concurrent.STM thisThread :: String thisThread = "WebApp" @@ -43,10 +45,29 @@ data WebApp = WebApp , daemonStatus :: DaemonStatusHandle , transferQueue :: TransferQueue , secretToken :: Text - , baseTitle :: String + , relDir :: FilePath , getStatic :: Static + , webAppState :: TMVar WebAppState } +data WebAppState = WebAppState + { showIntro :: Bool + } + +newWebAppState :: IO (TMVar WebAppState) +newWebAppState = liftIO $ atomically $ + newTMVar $ WebAppState { showIntro = True } + +getWebAppState :: forall sub. GHandler sub WebApp WebAppState +getWebAppState = liftIO . atomically . readTMVar =<< webAppState <$> getYesod + +modifyWebAppState :: forall sub. (WebAppState -> WebAppState) -> GHandler sub WebApp () +modifyWebAppState a = go =<< webAppState <$> getYesod + where + go s = liftIO $ atomically $ do + v <- takeTMVar s + putTMVar s $ a v + waitNotifier :: forall sub. (DaemonStatus -> NotificationBroadcaster) -> NotificationId -> GHandler sub WebApp () waitNotifier selector nid = do notifier <- getNotifier selector @@ -71,6 +92,7 @@ mkYesod "WebApp" [parseRoutes| /transfers/#NotificationId TransfersR GET /sidebar/#NotificationId SideBarR GET /config ConfigR GET +/addrepository AddRepositoryR GET /static StaticR Static getStatic |] @@ -119,7 +141,9 @@ autoUpdate ident gethtml ms_delay ms_startdelay = do let startdelay = show ms_startdelay $(widgetFile "longpolling") -{- A display of currently running and queued transfers. -} +{- A display of currently running and queued transfers. + - + - Or, if there have never been any this run, an intro display. -} transfersDisplay :: Bool -> Widget transfersDisplay warnNoScript = do webapp <- lift getYesod @@ -127,13 +151,35 @@ transfersDisplay warnNoScript = do M.toList . currentTransfers <$> liftIO (getDaemonStatus $ daemonStatus webapp) queued <- liftIO $ getTransferQueue $ transferQueue webapp - let transfers = current ++ queued let ident = transfersDisplayIdent - $(widgetFile "transfers") + let transfers = current ++ queued + if null transfers + then ifM (lift $ showIntro <$> getWebAppState) + ( introDisplay ident + , noop + ) + else do + lift $ modifyWebAppState $ \s -> s { showIntro = False } + $(widgetFile "transfers") transfersDisplayIdent :: Text transfersDisplayIdent = "transfers" +introDisplay :: Text -> Widget +introDisplay ident = do + webapp <- lift getYesod + let reldir = relDir webapp + remotelist <- liftIO $ runThreadState (threadState webapp) $ + Remote.prettyListUUIDs + =<< filter (/= webUUID) . nub . map Remote.uuid + <$> Remote.remoteList + let n = (length remotelist) + 1 -- plus this one + let numrepos = show n + let notenough = n < 2 + let barelyenough = n == 2 + let morethanenough = n > 2 + $(widgetFile "intro") + {- Called by client to get a display of currently in process transfers. - - Returns a div, which will be inserted into the calling page. @@ -237,7 +283,13 @@ getNoScriptR = defaultLayout $ getConfigR :: Handler RepHtml getConfigR = defaultLayout $ do sideBarDisplay False - setTitle "configuration" + setTitle "Configuration" + [whamlet|<a href="@{HomeR}">main|] + +getAddRepositoryR :: Handler RepHtml +getAddRepositoryR = defaultLayout $ do + sideBarDisplay False + setTitle "Add repository" [whamlet|<a href="@{HomeR}">main|] webAppThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> Maybe (IO ()) -> IO () @@ -259,13 +311,15 @@ webAppThread st dstatus transferqueue onstartup = do then relPathDirToFile home dir else dir token <- genRandomToken + s <- newWebAppState return $ WebApp { threadState = st , daemonStatus = dstatus , transferQueue = transferqueue , secretToken = pack token - , baseTitle = reldir + , relDir = reldir , getStatic = $(embed "static") + , webAppState = s } {- Creates a html shim file that's used to redirect into the webapp, diff --git a/Remote.hs b/Remote.hs index e211ef7cb6..bb582778fd 100644 --- a/Remote.hs +++ b/Remote.hs @@ -24,6 +24,7 @@ module Remote ( uuidDescriptions, byName, prettyPrintUUIDs, + prettyListUUIDs, remotesWithUUID, remotesWithoutUUID, keyLocations, @@ -128,6 +129,15 @@ prettyPrintUUIDs desc uuids = do , ("here", toJSON $ hereu == u) ] +{- List of remote names and/or descriptions, for human display. + - Omits the current repisitory. -} +prettyListUUIDs :: [UUID] -> Annex [String] +prettyListUUIDs uuids = do + hereu <- getUUID + m <- uuidDescriptions + return $ map (\u -> M.findWithDefault "" u m) $ + filter (/= hereu) uuids + {- Filters a list of remotes to ones that have the listed uuids. -} remotesWithUUID :: [Remote] -> [UUID] -> [Remote] remotesWithUUID rs us = filter (\r -> uuid r `elem` us) rs diff --git a/templates/bootstrap.hamlet b/templates/bootstrap.hamlet index 389895df74..13aefd486a 100644 --- a/templates/bootstrap.hamlet +++ b/templates/bootstrap.hamlet @@ -1,7 +1,7 @@ $doctype 5 <html> <head> - <title>#{baseTitle webapp} #{pageTitle page} + <title>#{relDir webapp} #{pageTitle page} <link rel="icon" href=@{StaticR favicon_ico} type="image/x-icon"> <meta name="viewport" content="width=device-width,initial-scale=1.0"> ^{pageHead page} diff --git a/templates/intro.hamlet b/templates/intro.hamlet new file mode 100644 index 0000000000..ef82df79b8 --- /dev/null +++ b/templates/intro.hamlet @@ -0,0 +1,23 @@ +<div .span9 ##{ident} .hero-unit> + <h2> + git-annex is watching over your files in <small><tt>#{reldir}</tt></small> + <p> + It will automatically notice changes, and keep files in sync between # + $if notenough + repositories on your devices ... + <h2> + But no other repositories are set up yet. + <a .btn .btn-primary .btn-large href="@{AddRepositoryR}">Add another repository</a> + $else + these # + $if barelyenough + <span .badge .badge-warning>#{numrepos}</span> + $else + <span .badge .badge-success>#{numrepos}</span> + \ repositories and devices: + <ul> + $forall name <- remotelist + <li>#{name} + <a .btn .btn-primary .btn-large href="@{AddRepositoryR}">Add another repository</a> + <div> + Or just sit back, watch the magic, and get on with using your files. diff --git a/templates/page.hamlet b/templates/page.hamlet index c397d248c2..5004241257 100644 --- a/templates/page.hamlet +++ b/templates/page.hamlet @@ -11,12 +11,12 @@ <ul .nav .pull-right> <li .dropdown #menu1> <a .dropdown-toggle data-toggle="dropdown" href="#menu1"> - Current Repository: #{baseTitle webapp} + Current Repository: #{relDir webapp} <b .caret></b> <ul .dropdown-menu> - <li><a href="#">#{baseTitle webapp}</a></li> + <li><a href="#">#{relDir webapp}</a></li> <li .divider></li> - <li><a href="#">Add new repository</a></li> + <li><a href="@{AddRepositoryR}">Add new repository</a></li> <div .container-fluid> <div .row-fluid> From 675ad9fe226e99ca9ee2defa7ba6b0489123f0dc Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 21:58:01 -0400 Subject: [PATCH 172/331] tweak --- templates/intro.hamlet | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/templates/intro.hamlet b/templates/intro.hamlet index ef82df79b8..d62bfda9ab 100644 --- a/templates/intro.hamlet +++ b/templates/intro.hamlet @@ -9,13 +9,13 @@ But no other repositories are set up yet. <a .btn .btn-primary .btn-large href="@{AddRepositoryR}">Add another repository</a> $else - these # $if barelyenough <span .badge .badge-warning>#{numrepos}</span> $else <span .badge .badge-success>#{numrepos}</span> \ repositories and devices: <ul> + <li>here $forall name <- remotelist <li>#{name} <a .btn .btn-primary .btn-large href="@{AddRepositoryR}">Add another repository</a> From 895b068e350977cec1e31d49bd87b13b0a5676d9 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 22:11:01 -0400 Subject: [PATCH 173/331] tweak intro --- Assistant/Threads/WebApp.hs | 11 ++++++----- Remote.hs | 13 +++++++++---- templates/intro.hamlet | 3 +-- 3 files changed, 16 insertions(+), 11 deletions(-) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index daddbc28cb..40f8300e53 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -27,6 +27,7 @@ import Utility.DataUnits import Types.Key import qualified Remote import Logs.Web (webUUID) +import Annex.UUID (getUUID) import Yesod import Yesod.Static @@ -169,11 +170,11 @@ introDisplay :: Text -> Widget introDisplay ident = do webapp <- lift getYesod let reldir = relDir webapp - remotelist <- liftIO $ runThreadState (threadState webapp) $ - Remote.prettyListUUIDs - =<< filter (/= webUUID) . nub . map Remote.uuid - <$> Remote.remoteList - let n = (length remotelist) + 1 -- plus this one + remotelist <- liftIO $ runThreadState (threadState webapp) $ do + u <- getUUID + rs <- map Remote.uuid <$> Remote.remoteList + Remote.prettyListUUIDs $ filter (/= webUUID) $ nub $ u:rs + let n = length remotelist let numrepos = show n let notenough = n < 2 let barelyenough = n == 2 diff --git a/Remote.hs b/Remote.hs index bb582778fd..ac9da05365 100644 --- a/Remote.hs +++ b/Remote.hs @@ -129,14 +129,19 @@ prettyPrintUUIDs desc uuids = do , ("here", toJSON $ hereu == u) ] -{- List of remote names and/or descriptions, for human display. - - Omits the current repisitory. -} +{- List of remote names and/or descriptions, for human display. -} prettyListUUIDs :: [UUID] -> Annex [String] prettyListUUIDs uuids = do hereu <- getUUID m <- uuidDescriptions - return $ map (\u -> M.findWithDefault "" u m) $ - filter (/= hereu) uuids + return $ map (\u -> prettify m hereu u) uuids + where + finddescription m u = M.findWithDefault "" u m + prettify m hereu u + | u == hereu = addName n "here" + | otherwise = n + where + n = finddescription m u {- Filters a list of remotes to ones that have the listed uuids. -} remotesWithUUID :: [Remote] -> [UUID] -> [Remote] diff --git a/templates/intro.hamlet b/templates/intro.hamlet index d62bfda9ab..6660b6a039 100644 --- a/templates/intro.hamlet +++ b/templates/intro.hamlet @@ -15,9 +15,8 @@ <span .badge .badge-success>#{numrepos}</span> \ repositories and devices: <ul> - <li>here $forall name <- remotelist <li>#{name} <a .btn .btn-primary .btn-large href="@{AddRepositoryR}">Add another repository</a> - <div> + <p> Or just sit back, watch the magic, and get on with using your files. From 74cf65a4dd5f7a59844184a4ece3279adc97d3a7 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Sun, 29 Jul 2012 22:18:58 -0400 Subject: [PATCH 174/331] avoid first person --- Assistant/Alert.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs index 78771b1ea7..49ad515ade 100644 --- a/Assistant/Alert.hs +++ b/Assistant/Alert.hs @@ -97,7 +97,7 @@ syncMountAlert :: FilePath -> [Remote] -> Alert syncMountAlert dir rs = baseActivityAlert { alertHeader = Just $ "Syncing with " ++ unwords (map Remote.name rs) , alertMessage = StringAlert $ unwords - ["I noticed you plugged in" + ["You plugged in" , dir , " -- let's get it in sync!" ] @@ -117,7 +117,7 @@ scanAlert r = baseActivityAlert sanityCheckAlert :: Alert sanityCheckAlert = activityAlert (Just "Running daily sanity check") - "to make sure I've not missed anything." + "to make sure everything is ok." sanityCheckFixAlert :: String -> Alert sanityCheckFixAlert msg = Alert From ec0493fa4d45a8d8f6617c906727d653afb1c50e Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 00:31:33 -0400 Subject: [PATCH 175/331] filter out dead repos from the intro --- Assistant/Threads/WebApp.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 40f8300e53..7ad40c3079 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -27,6 +27,7 @@ import Utility.DataUnits import Types.Key import qualified Remote import Logs.Web (webUUID) +import Logs.Trust import Annex.UUID (getUUID) import Yesod @@ -173,7 +174,8 @@ introDisplay ident = do remotelist <- liftIO $ runThreadState (threadState webapp) $ do u <- getUUID rs <- map Remote.uuid <$> Remote.remoteList - Remote.prettyListUUIDs $ filter (/= webUUID) $ nub $ u:rs + rs' <- snd <$> trustPartition DeadTrusted rs + Remote.prettyListUUIDs $ filter (/= webUUID) $ nub $ u:rs' let n = length remotelist let numrepos = show n let notenough = n < 2 From 3dce75fb23fca94ad86c3f0ee816bb0ad2ecb27c Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 02:07:02 -0400 Subject: [PATCH 176/331] make old activiy alerts stay visible They're updated to show whether the activity succeeded or failed. This adds several TODOs to the code to fix later. --- Assistant/Alert.hs | 34 ++++++++++++++++++++++++---- Assistant/DaemonStatus.hs | 29 +++++++++++++++++++----- Assistant/Threads/MountWatcher.hs | 2 +- Assistant/Threads/Pusher.hs | 17 ++++++++++---- Assistant/Threads/SanityChecker.hs | 13 +++++++---- Assistant/Threads/TransferScanner.hs | 5 ++-- Assistant/Threads/Watcher.hs | 13 +++++------ Assistant/Threads/WebApp.hs | 2 +- 8 files changed, 85 insertions(+), 30 deletions(-) diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs index 49ad515ade..23a93b1c16 100644 --- a/Assistant/Alert.hs +++ b/Assistant/Alert.hs @@ -20,8 +20,8 @@ type Widget = forall sub master. GWidget sub master () data AlertClass = Success | Message | Activity | Warning | Error deriving (Eq, Ord) -{- An alert can be a simple message, or an arbitrary Yesod Widget -} -data AlertMessage = StringAlert String | WidgetAlert Widget +{- An alert can be a simple message, or an arbitrary Yesod Widget. -} +data AlertMessage = StringAlert String | WidgetAlert (Alert -> Widget) data Alert = Alert { alertClass :: AlertClass @@ -37,7 +37,7 @@ type AlertId = Integer type AlertPair = (AlertId, Alert) -data AlertPriority = Low | Medium | High | Pinned +data AlertPriority = Filler | Low | Medium | High | Pinned deriving (Eq, Ord) {- The desired order is the reverse of: @@ -45,7 +45,8 @@ data AlertPriority = Low | Medium | High | Pinned - - Pinned alerts - - High priority alerts, newest first - - Medium priority Activity, newest first (mostly used for Activity) - - - Low priority alwerts, newest first + - - Low priority alerts, newest first + - - Filler priorty alerts, newest first - - Ties are broken by the AlertClass, with Errors etc coming first. -} compareAlertPairs :: AlertPair -> AlertPair -> Ordering @@ -56,6 +57,31 @@ compareAlertPairs `thenOrd` compare aid bid `thenOrd` compare aclass bclass +makeAlertFiller :: Bool -> Alert -> Alert +makeAlertFiller success alert + | alertPriority alert == Filler = alert + | otherwise = alert + { alertClass = if c == Activity then c' else c + , alertPriority = Filler + , alertHeader = finished <$> h + , alertMessage = massage m + } + where + h = alertHeader alert + m = alertMessage alert + c = alertClass alert + c' + | success = Success + | otherwise = Error + + massage (WidgetAlert w) = WidgetAlert w -- renders old on its own + massage (StringAlert s) = StringAlert $ + maybe (finished s) (const s) h + + finished s + | success = s ++ ": Succeeded" + | otherwise = s ++ ": Failed" + sortAlertPairs :: [AlertPair] -> [AlertPair] sortAlertPairs = reverse . sortBy compareAlertPairs diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs index f1b3bdb9fe..6d05c61528 100644 --- a/Assistant/DaemonStatus.hs +++ b/Assistant/DaemonStatus.hs @@ -223,12 +223,29 @@ addAlert dstatus alert = notifyAlert dstatus `after` modifyDaemonStatus dstatus m = M.insertWith' const i alert (alertMap s) removeAlert :: DaemonStatusHandle -> AlertId -> IO () -removeAlert dstatus i = notifyAlert dstatus `after` modifyDaemonStatus_ dstatus go - where - go s = s { alertMap = M.delete i (alertMap s) } +removeAlert dstatus i = updateAlert dstatus i (const Nothing) -{- Displays an alert while performing an activity, then removes it. -} -alertWhile :: DaemonStatusHandle -> Alert -> IO a -> IO a +updateAlert :: DaemonStatusHandle -> AlertId -> (Alert -> Maybe Alert) -> IO () +updateAlert dstatus i a = updateAlertMap dstatus $ \m -> M.update a i m + +updateAlertMap :: DaemonStatusHandle -> (AlertMap -> AlertMap) -> IO () +updateAlertMap dstatus a = notifyAlert dstatus `after` modifyDaemonStatus_ dstatus go + where + go s = s { alertMap = a (alertMap s) } + +{- Displays an alert while performing an activity. + - + - The alert is left visible afterwards, as filler. + - Old filler is pruned, to prevent the map growing too large. -} +alertWhile :: DaemonStatusHandle -> Alert -> IO Bool -> IO Bool alertWhile dstatus alert a = do let alert' = alert { alertClass = Activity } - bracket (addAlert dstatus alert') (removeAlert dstatus) (const a) + i <- addAlert dstatus alert' + r <- bracket_ noop noop a + updateAlertMap dstatus $ makeold i (makeAlertFiller r) + return r + where + -- TODO prune old filler + makeold i filler m + | M.size m < 20 = M.adjust filler i m + | otherwise = M.adjust filler i m diff --git a/Assistant/Threads/MountWatcher.hs b/Assistant/Threads/MountWatcher.hs index 20862dac12..4baef1d11a 100644 --- a/Assistant/Threads/MountWatcher.hs +++ b/Assistant/Threads/MountWatcher.hs @@ -165,7 +165,7 @@ handleMount st dstatus scanremotes mntent = do branch <- runThreadState st $ Command.Sync.currentBranch let nonspecial = filter (Git.repoIsLocal . Remote.repo) rs unless (null nonspecial) $ - alertWhile dstatus (syncMountAlert dir nonspecial) $ do + void $ alertWhile dstatus (syncMountAlert dir nonspecial) $ do debug thisThread ["syncing with", show nonspecial] runThreadState st $ manualPull branch nonspecial now <- getCurrentTime diff --git a/Assistant/Threads/Pusher.hs b/Assistant/Threads/Pusher.hs index 1b0420b9b3..0a0edf1d0e 100644 --- a/Assistant/Threads/Pusher.hs +++ b/Assistant/Threads/Pusher.hs @@ -37,7 +37,7 @@ pushRetryThread st dstatus pushmap = runEvery (Seconds halfhour) $ do , "failed pushes" ] now <- getCurrentTime - alertWhile dstatus (pushRetryAlert topush) $ + void $ alertWhile dstatus (pushRetryAlert topush) $ pushToRemotes thisThread now st (Just pushmap) topush where halfhour = 1800 @@ -54,7 +54,7 @@ pushThread st dstatus commitchan pushmap = do if shouldPush now commits then do remotes <- knownRemotes <$> getDaemonStatus dstatus - alertWhile dstatus (pushAlert remotes) $ + void $ alertWhile dstatus (pushAlert remotes) $ pushToRemotes thisThread now st (Just pushmap) remotes else do debug thisThread @@ -80,7 +80,7 @@ shouldPush _now commits - - Avoids running possibly long-duration commands in the Annex monad, so - as not to block other threads. -} -pushToRemotes :: ThreadName -> UTCTime -> ThreadState -> (Maybe FailedPushMap) -> [Remote] -> IO () +pushToRemotes :: ThreadName -> UTCTime -> ThreadState -> (Maybe FailedPushMap) -> [Remote] -> IO Bool pushToRemotes threadname now st mpushmap remotes = do (g, branch) <- runThreadState st $ (,) <$> fromRepo id <*> Command.Sync.currentBranch @@ -92,6 +92,11 @@ pushToRemotes threadname now st mpushmap remotes = do , show rs ] Command.Sync.updateBranch (Command.Sync.syncBranch branch) g + {- TODO git push exits nonzero if the remote + - is already up-to-date. This code does not tell + - the difference between the two. Could perhaps + - be check the refs when it seemed to fail? + - Note bewloe -} (succeeded, failed) <- inParallel (push g branch) rs case mpushmap of Nothing -> noop @@ -104,8 +109,10 @@ pushToRemotes threadname now st mpushmap remotes = do [ "failed to push to" , show failed ] - unless (null failed || not shouldretry) $ - retry branch g failed + if (null failed || not shouldretry) + {- TODO see above TODO item -} + then return True -- return $ null failed + else retry branch g failed makemap l = M.fromList $ zip l (repeat now) diff --git a/Assistant/Threads/SanityChecker.hs b/Assistant/Threads/SanityChecker.hs index cd5dc06446..a7c2189d80 100644 --- a/Assistant/Threads/SanityChecker.hs +++ b/Assistant/Threads/SanityChecker.hs @@ -31,7 +31,7 @@ sanityCheckerThread st dstatus transferqueue changechan = forever $ do debug thisThread ["starting sanity check"] - alertWhile dstatus sanityCheckAlert go + void $ alertWhile dstatus sanityCheckAlert go debug thisThread ["sanity check complete"] where @@ -40,14 +40,18 @@ sanityCheckerThread st dstatus transferqueue changechan = forever $ do { sanityCheckRunning = True } now <- getPOSIXTime -- before check started - catchIO (check st dstatus transferqueue changechan) - (runThreadState st . warning . show) + r <- catchIO (check st dstatus transferqueue changechan) + $ \e -> do + runThreadState st $ warning $ show e + return False modifyDaemonStatus_ dstatus $ \s -> s { sanityCheckRunning = False , lastSanityCheck = Just now } + return r + {- Only run one check per day, from the time of the last check. -} waitForNextCheck :: DaemonStatusHandle -> IO () waitForNextCheck dstatus = do @@ -67,7 +71,7 @@ oneDay = 24 * 60 * 60 {- It's important to stay out of the Annex monad as much as possible while - running potentially expensive parts of this check, since remaining in it - will block the watcher. -} -check :: ThreadState -> DaemonStatusHandle -> TransferQueue -> ChangeChan -> IO () +check :: ThreadState -> DaemonStatusHandle -> TransferQueue -> ChangeChan -> IO Bool check st dstatus transferqueue changechan = do g <- runThreadState st $ fromRepo id -- Find old unstaged symlinks, and add them to git. @@ -80,6 +84,7 @@ check st dstatus transferqueue changechan = do | isSymbolicLink s -> addsymlink file ms _ -> noop + return True where toonew timestamp now = now < (realToFrac (timestamp + slop) :: POSIXTime) slop = fromIntegral tenMinutes diff --git a/Assistant/Threads/TransferScanner.hs b/Assistant/Threads/TransferScanner.hs index 1d91a65d48..2cba0b2a78 100644 --- a/Assistant/Threads/TransferScanner.hs +++ b/Assistant/Threads/TransferScanner.hs @@ -32,18 +32,19 @@ transferScannerThread st dstatus scanremotes transferqueue = do runEvery (Seconds 2) $ do r <- getScanRemote scanremotes liftIO $ debug thisThread ["starting scan of", show r] - alertWhile dstatus (scanAlert r) $ + void $ alertWhile dstatus (scanAlert r) $ scan st dstatus transferqueue r liftIO $ debug thisThread ["finished scan of", show r] {- This is a naive scan through the git work tree. - - The scan is blocked when the transfer queue gets too large. -} -scan :: ThreadState -> DaemonStatusHandle -> TransferQueue -> Remote -> IO () +scan :: ThreadState -> DaemonStatusHandle -> TransferQueue -> Remote -> IO Bool scan st dstatus transferqueue r = do g <- runThreadState st $ fromRepo id files <- LsFiles.inRepo [] g go files + return True where go [] = return () go (f:fs) = do diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs index ddbd51655f..bfeec7630c 100644 --- a/Assistant/Threads/Watcher.hs +++ b/Assistant/Threads/Watcher.hs @@ -72,24 +72,23 @@ watchThread st dstatus transferqueue changechan = do } {- Initial scartup scan. The action should return once the scan is complete. -} -startupScan :: ThreadState -> DaemonStatusHandle -> IO a -> IO a +startupScan :: ThreadState -> DaemonStatusHandle -> IO a -> IO () startupScan st dstatus scanner = do runThreadState st $ showAction "scanning" - r <- alertWhile dstatus startupScanAlert $ do - r <- scanner - modifyDaemonStatus_ dstatus $ \s -> s { scanComplete = True } + void $ alertWhile dstatus startupScanAlert $ do + void $ scanner -- Notice any files that were deleted before -- watching was started. runThreadState st $ do inRepo $ Git.Command.run "add" [Param "--update"] showAction "started" - return r + + modifyDaemonStatus_ dstatus $ \s -> s { scanComplete = True } + return True void $ addAlert dstatus runningAlert - return r - ignored :: FilePath -> Bool ignored = ig . takeFileName where diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 7ad40c3079..d268559108 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -232,7 +232,7 @@ sideBarDisplay noScript = do (alertHeader alert) $ case alertMessage alert of StringAlert s -> [whamlet|#{s}|] - WidgetAlert w -> w + WidgetAlert w -> w alert rendermessage msg = addalert "yesodmessage" True False "alert-info" Nothing [whamlet|#{msg}|] From 40c997367544d72c6ab55eb96a1c3344fcf4012c Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 11:52:44 -0400 Subject: [PATCH 177/331] fix push status, broken when inParallel was adapted for -threaded Before pushing ran in its own process, so exitSuccess was the right thing to do, but with the threaded code, that's caught as an exception. --- Assistant/Threads/Pusher.hs | 17 +++++------------ Utility/Parallel.hs | 6 +++--- 2 files changed, 8 insertions(+), 15 deletions(-) diff --git a/Assistant/Threads/Pusher.hs b/Assistant/Threads/Pusher.hs index 0a0edf1d0e..3fe85673bc 100644 --- a/Assistant/Threads/Pusher.hs +++ b/Assistant/Threads/Pusher.hs @@ -92,33 +92,26 @@ pushToRemotes threadname now st mpushmap remotes = do , show rs ] Command.Sync.updateBranch (Command.Sync.syncBranch branch) g - {- TODO git push exits nonzero if the remote - - is already up-to-date. This code does not tell - - the difference between the two. Could perhaps - - be check the refs when it seemed to fail? - - Note bewloe -} (succeeded, failed) <- inParallel (push g branch) rs + let ok = null failed case mpushmap of Nothing -> noop Just pushmap -> changeFailedPushMap pushmap $ \m -> M.union (makemap failed) $ M.difference m (makemap succeeded) - unless (null failed) $ + unless (ok) $ debug threadname [ "failed to push to" , show failed ] - if (null failed || not shouldretry) - {- TODO see above TODO item -} - then return True -- return $ null failed + if (ok || not shouldretry) + then return ok else retry branch g failed makemap l = M.fromList $ zip l (repeat now) - push g branch remote = - ifM (Command.Sync.pushBranch remote branch g) - ( exitSuccess, exitFailure) + push g branch remote = Command.Sync.pushBranch remote branch g retry branch g rs = do debug threadname [ "trying manual pull to resolve failed pushes" ] diff --git a/Utility/Parallel.hs b/Utility/Parallel.hs index fcab2a90a1..373a0ece54 100644 --- a/Utility/Parallel.hs +++ b/Utility/Parallel.hs @@ -18,7 +18,7 @@ import Control.Exception - - Returns the values partitioned into ones with which the action succeeded, - and ones with which it failed. -} -inParallel :: (v -> IO ()) -> [v] -> IO ([v], [v]) +inParallel :: (v -> IO Bool) -> [v] -> IO ([v], [v]) inParallel a l = do mvars <- mapM thread l statuses <- mapM takeMVar mvars @@ -28,8 +28,8 @@ inParallel a l = do thread v = do mvar <- newEmptyMVar _ <- forkIO $ do - r <- try (a v) :: IO (Either SomeException ()) + r <- try (a v) :: IO (Either SomeException Bool) case r of Left _ -> putMVar mvar False - Right _ -> putMVar mvar True + Right b -> putMVar mvar b return mvar From 8d2667715b0508c538cf652e2dcfe2b8a47d1aff Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 12:21:53 -0400 Subject: [PATCH 178/331] prune old filler alerts --- Assistant/Alert.hs | 45 ++++++++++++++++++++++++++++++++----- Assistant/DaemonStatus.hs | 9 +------- Assistant/Threads/WebApp.hs | 5 +++-- 3 files changed, 43 insertions(+), 16 deletions(-) diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs index 23a93b1c16..817a1be272 100644 --- a/Assistant/Alert.hs +++ b/Assistant/Alert.hs @@ -12,6 +12,7 @@ module Assistant.Alert where import Common.Annex import qualified Remote +import qualified Data.Map as M import Yesod type Widget = forall sub master. GWidget sub master () @@ -20,6 +21,9 @@ type Widget = forall sub master. GWidget sub master () data AlertClass = Success | Message | Activity | Warning | Error deriving (Eq, Ord) +data AlertPriority = Filler | Low | Medium | High | Pinned + deriving (Eq, Ord) + {- An alert can be a simple message, or an arbitrary Yesod Widget. -} data AlertMessage = StringAlert String | WidgetAlert (Alert -> Widget) @@ -37,8 +41,19 @@ type AlertId = Integer type AlertPair = (AlertId, Alert) -data AlertPriority = Filler | Low | Medium | High | Pinned - deriving (Eq, Ord) +type AlertMap = M.Map AlertId Alert + +{- This is as many alerts as it makes sense to display at a time. + - A display might be smaller ,or larger, the point is to not overwhelm the + - user with a ton of alerts. -} +displayAlerts :: Int +displayAlerts = 10 + +{- This is not a hard maximum, but there's no point in keeping a great + - many filler alerts in an AlertMap, so when there's more than this many, + - they start being pruned, down toward displayAlerts. -} +maxAlerts :: Int +maxAlerts = displayAlerts * 2 {- The desired order is the reverse of: - @@ -57,9 +72,12 @@ compareAlertPairs `thenOrd` compare aid bid `thenOrd` compare aclass bclass +sortAlertPairs :: [AlertPair] -> [AlertPair] +sortAlertPairs = sortBy compareAlertPairs + makeAlertFiller :: Bool -> Alert -> Alert makeAlertFiller success alert - | alertPriority alert == Filler = alert + | isFiller alert = alert | otherwise = alert { alertClass = if c == Activity then c' else c , alertPriority = Filler @@ -79,11 +97,26 @@ makeAlertFiller success alert maybe (finished s) (const s) h finished s - | success = s ++ ": Succeeded" + | success = s ++ ": Ok" | otherwise = s ++ ": Failed" -sortAlertPairs :: [AlertPair] -> [AlertPair] -sortAlertPairs = reverse . sortBy compareAlertPairs +isFiller :: Alert -> Bool +isFiller alert = alertPriority alert == Filler + +{- Converts a given alert into filler, manipulating it in the AlertMap. + - + - Old filler alerts are pruned once maxAlerts is reached. + -} +convertToFiller :: AlertId -> Bool -> AlertMap -> AlertMap +convertToFiller i success m + | bloat > 0 = M.fromList $ prune $ M.toList m' + | otherwise = m' + where + bloat = M.size m - maxAlerts + m' = M.adjust (\al -> makeAlertFiller success al) i m + prune l = + let (f, rest) = partition (\(_, al) -> isFiller al) l + in drop bloat f ++ rest baseActivityAlert :: Alert baseActivityAlert = Alert diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs index 6d05c61528..77387deb84 100644 --- a/Assistant/DaemonStatus.hs +++ b/Assistant/DaemonStatus.hs @@ -50,8 +50,6 @@ data DaemonStatus = DaemonStatus type TransferMap = M.Map Transfer TransferInfo -type AlertMap = M.Map AlertId Alert - {- This TMVar is never left empty, so accessing it will never block. -} type DaemonStatusHandle = TMVar DaemonStatus @@ -242,10 +240,5 @@ alertWhile dstatus alert a = do let alert' = alert { alertClass = Activity } i <- addAlert dstatus alert' r <- bracket_ noop noop a - updateAlertMap dstatus $ makeold i (makeAlertFiller r) + updateAlertMap dstatus $ convertToFiller i r return r - where - -- TODO prune old filler - makeold i filler m - | M.size m < 20 = M.adjust filler i m - | otherwise = M.adjust filler i m diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index d268559108..5349ec2a46 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -204,11 +204,12 @@ sideBarDisplay noScript = do {- Any yesod message appears as the first alert. -} maybe noop rendermessage =<< lift getMessage - {- Add newest 10 alerts to the sidebar. -} + {- Add newest alerts to the sidebar. -} webapp <- lift getYesod alertpairs <- M.toList . alertMap <$> liftIO (getDaemonStatus $ daemonStatus webapp) - mapM_ renderalert $ take 10 $ sortAlertPairs alertpairs + mapM_ renderalert $ + take displayAlerts $ reverse $ sortAlertPairs alertpairs ident <- lift newIdent $(widgetFile "sidebar") From 9c9db6feb8e732887838337e700c33e6033cd192 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 12:23:40 -0400 Subject: [PATCH 179/331] make filler closeable --- Assistant/Alert.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs index 817a1be272..18f3ffa5d4 100644 --- a/Assistant/Alert.hs +++ b/Assistant/Alert.hs @@ -83,6 +83,7 @@ makeAlertFiller success alert , alertPriority = Filler , alertHeader = finished <$> h , alertMessage = massage m + , alertClosable = True } where h = alertHeader alert From 1f671ee40c7f26d0adb16408ba1cf7fc9ceb3a7a Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 13:31:19 -0400 Subject: [PATCH 180/331] spruce up display of the repo list --- Assistant/Threads/WebApp.hs | 7 +++++-- templates/intro.hamlet | 11 ++++++++--- 2 files changed, 13 insertions(+), 5 deletions(-) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 5349ec2a46..44fb44f2b7 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -171,17 +171,20 @@ introDisplay :: Text -> Widget introDisplay ident = do webapp <- lift getYesod let reldir = relDir webapp - remotelist <- liftIO $ runThreadState (threadState webapp) $ do + l <- liftIO $ runThreadState (threadState webapp) $ do u <- getUUID rs <- map Remote.uuid <$> Remote.remoteList rs' <- snd <$> trustPartition DeadTrusted rs Remote.prettyListUUIDs $ filter (/= webUUID) $ nub $ u:rs' - let n = length remotelist + let remotelist = zip counter l + let n = length l let numrepos = show n let notenough = n < 2 let barelyenough = n == 2 let morethanenough = n > 2 $(widgetFile "intro") + where + counter = map show ([1..] :: [Int]) {- Called by client to get a display of currently in process transfers. - diff --git a/templates/intro.hamlet b/templates/intro.hamlet index 6660b6a039..ecb15f39cc 100644 --- a/templates/intro.hamlet +++ b/templates/intro.hamlet @@ -14,9 +14,14 @@ $else <span .badge .badge-success>#{numrepos}</span> \ repositories and devices: - <ul> - $forall name <- remotelist - <li>#{name} + <table .table .table-striped .table-condensed> + <tbody> + $forall (num, name) <- remotelist + <tr> + <td> + #{num} + <td> + #{name} <a .btn .btn-primary .btn-large href="@{AddRepositoryR}">Add another repository</a> <p> Or just sit back, watch the magic, and get on with using your files. From a9941308434354046fa51d3327c5e05ff080a247 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 14:08:22 -0400 Subject: [PATCH 181/331] implement server-side alert closing Rather than using bootstrap's client-side closing. Now closed alerts stay closed. --- Assistant/Alert.hs | 10 +++- Assistant/DaemonStatus.hs | 4 +- Assistant/Threads/WebApp.hs | 23 +++++++-- static/js/bootstrap-alert.js | 94 ------------------------------------ templates/alert.hamlet | 2 +- 5 files changed, 30 insertions(+), 103 deletions(-) delete mode 100644 static/js/bootstrap-alert.js diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs index 18f3ffa5d4..4a3b2cf720 100644 --- a/Assistant/Alert.hs +++ b/Assistant/Alert.hs @@ -37,7 +37,15 @@ data Alert = Alert } {- Higher AlertId indicates a more recent alert. -} -type AlertId = Integer +newtype AlertId = AlertId Integer + deriving (Read, Show, Eq, Ord) + +{- Note: This first alert id is used for yesod's message. -} +firstAlertId :: AlertId +firstAlertId = AlertId 0 + +nextAlertId :: AlertId -> AlertId +nextAlertId (AlertId i) = AlertId $ succ i type AlertPair = (AlertId, Alert) diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs index 77387deb84..3c0bfba429 100644 --- a/Assistant/DaemonStatus.hs +++ b/Assistant/DaemonStatus.hs @@ -61,7 +61,7 @@ newDaemonStatus = DaemonStatus <*> pure Nothing <*> pure M.empty <*> pure M.empty - <*> pure 0 + <*> pure firstAlertId <*> pure [] <*> newNotificationBroadcaster <*> newNotificationBroadcaster @@ -217,7 +217,7 @@ addAlert dstatus alert = notifyAlert dstatus `after` modifyDaemonStatus dstatus where go s = (s { alertMax = i, alertMap = m }, i) where - i = alertMax s + 1 + i = nextAlertId $ alertMax s m = M.insertWith' const i alert (alertMap s) removeAlert :: DaemonStatusHandle -> AlertId -> IO () diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 44fb44f2b7..0de4a50a80 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -93,6 +93,7 @@ mkYesod "WebApp" [parseRoutes| /noscriptauto NoScriptAutoR GET /transfers/#NotificationId TransfersR GET /sidebar/#NotificationId SideBarR GET +/closealert/#AlertId CloseAlert GET /config ConfigR GET /addrepository AddRepositoryR GET /static StaticR Static getStatic @@ -102,6 +103,10 @@ instance PathPiece NotificationId where toPathPiece = pack . show fromPathPiece = readish . unpack +instance PathPiece AlertId where + toPathPiece = pack . show + fromPathPiece = readish . unpack + instance Yesod WebApp where defaultLayout content = do webapp <- getYesod @@ -110,7 +115,6 @@ instance Yesod WebApp where addStylesheet $ StaticR css_bootstrap_responsive_css addScript $ StaticR jquery_full_js addScript $ StaticR js_bootstrap_dropdown_js - addScript $ StaticR js_bootstrap_alert_js $(widgetFile "page") hamletToRepHtml $(hamletFile $ hamletTemplate "bootstrap") @@ -229,7 +233,7 @@ sideBarDisplay noScript = do bootstrapclass Message = "alert-info" renderalert (alertid, alert) = addalert - (show alertid) + alertid (alertClosable alert) (alertBlockDisplay alert) (bootstrapclass $ alertClass alert) @@ -238,11 +242,14 @@ sideBarDisplay noScript = do StringAlert s -> [whamlet|#{s}|] WidgetAlert w -> w alert - rendermessage msg = addalert "yesodmessage" True False + rendermessage msg = addalert firstAlertId True False "alert-info" Nothing [whamlet|#{msg}|] - addalert :: String -> Bool -> Bool -> Text -> Maybe String -> Widget -> Widget - addalert alertid closable block divclass heading widget = $(widgetFile "alert") + addalert :: AlertId -> Bool -> Bool -> Text -> Maybe String -> Widget -> Widget + addalert i closable block divclass heading widget = do + let alertid = show i + let closealert = CloseAlert i + $(widgetFile "alert") {- Called by client to get a sidebar display. - @@ -259,6 +266,12 @@ getSideBarR nid = do page <- widgetToPageContent $ sideBarDisplay True hamletToRepHtml $ [hamlet|^{pageBody page}|] +{- Called by the client to close an alert. -} +getCloseAlert :: AlertId -> Handler () +getCloseAlert i = do + webapp <- getYesod + void $ liftIO $ removeAlert (daemonStatus webapp) i + dashboard :: Bool -> Bool -> Widget dashboard noScript warnNoScript = do sideBarDisplay noScript diff --git a/static/js/bootstrap-alert.js b/static/js/bootstrap-alert.js deleted file mode 100644 index d17f44e150..0000000000 --- a/static/js/bootstrap-alert.js +++ /dev/null @@ -1,94 +0,0 @@ -/* ========================================================== - * bootstrap-alert.js v2.0.2 - * http://twitter.github.com/bootstrap/javascript.html#alerts - * ========================================================== - * Copyright 2012 Twitter, Inc. - * - * Licensed under the Apache License, Version 2.0 (the "License"); - * you may not use this file except in compliance with the License. - * You may obtain a copy of the License at - * - * http://www.apache.org/licenses/LICENSE-2.0 - * - * Unless required by applicable law or agreed to in writing, software - * distributed under the License is distributed on an "AS IS" BASIS, - * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. - * See the License for the specific language governing permissions and - * limitations under the License. - * ========================================================== */ - - -!function( $ ){ - - "use strict" - - /* ALERT CLASS DEFINITION - * ====================== */ - - var dismiss = '[data-dismiss="alert"]' - , Alert = function ( el ) { - $(el).on('click', dismiss, this.close) - } - - Alert.prototype = { - - constructor: Alert - - , close: function ( e ) { - var $this = $(this) - , selector = $this.attr('data-target') - , $parent - - if (!selector) { - selector = $this.attr('href') - selector = selector && selector.replace(/.*(?=#[^\s]*$)/, '') //strip for ie7 - } - - $parent = $(selector) - $parent.trigger('close') - - e && e.preventDefault() - - $parent.length || ($parent = $this.hasClass('alert') ? $this : $this.parent()) - - $parent - .trigger('close') - .removeClass('in') - - function removeElement() { - $parent - .trigger('closed') - .remove() - } - - $.support.transition && $parent.hasClass('fade') ? - $parent.on($.support.transition.end, removeElement) : - removeElement() - } - - } - - - /* ALERT PLUGIN DEFINITION - * ======================= */ - - $.fn.alert = function ( option ) { - return this.each(function () { - var $this = $(this) - , data = $this.data('alert') - if (!data) $this.data('alert', (data = new Alert(this))) - if (typeof option == 'string') data[option].call($this) - }) - } - - $.fn.alert.Constructor = Alert - - - /* ALERT DATA-API - * ============== */ - - $(function () { - $('body').on('click.alert.data-api', dismiss, Alert.prototype.close) - }) - -}( window.jQuery ); \ No newline at end of file diff --git a/templates/alert.hamlet b/templates/alert.hamlet index 2d0daf8418..bf84482b10 100644 --- a/templates/alert.hamlet +++ b/templates/alert.hamlet @@ -1,4 +1,4 @@ -<div .alert .fade .in .#{divclass} :block:.alert-block ##{alertid}> +<div .alert .fade .in .#{divclass} :block:.alert-block ##{alertid} :closable:onclick="(function( $ ) { $.get('@{closealert}') })( jQuery );"> $if closable <a .close data-dismiss="alert" href="#">×</a> $maybe h <- heading From 78b3dada5b056320922cb9f453343ae4d95b0407 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 14:50:32 -0400 Subject: [PATCH 182/331] better connection close handling Depending on how the webapp was started up and whether the user clicked on any links in it, window.close() may be disallowed by browser security policy. Also if that fails, display a modal dialog that nicely blackens out the webapp. TODO: avoid Escape closing it. Bootstrap's docs are unclear about how to do that. --- Assistant/Threads/WebApp.hs | 1 + static/js/bootstrap-modal.js | 210 +++++++++++++++++++++++++++++++++++ templates/longpolling.julius | 13 +-- templates/page.hamlet | 7 ++ 4 files changed, 224 insertions(+), 7 deletions(-) create mode 100644 static/js/bootstrap-modal.js diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 0de4a50a80..e75870e0d7 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -115,6 +115,7 @@ instance Yesod WebApp where addStylesheet $ StaticR css_bootstrap_responsive_css addScript $ StaticR jquery_full_js addScript $ StaticR js_bootstrap_dropdown_js + addScript $ StaticR js_bootstrap_modal_js $(widgetFile "page") hamletToRepHtml $(hamletFile $ hamletTemplate "bootstrap") diff --git a/static/js/bootstrap-modal.js b/static/js/bootstrap-modal.js new file mode 100644 index 0000000000..e929706279 --- /dev/null +++ b/static/js/bootstrap-modal.js @@ -0,0 +1,210 @@ +/* ========================================================= + * bootstrap-modal.js v2.0.2 + * http://twitter.github.com/bootstrap/javascript.html#modals + * ========================================================= + * Copyright 2012 Twitter, Inc. + * + * Licensed under the Apache License, Version 2.0 (the "License"); + * you may not use this file except in compliance with the License. + * You may obtain a copy of the License at + * + * http://www.apache.org/licenses/LICENSE-2.0 + * + * Unless required by applicable law or agreed to in writing, software + * distributed under the License is distributed on an "AS IS" BASIS, + * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. + * See the License for the specific language governing permissions and + * limitations under the License. + * ========================================================= */ + + +!function( $ ){ + + "use strict" + + /* MODAL CLASS DEFINITION + * ====================== */ + + var Modal = function ( content, options ) { + this.options = options + this.$element = $(content) + .delegate('[data-dismiss="modal"]', 'click.dismiss.modal', $.proxy(this.hide, this)) + } + + Modal.prototype = { + + constructor: Modal + + , toggle: function () { + return this[!this.isShown ? 'show' : 'hide']() + } + + , show: function () { + var that = this + + if (this.isShown) return + + $('body').addClass('modal-open') + + this.isShown = true + this.$element.trigger('show') + + escape.call(this) + backdrop.call(this, function () { + var transition = $.support.transition && that.$element.hasClass('fade') + + !that.$element.parent().length && that.$element.appendTo(document.body) //don't move modals dom position + + that.$element + .show() + + if (transition) { + that.$element[0].offsetWidth // force reflow + } + + that.$element.addClass('in') + + transition ? + that.$element.one($.support.transition.end, function () { that.$element.trigger('shown') }) : + that.$element.trigger('shown') + + }) + } + + , hide: function ( e ) { + e && e.preventDefault() + + if (!this.isShown) return + + var that = this + this.isShown = false + + $('body').removeClass('modal-open') + + escape.call(this) + + this.$element + .trigger('hide') + .removeClass('in') + + $.support.transition && this.$element.hasClass('fade') ? + hideWithTransition.call(this) : + hideModal.call(this) + } + + } + + + /* MODAL PRIVATE METHODS + * ===================== */ + + function hideWithTransition() { + var that = this + , timeout = setTimeout(function () { + that.$element.off($.support.transition.end) + hideModal.call(that) + }, 500) + + this.$element.one($.support.transition.end, function () { + clearTimeout(timeout) + hideModal.call(that) + }) + } + + function hideModal( that ) { + this.$element + .hide() + .trigger('hidden') + + backdrop.call(this) + } + + function backdrop( callback ) { + var that = this + , animate = this.$element.hasClass('fade') ? 'fade' : '' + + if (this.isShown && this.options.backdrop) { + var doAnimate = $.support.transition && animate + + this.$backdrop = $('<div class="modal-backdrop ' + animate + '" />') + .appendTo(document.body) + + if (this.options.backdrop != 'static') { + this.$backdrop.click($.proxy(this.hide, this)) + } + + if (doAnimate) this.$backdrop[0].offsetWidth // force reflow + + this.$backdrop.addClass('in') + + doAnimate ? + this.$backdrop.one($.support.transition.end, callback) : + callback() + + } else if (!this.isShown && this.$backdrop) { + this.$backdrop.removeClass('in') + + $.support.transition && this.$element.hasClass('fade')? + this.$backdrop.one($.support.transition.end, $.proxy(removeBackdrop, this)) : + removeBackdrop.call(this) + + } else if (callback) { + callback() + } + } + + function removeBackdrop() { + this.$backdrop.remove() + this.$backdrop = null + } + + function escape() { + var that = this + if (this.isShown && this.options.keyboard) { + $(document).on('keyup.dismiss.modal', function ( e ) { + e.which == 27 && that.hide() + }) + } else if (!this.isShown) { + $(document).off('keyup.dismiss.modal') + } + } + + + /* MODAL PLUGIN DEFINITION + * ======================= */ + + $.fn.modal = function ( option ) { + return this.each(function () { + var $this = $(this) + , data = $this.data('modal') + , options = $.extend({}, $.fn.modal.defaults, $this.data(), typeof option == 'object' && option) + if (!data) $this.data('modal', (data = new Modal(this, options))) + if (typeof option == 'string') data[option]() + else if (options.show) data.show() + }) + } + + $.fn.modal.defaults = { + backdrop: true + , keyboard: true + , show: true + } + + $.fn.modal.Constructor = Modal + + + /* MODAL DATA-API + * ============== */ + + $(function () { + $('body').on('click.modal.data-api', '[data-toggle="modal"]', function ( e ) { + var $this = $(this), href + , $target = $($this.attr('data-target') || (href = $this.attr('href')) && href.replace(/.*(?=#[^\s]+$)/, '')) //strip for ie7 + , option = $target.data('modal') ? 'toggle' : $.extend({}, $target.data(), $this.data()) + + e.preventDefault() + $target.modal(option) + }) + }) + +}( window.jQuery ); \ No newline at end of file diff --git a/templates/longpolling.julius b/templates/longpolling.julius index 95425d615a..a4077c3d50 100644 --- a/templates/longpolling.julius +++ b/templates/longpolling.julius @@ -5,9 +5,9 @@ // Maximum update frequency is controlled by #{startdelay} // and #{delay}, both in milliseconds. -(function( $ ) { +$dead=0; -numerrs=0; +(function( $ ) { $.LongPoll#{ident} = (function() { return { @@ -21,12 +21,11 @@ $.LongPoll#{ident} = (function() { numerrs=0; }, 'error': function(jqxhr, msg, e) { - numerrs=numerrs+1; - if (numerrs > 3) { + if (! $dead) { + $dead=1; + // blocked by many browsers window.close(); - } - else { - setTimeout($.LongPoll#{ident}.send, #{show delay}); + $('#lostconnection').modal('show'); } }, }); diff --git a/templates/page.hamlet b/templates/page.hamlet index 5004241257..919724f870 100644 --- a/templates/page.hamlet +++ b/templates/page.hamlet @@ -21,3 +21,10 @@ <div .container-fluid> <div .row-fluid> ^{content} +<div #lostconnection .modal .fade> + <div .modal-header> + <h3> + git-annex has shut down + <div .modal-body> + <p> + You can now close this browser window. From f4484949eff4af666f3aabd7dc78a8973c444d91 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 14:53:36 -0400 Subject: [PATCH 183/331] consistent wording --- templates/page.hamlet | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/templates/page.hamlet b/templates/page.hamlet index 919724f870..ea8025d4ff 100644 --- a/templates/page.hamlet +++ b/templates/page.hamlet @@ -16,7 +16,7 @@ <ul .dropdown-menu> <li><a href="#">#{relDir webapp}</a></li> <li .divider></li> - <li><a href="@{AddRepositoryR}">Add new repository</a></li> + <li><a href="@{AddRepositoryR}">Add another repository</a></li> <div .container-fluid> <div .row-fluid> From 5469bd6e427ea09e6dea2137f40da74d16f9a0a2 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 15:33:12 -0400 Subject: [PATCH 184/331] remove old filler that is effectively the same as new filler --- Assistant/Alert.hs | 58 ++++++++++++++++++++++++++++++++++------------ 1 file changed, 43 insertions(+), 15 deletions(-) diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs index 4a3b2cf720..54192aae65 100644 --- a/Assistant/Alert.hs +++ b/Assistant/Alert.hs @@ -36,6 +36,10 @@ data Alert = Alert , alertPriority :: AlertPriority } +type AlertPair = (AlertId, Alert) + +type AlertMap = M.Map AlertId Alert + {- Higher AlertId indicates a more recent alert. -} newtype AlertId = AlertId Integer deriving (Read, Show, Eq, Ord) @@ -47,15 +51,11 @@ firstAlertId = AlertId 0 nextAlertId :: AlertId -> AlertId nextAlertId (AlertId i) = AlertId $ succ i -type AlertPair = (AlertId, Alert) - -type AlertMap = M.Map AlertId Alert - {- This is as many alerts as it makes sense to display at a time. - A display might be smaller ,or larger, the point is to not overwhelm the - user with a ton of alerts. -} displayAlerts :: Int -displayAlerts = 10 +displayAlerts = 6 {- This is not a hard maximum, but there's no point in keeping a great - many filler alerts in an AlertMap, so when there's more than this many, @@ -74,8 +74,8 @@ maxAlerts = displayAlerts * 2 -} compareAlertPairs :: AlertPair -> AlertPair -> Ordering compareAlertPairs - (aid, Alert {alertClass = aclass, alertPriority = aprio}) - (bid, Alert {alertClass = bclass, alertPriority = bprio}) + (aid, Alert { alertClass = aclass, alertPriority = aprio }) + (bid, Alert { alertClass = bclass, alertPriority = bprio }) = compare aprio bprio `thenOrd` compare aid bid `thenOrd` compare aclass bclass @@ -83,6 +83,25 @@ compareAlertPairs sortAlertPairs :: [AlertPair] -> [AlertPair] sortAlertPairs = sortBy compareAlertPairs +{- Checks if two alerts display the same. + - Yesod Widgets cannot be compared, as they run code. -} +effectivelySameAlert :: Alert -> Alert -> Bool +effectivelySameAlert x y + | uncomparable x || uncomparable y = False + | otherwise = all id + [ alertClass x == alertClass y + , alertHeader x == alertHeader y + , extract (alertMessage x) == extract (alertMessage y) + , alertBlockDisplay x == alertBlockDisplay y + , alertClosable x == alertClosable y + , alertPriority x == alertPriority y + ] + where + uncomparable (Alert { alertMessage = StringAlert _ }) = False + uncomparable _ = True + extract (StringAlert s) = s + extract _ = "" + makeAlertFiller :: Bool -> Alert -> Alert makeAlertFiller success alert | isFiller alert = alert @@ -113,19 +132,28 @@ isFiller :: Alert -> Bool isFiller alert = alertPriority alert == Filler {- Converts a given alert into filler, manipulating it in the AlertMap. + - + - Any old filler that looks the same as the reference alert is removed. - - Old filler alerts are pruned once maxAlerts is reached. -} convertToFiller :: AlertId -> Bool -> AlertMap -> AlertMap -convertToFiller i success m - | bloat > 0 = M.fromList $ prune $ M.toList m' - | otherwise = m' +convertToFiller i success m = case M.lookup i m of + Nothing -> m + Just al -> + let al' = makeAlertFiller success al + in pruneBloat $ M.filterWithKey (pruneSame al') $ + M.insertWith' const i al' m where - bloat = M.size m - maxAlerts - m' = M.adjust (\al -> makeAlertFiller success al) i m - prune l = - let (f, rest) = partition (\(_, al) -> isFiller al) l - in drop bloat f ++ rest + pruneSame ref k al = k == i || not (effectivelySameAlert ref al) + pruneBloat m' + | bloat > 0 = M.fromList $ pruneold $ M.toList m' + | otherwise = m' + where + bloat = M.size m' - maxAlerts + pruneold l = + let (f, rest) = partition (\(_, al) -> isFiller al) l + in drop bloat f ++ rest baseActivityAlert :: Alert baseActivityAlert = Alert From 703f24b83e1788955bf0a35525dc16fb2dbfb39a Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 15:39:24 -0400 Subject: [PATCH 185/331] remove href Avoids a reload of the page when closing an alert. --- templates/alert.hamlet | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/templates/alert.hamlet b/templates/alert.hamlet index bf84482b10..8fa77eac1d 100644 --- a/templates/alert.hamlet +++ b/templates/alert.hamlet @@ -1,6 +1,6 @@ <div .alert .fade .in .#{divclass} :block:.alert-block ##{alertid} :closable:onclick="(function( $ ) { $.get('@{closealert}') })( jQuery );"> $if closable - <a .close data-dismiss="alert" href="#">×</a> + <a .close data-dismiss="alert">×</a> $maybe h <- heading $if block <h4 class="alert-heading">#{h}</h4> From 2400c6faa34bc696c30253edb219a5ffad0b2a36 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 16:11:16 -0400 Subject: [PATCH 186/331] insert modal dialog html from javascript This avoids it being visible all the time in noscript --- templates/longpolling.julius | 15 +++++++++++++-- templates/page.hamlet | 8 +------- 2 files changed, 14 insertions(+), 9 deletions(-) diff --git a/templates/longpolling.julius b/templates/longpolling.julius index a4077c3d50..0d18b8435e 100644 --- a/templates/longpolling.julius +++ b/templates/longpolling.julius @@ -5,7 +5,17 @@ // Maximum update frequency is controlled by #{startdelay} // and #{delay}, both in milliseconds. -$dead=0; +$dead = 0; + +$connfailed = + '<div id="modal" class="modal fade">' + + ' <div .modal-header>' + + ' <h3>git-annex has shut down</h2>' + + ' </div>' + + ' <div class="modal-body">' + + ' You can now close this browser window.' + + ' </div>' + + '</div>' ; (function( $ ) { @@ -25,7 +35,8 @@ $.LongPoll#{ident} = (function() { $dead=1; // blocked by many browsers window.close(); - $('#lostconnection').modal('show'); + $('#modal').replaceWith($connfailed); + $('#modal').modal('show'); } }, }); diff --git a/templates/page.hamlet b/templates/page.hamlet index ea8025d4ff..67b19aaf71 100644 --- a/templates/page.hamlet +++ b/templates/page.hamlet @@ -21,10 +21,4 @@ <div .container-fluid> <div .row-fluid> ^{content} -<div #lostconnection .modal .fade> - <div .modal-header> - <h3> - git-annex has shut down - <div .modal-body> - <p> - You can now close this browser window. +<div #modal></div> From afacc413e1643a93a71e93cba3f4e1e470fc4581 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 16:14:27 -0400 Subject: [PATCH 187/331] bring back connection failure counter Otherwise, navigating between pages can, I guess, cause connection failures that take down the webapp. --- templates/longpolling.julius | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/templates/longpolling.julius b/templates/longpolling.julius index 0d18b8435e..dd5705fc95 100644 --- a/templates/longpolling.julius +++ b/templates/longpolling.julius @@ -5,7 +5,7 @@ // Maximum update frequency is controlled by #{startdelay} // and #{delay}, both in milliseconds. -$dead = 0; +$connfails = 0; $connfailed = '<div id="modal" class="modal fade">' + @@ -31,8 +31,8 @@ $.LongPoll#{ident} = (function() { numerrs=0; }, 'error': function(jqxhr, msg, e) { - if (! $dead) { - $dead=1; + $connfails = $confails + 1; + if (! $connfails > 3) { // blocked by many browsers window.close(); $('#modal').replaceWith($connfailed); From 453b185c8506e4a6a030788f42eec196386ac78e Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 16:24:55 -0400 Subject: [PATCH 188/331] bring back retry on connection fail --- templates/longpolling.julius | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) diff --git a/templates/longpolling.julius b/templates/longpolling.julius index dd5705fc95..76ff94ce35 100644 --- a/templates/longpolling.julius +++ b/templates/longpolling.julius @@ -5,9 +5,9 @@ // Maximum update frequency is controlled by #{startdelay} // and #{delay}, both in milliseconds. -$connfails = 0; +connfails=0; -$connfailed = +connfailed= '<div id="modal" class="modal fade">' + ' <div .modal-header>' + ' <h3>git-annex has shut down</h2>' + @@ -31,13 +31,16 @@ $.LongPoll#{ident} = (function() { numerrs=0; }, 'error': function(jqxhr, msg, e) { - $connfails = $confails + 1; - if (! $connfails > 3) { + connfails=connfails+1; + if (connfails > 3) { // blocked by many browsers window.close(); - $('#modal').replaceWith($connfailed); + $('#modal').replaceWith(connfailed); $('#modal').modal('show'); } + else { + setTimeout($.LongPoll#{ident}.send, #{show delay}); + } }, }); } From b2e359a15d20d2b2b13a1883b451d014ae60db7c Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 16:32:32 -0400 Subject: [PATCH 189/331] fix kqueue build --- Assistant/DaemonStatus.hs | 11 ++++++++--- Assistant/Threads/Watcher.hs | 11 +++++++---- 2 files changed, 15 insertions(+), 7 deletions(-) diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs index 3c0bfba429..13828d3eee 100644 --- a/Assistant/DaemonStatus.hs +++ b/Assistant/DaemonStatus.hs @@ -236,9 +236,14 @@ updateAlertMap dstatus a = notifyAlert dstatus `after` modifyDaemonStatus_ dstat - The alert is left visible afterwards, as filler. - Old filler is pruned, to prevent the map growing too large. -} alertWhile :: DaemonStatusHandle -> Alert -> IO Bool -> IO Bool -alertWhile dstatus alert a = do +alertWhile dstatus alert a = alertWhile' dstatus alert $ do + r <- a + return $ (r, r) + +alertWhile' :: DaemonStatusHandle -> Alert -> IO (Bool, a) -> IO a +alertWhile' dstatus alert a = do let alert' = alert { alertClass = Activity } i <- addAlert dstatus alert' - r <- bracket_ noop noop a - updateAlertMap dstatus $ convertToFiller i r + (ok, r) <- bracket_ noop noop a + updateAlertMap dstatus $ convertToFiller i ok return r diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs index bfeec7630c..51dc572636 100644 --- a/Assistant/Threads/Watcher.hs +++ b/Assistant/Threads/Watcher.hs @@ -72,11 +72,11 @@ watchThread st dstatus transferqueue changechan = do } {- Initial scartup scan. The action should return once the scan is complete. -} -startupScan :: ThreadState -> DaemonStatusHandle -> IO a -> IO () +startupScan :: ThreadState -> DaemonStatusHandle -> IO a -> IO a startupScan st dstatus scanner = do runThreadState st $ showAction "scanning" - void $ alertWhile dstatus startupScanAlert $ do - void $ scanner + r <- alertWhile' dstatus startupScanAlert $ do + r <- scanner -- Notice any files that were deleted before -- watching was started. @@ -85,10 +85,13 @@ startupScan st dstatus scanner = do showAction "started" modifyDaemonStatus_ dstatus $ \s -> s { scanComplete = True } - return True + + return (True, r) void $ addAlert dstatus runningAlert + return r + ignored :: FilePath -> Bool ignored = ig . takeFileName where From d1358cc96f2e719a90e2192a24e61c57ce9ed50c Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 16:54:38 -0400 Subject: [PATCH 190/331] fix html --- templates/longpolling.julius | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/templates/longpolling.julius b/templates/longpolling.julius index 76ff94ce35..35205bd04d 100644 --- a/templates/longpolling.julius +++ b/templates/longpolling.julius @@ -9,8 +9,8 @@ connfails=0; connfailed= '<div id="modal" class="modal fade">' + - ' <div .modal-header>' + - ' <h3>git-annex has shut down</h2>' + + ' <div class="modal-header">' + + ' <h3>git-annex has shut down</h3>' + ' </div>' + ' <div class="modal-body">' + ' You can now close this browser window.' + From 502bc5d5f84a26bfd2ca700d8f90d78a81c7b1ac Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 18:01:41 -0400 Subject: [PATCH 191/331] rewrote longpolling, trying to avoid duplication does not work though. stupid JS --- Assistant/Threads/WebApp.hs | 1 + static/longpolling.js | 41 ++++++++++++++++++++++++ templates/longpolling.julius | 61 ++++++------------------------------ 3 files changed, 51 insertions(+), 52 deletions(-) create mode 100644 static/longpolling.js diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index e75870e0d7..7b96665d32 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -146,6 +146,7 @@ autoUpdate :: Text -> Route WebApp -> Int -> Int -> Widget autoUpdate ident gethtml ms_delay ms_startdelay = do let delay = show ms_delay let startdelay = show ms_startdelay + addScript $ StaticR longpolling_js $(widgetFile "longpolling") {- A display of currently running and queued transfers. diff --git a/static/longpolling.js b/static/longpolling.js new file mode 100644 index 0000000000..4e5f102f00 --- /dev/null +++ b/static/longpolling.js @@ -0,0 +1,41 @@ +// Uses long-polling to update a div with a specified id, +// by polling an url, which should return a new div, with the same id. + +connfails=0; + +connfailed= + '<div id="modal" class="modal fade">' + + ' <div class="modal-header">' + + ' <h3>git-annex has shut down</h3>' + + ' </div>' + + ' <div class="modal-body">' + + ' You can now close this browser window.' + + ' </div>' + + '</div>' ; + +function longpoll(url, divid) { + (function( $ ) { + $.ajax({ + 'url': url, + 'dataType': 'html', + 'success': function(data, status, jqxhr) { + $('#' + divid).replaceWith(data); + connfails=0; + return 1; + }, + 'error': function(jqxhr, msg, e) { + connfails=connfails+1; + if (connfails > 3) { + // blocked by many browsers + window.close(); + $('#modal').replaceWith(connfailed); + $('#modal').modal('show'); + return 0; + } + else { + return 1; + } + } + }); + })( jQuery ); +} diff --git a/templates/longpolling.julius b/templates/longpolling.julius index 35205bd04d..29e533c418 100644 --- a/templates/longpolling.julius +++ b/templates/longpolling.julius @@ -1,54 +1,11 @@ - -// Uses long-polling to update a div with id=#{ident} -// The gethtml route should return a new div, with the same id. -// -// Maximum update frequency is controlled by #{startdelay} -// and #{delay}, both in milliseconds. - -connfails=0; - -connfailed= - '<div id="modal" class="modal fade">' + - ' <div class="modal-header">' + - ' <h3>git-annex has shut down</h3>' + - ' </div>' + - ' <div class="modal-body">' + - ' You can now close this browser window.' + - ' </div>' + - '</div>' ; - -(function( $ ) { - -$.LongPoll#{ident} = (function() { - return { - send : function() { - $.ajax({ - 'url': '@{gethtml}', - 'dataType': 'html', - 'success': function(data, status, jqxhr) { - $('##{ident}').replaceWith(data); - setTimeout($.LongPoll#{ident}.send, #{show delay}); - numerrs=0; - }, - 'error': function(jqxhr, msg, e) { - connfails=connfails+1; - if (connfails > 3) { - // blocked by many browsers - window.close(); - $('#modal').replaceWith(connfailed); - $('#modal').modal('show'); - } - else { - setTimeout($.LongPoll#{ident}.send, #{show delay}); - } - }, - }); - } +// longpolling for #{ident} +function poller#{ident}() { + if (longpoll('@{gethtml}', '#{ident}')) { + setTimeout(poller#{ident}, #{delay}); } -}()); - -$(document).bind('ready.app', function() { - setTimeout($.LongPoll#{ident}.send, #{show startdelay}); -}); - +} +(function( $ ) { + $(document).bind('ready.app', function() { + setTimeout(poller#{ident}, #{startdelay}); + }); })( jQuery ); From 254c174bba261a14ebd75e9fefae823a8a0f3d88 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 18:18:53 -0400 Subject: [PATCH 192/331] fix transfers display logic --- Assistant/Threads/WebApp.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index e75870e0d7..fac2cf1eab 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -163,11 +163,9 @@ transfersDisplay warnNoScript = do if null transfers then ifM (lift $ showIntro <$> getWebAppState) ( introDisplay ident - , noop + , $(widgetFile "transfers") ) - else do - lift $ modifyWebAppState $ \s -> s { showIntro = False } - $(widgetFile "transfers") + else $(widgetFile "transfers") transfersDisplayIdent :: Text transfersDisplayIdent = "transfers" @@ -188,6 +186,7 @@ introDisplay ident = do let barelyenough = n == 2 let morethanenough = n > 2 $(widgetFile "intro") + lift $ modifyWebAppState $ \s -> s { showIntro = False } where counter = map show ([1..] :: [Int]) From 5de897e8d70d82effe389fddf4b8be287b5f738f Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 18:26:36 -0400 Subject: [PATCH 193/331] remove the "running" alert --- Assistant/Alert.hs | 7 ------- Assistant/Threads/Watcher.hs | 2 -- 2 files changed, 9 deletions(-) diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs index 54192aae65..9a0bba8ae5 100644 --- a/Assistant/Alert.hs +++ b/Assistant/Alert.hs @@ -174,13 +174,6 @@ activityAlert header message = baseActivityAlert startupScanAlert :: Alert startupScanAlert = activityAlert Nothing "Performing startup scan" -runningAlert :: Alert -runningAlert = baseActivityAlert - { alertClass = Success - , alertMessage = StringAlert "Running" - , alertPriority = Pinned - } - pushAlert :: [Remote] -> Alert pushAlert rs = activityAlert Nothing $ "Syncing with " ++ unwords (map Remote.name rs) diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs index 51dc572636..8ba015b19a 100644 --- a/Assistant/Threads/Watcher.hs +++ b/Assistant/Threads/Watcher.hs @@ -87,8 +87,6 @@ startupScan st dstatus scanner = do modifyDaemonStatus_ dstatus $ \s -> s { scanComplete = True } return (True, r) - - void $ addAlert dstatus runningAlert return r From 9648acc7a4edd44a080f40d8e918b1388b24171a Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 20:22:10 -0400 Subject: [PATCH 194/331] got this JS working --- static/longpolling.js | 45 +++++++++++++++++------------------- templates/longpolling.julius | 12 ++++------ 2 files changed, 26 insertions(+), 31 deletions(-) diff --git a/static/longpolling.js b/static/longpolling.js index 4e5f102f00..75c6faeaf3 100644 --- a/static/longpolling.js +++ b/static/longpolling.js @@ -13,29 +13,26 @@ connfailed= ' </div>' + '</div>' ; -function longpoll(url, divid) { - (function( $ ) { - $.ajax({ - 'url': url, - 'dataType': 'html', - 'success': function(data, status, jqxhr) { - $('#' + divid).replaceWith(data); - connfails=0; - return 1; - }, - 'error': function(jqxhr, msg, e) { - connfails=connfails+1; - if (connfails > 3) { - // blocked by many browsers - window.close(); - $('#modal').replaceWith(connfailed); - $('#modal').modal('show'); - return 0; - } - else { - return 1; - } +function longpoll(url, divid, cont) { + $.ajax({ + 'url': url, + 'dataType': 'html', + 'success': function(data, status, jqxhr) { + $('#' + divid).replaceWith(data); + connfails=0; + cont(); + }, + 'error': function(jqxhr, msg, e) { + connfails=connfails+1; + if (connfails > 3) { + // blocked by many browsers + window.close(); + $('#modal').replaceWith(connfailed); + $('#modal').modal('show'); } - }); - })( jQuery ); + else { + cont(); + } + } + }); } diff --git a/templates/longpolling.julius b/templates/longpolling.julius index 29e533c418..d34d5b47d8 100644 --- a/templates/longpolling.julius +++ b/templates/longpolling.julius @@ -1,11 +1,9 @@ // longpolling for #{ident} function poller#{ident}() { - if (longpoll('@{gethtml}', '#{ident}')) { + longpoll('@{gethtml}', '#{ident}', function() { setTimeout(poller#{ident}, #{delay}); - } -} -(function( $ ) { - $(document).bind('ready.app', function() { - setTimeout(poller#{ident}, #{startdelay}); }); -})( jQuery ); +} +$(function() { + setTimeout(poller#{ident}, #{startdelay}); +}); From d3413ee5a98367bc2f3c56011db8c9393306d80b Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 20:33:23 -0400 Subject: [PATCH 195/331] further refactoring my js --- static/longpolling.js | 17 ++--------------- templates/longpolling.julius | 7 ++++--- templates/page.julius | 17 +++++++++++++++++ 3 files changed, 23 insertions(+), 18 deletions(-) create mode 100644 templates/page.julius diff --git a/static/longpolling.js b/static/longpolling.js index 75c6faeaf3..5b704acec3 100644 --- a/static/longpolling.js +++ b/static/longpolling.js @@ -3,17 +3,7 @@ connfails=0; -connfailed= - '<div id="modal" class="modal fade">' + - ' <div class="modal-header">' + - ' <h3>git-annex has shut down</h3>' + - ' </div>' + - ' <div class="modal-body">' + - ' You can now close this browser window.' + - ' </div>' + - '</div>' ; - -function longpoll(url, divid, cont) { +function longpoll(url, divid, cont, fail) { $.ajax({ 'url': url, 'dataType': 'html', @@ -25,10 +15,7 @@ function longpoll(url, divid, cont) { 'error': function(jqxhr, msg, e) { connfails=connfails+1; if (connfails > 3) { - // blocked by many browsers - window.close(); - $('#modal').replaceWith(connfailed); - $('#modal').modal('show'); + fail(); } else { cont(); diff --git a/templates/longpolling.julius b/templates/longpolling.julius index d34d5b47d8..520699cd73 100644 --- a/templates/longpolling.julius +++ b/templates/longpolling.julius @@ -1,8 +1,9 @@ // longpolling for #{ident} function poller#{ident}() { - longpoll('@{gethtml}', '#{ident}', function() { - setTimeout(poller#{ident}, #{delay}); - }); + longpoll('@{gethtml}', '#{ident}' + , function() { setTimeout(poller#{ident}, #{delay}); } + , function() { webapp_disconnected(); } + ); } $(function() { setTimeout(poller#{ident}, #{startdelay}); diff --git a/templates/page.julius b/templates/page.julius new file mode 100644 index 0000000000..a9d0b42239 --- /dev/null +++ b/templates/page.julius @@ -0,0 +1,17 @@ +connfailed = + '<div id="modal" class="modal fade">' + + ' <div class="modal-header">' + + ' <h3>git-annex has shut down</h3>' + + ' </div>' + + ' <div class="modal-body">' + + ' You can now close this browser window.' + + ' </div>' + + '</div>' ; + +function webapp_disconnected () { + $('#modal').replaceWith(connfailed); + $('#modal').modal('show'); + + // ideal, but blocked by many browsers + window.close(); +} From 2821f9f976b104bcb107f44a13ae7f2eb61f2d7a Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 20:35:30 -0400 Subject: [PATCH 196/331] cleanup --- templates/longpolling.julius | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/templates/longpolling.julius b/templates/longpolling.julius index 520699cd73..67fe059cf9 100644 --- a/templates/longpolling.julius +++ b/templates/longpolling.julius @@ -1,10 +1,9 @@ -// longpolling for #{ident} -function poller#{ident}() { +function longpoll_#{ident}() { longpoll('@{gethtml}', '#{ident}' - , function() { setTimeout(poller#{ident}, #{delay}); } + , function() { setTimeout(longpoll_#{ident}, #{delay}); } , function() { webapp_disconnected(); } ); } $(function() { - setTimeout(poller#{ident}, #{startdelay}); + setTimeout(longpoll_#{ident}, #{startdelay}); }); From 6e40aed948c44348c977bb7ed7a9a6a84b9972ba Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Mon, 30 Jul 2012 22:24:19 -0400 Subject: [PATCH 197/331] fix noscript mode to not allocate notification ids on each refresh Now the javascript does an ajax call at the start to request the url to use to poll, and the notification id is generated then, once we know javascript is working. --- Assistant/Threads/WebApp.hs | 82 +++++++++++++++++++++--------------- static/longpolling.js | 4 +- templates/dashboard.hamlet | 10 +++++ templates/longpolling.julius | 7 ++- 4 files changed, 65 insertions(+), 38 deletions(-) create mode 100644 templates/dashboard.hamlet diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index a9b87ea58c..79a388463b 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -36,6 +36,7 @@ import Text.Hamlet import Network.Socket (PortNumber) import Text.Blaze.Renderer.String import Data.Text (Text, pack, unpack) +import qualified Data.Text as T import qualified Data.Map as M import Control.Concurrent.STM @@ -93,6 +94,8 @@ mkYesod "WebApp" [parseRoutes| /noscriptauto NoScriptAutoR GET /transfers/#NotificationId TransfersR GET /sidebar/#NotificationId SideBarR GET +/notifier/transfers NotifierTransfersR GET +/notifier/sidebar NotifierSideBarR GET /closealert/#AlertId CloseAlert GET /config ConfigR GET /addrepository AddRepositoryR GET @@ -136,19 +139,40 @@ instance Yesod WebApp where - - The widget should have a html element with an id=ident, which will be - replaced when it's updated. - - - - Updating is done by getting html from the gethtml route. + - + - The geturl route should return the notifier url to use for polling. - - ms_delay is how long to delay between AJAX updates - ms_startdelay is how long to delay before updating with AJAX at the start -} autoUpdate :: Text -> Route WebApp -> Int -> Int -> Widget -autoUpdate ident gethtml ms_delay ms_startdelay = do +autoUpdate ident geturl ms_delay ms_startdelay = do let delay = show ms_delay let startdelay = show ms_startdelay addScript $ StaticR longpolling_js $(widgetFile "longpolling") +{- Notifier urls are requested by the javascript, to avoid allocation + - of NotificationIds when noscript pages are loaded. This constructs a + - notifier url for a given Route and NotificationBroadcaster. + -} +notifierUrl :: (NotificationId -> Route WebApp) -> (DaemonStatus -> NotificationBroadcaster) -> Handler RepPlain +notifierUrl route selector = do + (urlbits, _params) <- renderRoute . route <$> newNotifier selector + webapp <- getYesod + return $ RepPlain $ toContent $ T.concat + [ "/" + , T.intercalate "/" urlbits + , "?auth=" + , secretToken webapp + ] + +getNotifierTransfersR :: Handler RepPlain +getNotifierTransfersR = notifierUrl TransfersR transferNotifier + +getNotifierSideBarR :: Handler RepPlain +getNotifierSideBarR = notifierUrl SideBarR alertNotifier + {- A display of currently running and queued transfers. - - Or, if there have never been any this run, an intro display. -} @@ -159,7 +183,8 @@ transfersDisplay warnNoScript = do M.toList . currentTransfers <$> liftIO (getDaemonStatus $ daemonStatus webapp) queued <- liftIO $ getTransferQueue $ transferQueue webapp - let ident = transfersDisplayIdent + let ident = "transfers" + autoUpdate ident NotifierTransfersR (10 :: Int) (10 :: Int) let transfers = current ++ queued if null transfers then ifM (lift $ showIntro <$> getWebAppState) @@ -168,9 +193,7 @@ transfersDisplay warnNoScript = do ) else $(widgetFile "transfers") -transfersDisplayIdent :: Text -transfersDisplayIdent = "transfers" - +{- An intro message, and list of repositories. -} introDisplay :: Text -> Widget introDisplay ident = do webapp <- lift getYesod @@ -206,8 +229,8 @@ getTransfersR nid = do page <- widgetToPageContent $ transfersDisplay False hamletToRepHtml $ [hamlet|^{pageBody page}|] -sideBarDisplay :: Bool -> Widget -sideBarDisplay noScript = do +sideBarDisplay :: Widget +sideBarDisplay = do let content = do {- Any yesod message appears as the first alert. -} maybe noop rendermessage =<< lift getMessage @@ -218,14 +241,9 @@ sideBarDisplay noScript = do <$> liftIO (getDaemonStatus $ daemonStatus webapp) mapM_ renderalert $ take displayAlerts $ reverse $ sortAlertPairs alertpairs - ident <- lift newIdent + let ident = "sidebar" $(widgetFile "sidebar") - - unless noScript $ do - {- Set up automatic updates of the sidebar - - when alerts come in. -} - nid <- lift $ newNotifier alertNotifier - autoUpdate ident (SideBarR nid) (10 :: Int) (10 :: Int) + autoUpdate ident NotifierSideBarR (10 :: Int) (10 :: Int) where bootstrapclass Activity = "alert-info" bootstrapclass Warning = "alert" @@ -264,7 +282,7 @@ getSideBarR :: NotificationId -> Handler RepHtml getSideBarR nid = do waitNotifier alertNotifier nid - page <- widgetToPageContent $ sideBarDisplay True + page <- widgetToPageContent sideBarDisplay hamletToRepHtml $ [hamlet|^{pageBody page}|] {- Called by the client to close an alert. -} @@ -273,43 +291,39 @@ getCloseAlert i = do webapp <- getYesod void $ liftIO $ removeAlert (daemonStatus webapp) i -dashboard :: Bool -> Bool -> Widget -dashboard noScript warnNoScript = do - sideBarDisplay noScript - transfersDisplay warnNoScript +{- The main dashboard. -} +dashboard :: Bool -> Widget +dashboard warnNoScript = do + sideBarDisplay + let content = transfersDisplay warnNoScript + $(widgetFile "dashboard") getHomeR :: Handler RepHtml -getHomeR = defaultLayout $ do - {- Set up automatic updates for the transfers display. -} - nid <- lift $ newNotifier transferNotifier - autoUpdate transfersDisplayIdent (TransfersR nid) (10 :: Int) (10 :: Int) - - dashboard False True +getHomeR = defaultLayout $ dashboard True -{- Same as HomeR, except with no javascript, so it doesn't allocate - - new resources each time the page is refreshed, and with autorefreshing - - via meta refresh. -} +{- Same as HomeR, except with autorefreshing via meta refresh. -} getNoScriptAutoR :: Handler RepHtml getNoScriptAutoR = defaultLayout $ do let ident = NoScriptR let delayseconds = 3 :: Int let this = NoScriptAutoR toWidgetHead $(hamletFile $ hamletTemplate "metarefresh") - dashboard True False + dashboard False +{- Same as HomeR, except no autorefresh at all (and no noscript warning). -} getNoScriptR :: Handler RepHtml getNoScriptR = defaultLayout $ - dashboard True True + dashboard False getConfigR :: Handler RepHtml getConfigR = defaultLayout $ do - sideBarDisplay False + sideBarDisplay setTitle "Configuration" [whamlet|<a href="@{HomeR}">main|] getAddRepositoryR :: Handler RepHtml getAddRepositoryR = defaultLayout $ do - sideBarDisplay False + sideBarDisplay setTitle "Add repository" [whamlet|<a href="@{HomeR}">main|] diff --git a/static/longpolling.js b/static/longpolling.js index 5b704acec3..965c1d18db 100644 --- a/static/longpolling.js +++ b/static/longpolling.js @@ -1,5 +1,5 @@ -// Uses long-polling to update a div with a specified id, -// by polling an url, which should return a new div, with the same id. +// Updates a div with a specified id, by polling an url, +// which should return a new div, with the same id. connfails=0; diff --git a/templates/dashboard.hamlet b/templates/dashboard.hamlet new file mode 100644 index 0000000000..7bcfce9626 --- /dev/null +++ b/templates/dashboard.hamlet @@ -0,0 +1,10 @@ +^{content} +$if warnNoScript + <noscript> + <div .navbar .navbar-fixed-bottom> + <div .navbar-inner> + <div .container> + Javascript is disabled; cannot update in real-time. + <div .btn-group> + <a .btn .btn-primary href="@{NoScriptAutoR}">Auto-refresh every 3 seconds # + <a .btn .btn-primary href="@{NoScriptR}">Manually refresh diff --git a/templates/longpolling.julius b/templates/longpolling.julius index 67fe059cf9..affa50cc81 100644 --- a/templates/longpolling.julius +++ b/templates/longpolling.julius @@ -1,9 +1,12 @@ function longpoll_#{ident}() { - longpoll('@{gethtml}', '#{ident}' + longpoll(longpoll_#{ident}_url, '#{ident}' , function() { setTimeout(longpoll_#{ident}, #{delay}); } , function() { webapp_disconnected(); } ); } $(function() { - setTimeout(longpoll_#{ident}, #{startdelay}); + $.get("@{geturl}", function(url){ + longpoll_#{ident}_url = url; + setTimeout(longpoll_#{ident}, #{startdelay}); + }); }); From 58dfa3fa5b1b8be6f344e9ef5bfb3adda11069ab Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Tue, 31 Jul 2012 01:11:32 -0400 Subject: [PATCH 198/331] split up webapp files --- Assistant/Threads/WebApp.hs | 304 +----------------------------- Assistant/WebApp.hs | 106 +++++++++++ Assistant/WebApp/Configurators.hs | 56 ++++++ Assistant/WebApp/DashBoard.hs | 89 +++++++++ Assistant/WebApp/Notifications.hs | 58 ++++++ Assistant/WebApp/SideBar.hs | 84 +++++++++ Assistant/WebApp/routes | 13 ++ 7 files changed, 413 insertions(+), 297 deletions(-) create mode 100644 Assistant/WebApp.hs create mode 100644 Assistant/WebApp/Configurators.hs create mode 100644 Assistant/WebApp/DashBoard.hs create mode 100644 Assistant/WebApp/Notifications.hs create mode 100644 Assistant/WebApp/SideBar.hs create mode 100644 Assistant/WebApp/routes diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 79a388463b..7b794b6ebf 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -11,321 +11,31 @@ module Assistant.Threads.WebApp where import Assistant.Common +import Assistant.WebApp +import Assistant.WebApp.DashBoard +import Assistant.WebApp.SideBar +import Assistant.WebApp.Notifications +import Assistant.WebApp.Configurators import Assistant.ThreadedMonad import Assistant.DaemonStatus import Assistant.TransferQueue -import Assistant.Alert hiding (Widget) -import Utility.NotificationBroadcaster import Utility.WebApp import Utility.Yesod import Utility.FileMode import Utility.TempFile import Git -import Logs.Transfer -import Utility.Percentage -import Utility.DataUnits -import Types.Key -import qualified Remote -import Logs.Web (webUUID) -import Logs.Trust -import Annex.UUID (getUUID) import Yesod import Yesod.Static import Text.Hamlet import Network.Socket (PortNumber) import Text.Blaze.Renderer.String -import Data.Text (Text, pack, unpack) -import qualified Data.Text as T -import qualified Data.Map as M -import Control.Concurrent.STM +import Data.Text (pack, unpack) thisThread :: String thisThread = "WebApp" -data WebApp = WebApp - { threadState :: ThreadState - , daemonStatus :: DaemonStatusHandle - , transferQueue :: TransferQueue - , secretToken :: Text - , relDir :: FilePath - , getStatic :: Static - , webAppState :: TMVar WebAppState - } - -data WebAppState = WebAppState - { showIntro :: Bool - } - -newWebAppState :: IO (TMVar WebAppState) -newWebAppState = liftIO $ atomically $ - newTMVar $ WebAppState { showIntro = True } - -getWebAppState :: forall sub. GHandler sub WebApp WebAppState -getWebAppState = liftIO . atomically . readTMVar =<< webAppState <$> getYesod - -modifyWebAppState :: forall sub. (WebAppState -> WebAppState) -> GHandler sub WebApp () -modifyWebAppState a = go =<< webAppState <$> getYesod - where - go s = liftIO $ atomically $ do - v <- takeTMVar s - putTMVar s $ a v - -waitNotifier :: forall sub. (DaemonStatus -> NotificationBroadcaster) -> NotificationId -> GHandler sub WebApp () -waitNotifier selector nid = do - notifier <- getNotifier selector - liftIO $ waitNotification $ notificationHandleFromId notifier nid - -newNotifier :: forall sub. (DaemonStatus -> NotificationBroadcaster) -> GHandler sub WebApp NotificationId -newNotifier selector = do - notifier <- getNotifier selector - liftIO $ notificationHandleToId <$> newNotificationHandle notifier - -getNotifier :: forall sub. (DaemonStatus -> NotificationBroadcaster) -> GHandler sub WebApp NotificationBroadcaster -getNotifier selector = do - webapp <- getYesod - liftIO $ selector <$> getDaemonStatus (daemonStatus webapp) - -staticFiles "static" - -mkYesod "WebApp" [parseRoutes| -/ HomeR GET -/noscript NoScriptR GET -/noscriptauto NoScriptAutoR GET -/transfers/#NotificationId TransfersR GET -/sidebar/#NotificationId SideBarR GET -/notifier/transfers NotifierTransfersR GET -/notifier/sidebar NotifierSideBarR GET -/closealert/#AlertId CloseAlert GET -/config ConfigR GET -/addrepository AddRepositoryR GET -/static StaticR Static getStatic -|] - -instance PathPiece NotificationId where - toPathPiece = pack . show - fromPathPiece = readish . unpack - -instance PathPiece AlertId where - toPathPiece = pack . show - fromPathPiece = readish . unpack - -instance Yesod WebApp where - defaultLayout content = do - webapp <- getYesod - page <- widgetToPageContent $ do - addStylesheet $ StaticR css_bootstrap_css - addStylesheet $ StaticR css_bootstrap_responsive_css - addScript $ StaticR jquery_full_js - addScript $ StaticR js_bootstrap_dropdown_js - addScript $ StaticR js_bootstrap_modal_js - $(widgetFile "page") - hamletToRepHtml $(hamletFile $ hamletTemplate "bootstrap") - - {- Require an auth token be set when accessing any (non-static route) -} - isAuthorized _ _ = checkAuthToken secretToken - - {- Add the auth token to every url generated, except static subsite - - urls (which can show up in Permission Denied pages). -} - joinPath = insertAuthToken secretToken excludeStatic - where - excludeStatic [] = True - excludeStatic (p:_) = p /= "static" - - makeSessionBackend = webAppSessionBackend - jsLoader _ = BottomOfHeadBlocking - -{- Add to any widget to make it auto-update using long polling. - - - - The widget should have a html element with an id=ident, which will be - - replaced when it's updated. - - - - The geturl route should return the notifier url to use for polling. - - - - ms_delay is how long to delay between AJAX updates - - ms_startdelay is how long to delay before updating with AJAX at the start - -} -autoUpdate :: Text -> Route WebApp -> Int -> Int -> Widget -autoUpdate ident geturl ms_delay ms_startdelay = do - let delay = show ms_delay - let startdelay = show ms_startdelay - addScript $ StaticR longpolling_js - $(widgetFile "longpolling") - -{- Notifier urls are requested by the javascript, to avoid allocation - - of NotificationIds when noscript pages are loaded. This constructs a - - notifier url for a given Route and NotificationBroadcaster. - -} -notifierUrl :: (NotificationId -> Route WebApp) -> (DaemonStatus -> NotificationBroadcaster) -> Handler RepPlain -notifierUrl route selector = do - (urlbits, _params) <- renderRoute . route <$> newNotifier selector - webapp <- getYesod - return $ RepPlain $ toContent $ T.concat - [ "/" - , T.intercalate "/" urlbits - , "?auth=" - , secretToken webapp - ] - -getNotifierTransfersR :: Handler RepPlain -getNotifierTransfersR = notifierUrl TransfersR transferNotifier - -getNotifierSideBarR :: Handler RepPlain -getNotifierSideBarR = notifierUrl SideBarR alertNotifier - -{- A display of currently running and queued transfers. - - - - Or, if there have never been any this run, an intro display. -} -transfersDisplay :: Bool -> Widget -transfersDisplay warnNoScript = do - webapp <- lift getYesod - current <- liftIO $ runThreadState (threadState webapp) $ - M.toList . currentTransfers - <$> liftIO (getDaemonStatus $ daemonStatus webapp) - queued <- liftIO $ getTransferQueue $ transferQueue webapp - let ident = "transfers" - autoUpdate ident NotifierTransfersR (10 :: Int) (10 :: Int) - let transfers = current ++ queued - if null transfers - then ifM (lift $ showIntro <$> getWebAppState) - ( introDisplay ident - , $(widgetFile "transfers") - ) - else $(widgetFile "transfers") - -{- An intro message, and list of repositories. -} -introDisplay :: Text -> Widget -introDisplay ident = do - webapp <- lift getYesod - let reldir = relDir webapp - l <- liftIO $ runThreadState (threadState webapp) $ do - u <- getUUID - rs <- map Remote.uuid <$> Remote.remoteList - rs' <- snd <$> trustPartition DeadTrusted rs - Remote.prettyListUUIDs $ filter (/= webUUID) $ nub $ u:rs' - let remotelist = zip counter l - let n = length l - let numrepos = show n - let notenough = n < 2 - let barelyenough = n == 2 - let morethanenough = n > 2 - $(widgetFile "intro") - lift $ modifyWebAppState $ \s -> s { showIntro = False } - where - counter = map show ([1..] :: [Int]) - -{- Called by client to get a display of currently in process transfers. - - - - Returns a div, which will be inserted into the calling page. - - - - Note that the head of the widget is not included, only its - - body is. To get the widget head content, the widget is also - - inserted onto the getHomeR page. - -} -getTransfersR :: NotificationId -> Handler RepHtml -getTransfersR nid = do - waitNotifier transferNotifier nid - - page <- widgetToPageContent $ transfersDisplay False - hamletToRepHtml $ [hamlet|^{pageBody page}|] - -sideBarDisplay :: Widget -sideBarDisplay = do - let content = do - {- Any yesod message appears as the first alert. -} - maybe noop rendermessage =<< lift getMessage - - {- Add newest alerts to the sidebar. -} - webapp <- lift getYesod - alertpairs <- M.toList . alertMap - <$> liftIO (getDaemonStatus $ daemonStatus webapp) - mapM_ renderalert $ - take displayAlerts $ reverse $ sortAlertPairs alertpairs - let ident = "sidebar" - $(widgetFile "sidebar") - autoUpdate ident NotifierSideBarR (10 :: Int) (10 :: Int) - where - bootstrapclass Activity = "alert-info" - bootstrapclass Warning = "alert" - bootstrapclass Error = "alert-error" - bootstrapclass Success = "alert-success" - bootstrapclass Message = "alert-info" - - renderalert (alertid, alert) = addalert - alertid - (alertClosable alert) - (alertBlockDisplay alert) - (bootstrapclass $ alertClass alert) - (alertHeader alert) - $ case alertMessage alert of - StringAlert s -> [whamlet|#{s}|] - WidgetAlert w -> w alert - - rendermessage msg = addalert firstAlertId True False - "alert-info" Nothing [whamlet|#{msg}|] - - addalert :: AlertId -> Bool -> Bool -> Text -> Maybe String -> Widget -> Widget - addalert i closable block divclass heading widget = do - let alertid = show i - let closealert = CloseAlert i - $(widgetFile "alert") - -{- Called by client to get a sidebar display. - - - - Returns a div, which will be inserted into the calling page. - - - - Note that the head of the widget is not included, only its - - body is. To get the widget head content, the widget is also - - inserted onto all pages. - -} -getSideBarR :: NotificationId -> Handler RepHtml -getSideBarR nid = do - waitNotifier alertNotifier nid - - page <- widgetToPageContent sideBarDisplay - hamletToRepHtml $ [hamlet|^{pageBody page}|] - -{- Called by the client to close an alert. -} -getCloseAlert :: AlertId -> Handler () -getCloseAlert i = do - webapp <- getYesod - void $ liftIO $ removeAlert (daemonStatus webapp) i - -{- The main dashboard. -} -dashboard :: Bool -> Widget -dashboard warnNoScript = do - sideBarDisplay - let content = transfersDisplay warnNoScript - $(widgetFile "dashboard") - -getHomeR :: Handler RepHtml -getHomeR = defaultLayout $ dashboard True - -{- Same as HomeR, except with autorefreshing via meta refresh. -} -getNoScriptAutoR :: Handler RepHtml -getNoScriptAutoR = defaultLayout $ do - let ident = NoScriptR - let delayseconds = 3 :: Int - let this = NoScriptAutoR - toWidgetHead $(hamletFile $ hamletTemplate "metarefresh") - dashboard False - -{- Same as HomeR, except no autorefresh at all (and no noscript warning). -} -getNoScriptR :: Handler RepHtml -getNoScriptR = defaultLayout $ - dashboard False - -getConfigR :: Handler RepHtml -getConfigR = defaultLayout $ do - sideBarDisplay - setTitle "Configuration" - [whamlet|<a href="@{HomeR}">main|] - -getAddRepositoryR :: Handler RepHtml -getAddRepositoryR = defaultLayout $ do - sideBarDisplay - setTitle "Add repository" - [whamlet|<a href="@{HomeR}">main|] +mkYesodDispatch "WebApp" $(parseRoutesFile "Assistant/WebApp/routes") webAppThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> Maybe (IO ()) -> IO () webAppThread st dstatus transferqueue onstartup = do diff --git a/Assistant/WebApp.hs b/Assistant/WebApp.hs new file mode 100644 index 0000000000..d3989a68af --- /dev/null +++ b/Assistant/WebApp.hs @@ -0,0 +1,106 @@ +{- git-annex assistant webapp data types + - + - Copyright 2012 Joey Hess <joey@kitenet.net> + - + - Licensed under the GNU GPL version 3 or higher. + -} + +{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-} +{-# OPTIONS_GHC -fno-warn-orphans #-} + +module Assistant.WebApp where + +import Assistant.Common +import Assistant.ThreadedMonad +import Assistant.DaemonStatus +import Assistant.TransferQueue +import Assistant.Alert hiding (Widget) +import Utility.NotificationBroadcaster +import Utility.WebApp +import Utility.Yesod + +import Yesod +import Yesod.Static +import Text.Hamlet +import Data.Text (Text, pack, unpack) +import Control.Concurrent.STM + +staticFiles "static" + +mkYesodData "WebApp" $(parseRoutesFile "Assistant/WebApp/routes") + +data WebApp = WebApp + { threadState :: ThreadState + , daemonStatus :: DaemonStatusHandle + , transferQueue :: TransferQueue + , secretToken :: Text + , relDir :: FilePath + , getStatic :: Static + , webAppState :: TMVar WebAppState + } + +instance Yesod WebApp where + defaultLayout content = do + webapp <- getYesod + page <- widgetToPageContent $ do + addStylesheet $ StaticR css_bootstrap_css + addStylesheet $ StaticR css_bootstrap_responsive_css + addScript $ StaticR jquery_full_js + addScript $ StaticR js_bootstrap_dropdown_js + addScript $ StaticR js_bootstrap_modal_js + $(widgetFile "page") + hamletToRepHtml $(hamletFile $ hamletTemplate "bootstrap") + + {- Require an auth token be set when accessing any (non-static route) -} + isAuthorized _ _ = checkAuthToken secretToken + + {- Add the auth token to every url generated, except static subsite + - urls (which can show up in Permission Denied pages). -} + joinPath = insertAuthToken secretToken excludeStatic + where + excludeStatic [] = True + excludeStatic (p:_) = p /= "static" + + makeSessionBackend = webAppSessionBackend + jsLoader _ = BottomOfHeadBlocking + +data WebAppState = WebAppState + { showIntro :: Bool + } + +newWebAppState :: IO (TMVar WebAppState) +newWebAppState = liftIO $ atomically $ + newTMVar $ WebAppState { showIntro = True } + +getWebAppState :: forall sub. GHandler sub WebApp WebAppState +getWebAppState = liftIO . atomically . readTMVar =<< webAppState <$> getYesod + +modifyWebAppState :: forall sub. (WebAppState -> WebAppState) -> GHandler sub WebApp () +modifyWebAppState a = go =<< webAppState <$> getYesod + where + go s = liftIO $ atomically $ do + v <- takeTMVar s + putTMVar s $ a v + +waitNotifier :: forall sub. (DaemonStatus -> NotificationBroadcaster) -> NotificationId -> GHandler sub WebApp () +waitNotifier selector nid = do + notifier <- getNotifier selector + liftIO $ waitNotification $ notificationHandleFromId notifier nid + +newNotifier :: forall sub. (DaemonStatus -> NotificationBroadcaster) -> GHandler sub WebApp NotificationId +newNotifier selector = do + notifier <- getNotifier selector + liftIO $ notificationHandleToId <$> newNotificationHandle notifier + +getNotifier :: forall sub. (DaemonStatus -> NotificationBroadcaster) -> GHandler sub WebApp NotificationBroadcaster +getNotifier selector = do + webapp <- getYesod + liftIO $ selector <$> getDaemonStatus (daemonStatus webapp) + +instance PathPiece NotificationId where + toPathPiece = pack . show + fromPathPiece = readish . unpack + +instance PathPiece AlertId where + toPathPiece = pack . show + fromPathPiece = readish . unpack diff --git a/Assistant/WebApp/Configurators.hs b/Assistant/WebApp/Configurators.hs new file mode 100644 index 0000000000..be6f12db3c --- /dev/null +++ b/Assistant/WebApp/Configurators.hs @@ -0,0 +1,56 @@ +{- git-annex assistant webapp configurators + - + - Copyright 2012 Joey Hess <joey@kitenet.net> + - + - Licensed under the GNU GPL version 3 or higher. + -} + +{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-} + +module Assistant.WebApp.Configurators where + +import Assistant.Common +import Assistant.WebApp +import Assistant.WebApp.SideBar +import Assistant.ThreadedMonad +import Utility.Yesod +import qualified Remote +import Logs.Web (webUUID) +import Logs.Trust +import Annex.UUID (getUUID) + +import Yesod +import Data.Text (Text) + +{- An intro message, list of repositories, and nudge to make more. -} +introDisplay :: Text -> Widget +introDisplay ident = do + webapp <- lift getYesod + let reldir = relDir webapp + l <- liftIO $ runThreadState (threadState webapp) $ do + u <- getUUID + rs <- map Remote.uuid <$> Remote.remoteList + rs' <- snd <$> trustPartition DeadTrusted rs + Remote.prettyListUUIDs $ filter (/= webUUID) $ nub $ u:rs' + let remotelist = zip counter l + let n = length l + let numrepos = show n + let notenough = n < 2 + let barelyenough = n == 2 + let morethanenough = n > 2 + $(widgetFile "intro") + lift $ modifyWebAppState $ \s -> s { showIntro = False } + where + counter = map show ([1..] :: [Int]) + +getConfigR :: Handler RepHtml +getConfigR = defaultLayout $ do + sideBarDisplay + setTitle "Configuration" + [whamlet|<a href="@{HomeR}">main|] + +getAddRepositoryR :: Handler RepHtml +getAddRepositoryR = defaultLayout $ do + sideBarDisplay + setTitle "Add repository" + [whamlet|<a href="@{HomeR}">main|] diff --git a/Assistant/WebApp/DashBoard.hs b/Assistant/WebApp/DashBoard.hs new file mode 100644 index 0000000000..5df68c93b6 --- /dev/null +++ b/Assistant/WebApp/DashBoard.hs @@ -0,0 +1,89 @@ +{- git-annex assistant webapp dashboard + - + - Copyright 2012 Joey Hess <joey@kitenet.net> + - + - Licensed under the GNU GPL version 3 or higher. + -} + +{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-} + +module Assistant.WebApp.DashBoard where + +import Assistant.Common +import Assistant.WebApp +import Assistant.WebApp.SideBar +import Assistant.WebApp.Notifications +import Assistant.WebApp.Configurators +import Assistant.ThreadedMonad +import Assistant.DaemonStatus +import Assistant.TransferQueue +import Utility.NotificationBroadcaster +import Utility.Yesod +import Logs.Transfer +import Utility.Percentage +import Utility.DataUnits +import Types.Key +import qualified Remote + +import Yesod +import Text.Hamlet +import qualified Data.Map as M + +{- A display of currently running and queued transfers. + - + - Or, if there have never been any this run, an intro display. -} +transfersDisplay :: Bool -> Widget +transfersDisplay warnNoScript = do + webapp <- lift getYesod + current <- liftIO $ runThreadState (threadState webapp) $ + M.toList . currentTransfers + <$> liftIO (getDaemonStatus $ daemonStatus webapp) + queued <- liftIO $ getTransferQueue $ transferQueue webapp + let ident = "transfers" + autoUpdate ident NotifierTransfersR (10 :: Int) (10 :: Int) + let transfers = current ++ queued + if null transfers + then ifM (lift $ showIntro <$> getWebAppState) + ( introDisplay ident + , $(widgetFile "transfers") + ) + else $(widgetFile "transfers") + +{- Called by client to get a display of currently in process transfers. + - + - Returns a div, which will be inserted into the calling page. + - + - Note that the head of the widget is not included, only its + - body is. To get the widget head content, the widget is also + - inserted onto the getHomeR page. + -} +getTransfersR :: NotificationId -> Handler RepHtml +getTransfersR nid = do + waitNotifier transferNotifier nid + + page <- widgetToPageContent $ transfersDisplay False + hamletToRepHtml $ [hamlet|^{pageBody page}|] + +{- The main dashboard. -} +dashboard :: Bool -> Widget +dashboard warnNoScript = do + sideBarDisplay + let content = transfersDisplay warnNoScript + $(widgetFile "dashboard") + +getHomeR :: Handler RepHtml +getHomeR = defaultLayout $ dashboard True + +{- Same as HomeR, except with autorefreshing via meta refresh. -} +getNoScriptAutoR :: Handler RepHtml +getNoScriptAutoR = defaultLayout $ do + let ident = NoScriptR + let delayseconds = 3 :: Int + let this = NoScriptAutoR + toWidgetHead $(hamletFile $ hamletTemplate "metarefresh") + dashboard False + +{- Same as HomeR, except no autorefresh at all (and no noscript warning). -} +getNoScriptR :: Handler RepHtml +getNoScriptR = defaultLayout $ + dashboard False diff --git a/Assistant/WebApp/Notifications.hs b/Assistant/WebApp/Notifications.hs new file mode 100644 index 0000000000..1e7c0176a0 --- /dev/null +++ b/Assistant/WebApp/Notifications.hs @@ -0,0 +1,58 @@ +{- git-annex assistant webapp notifications + - + - Copyright 2012 Joey Hess <joey@kitenet.net> + - + - Licensed under the GNU GPL version 3 or higher. + -} + +{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-} + +module Assistant.WebApp.Notifications where + +import Assistant.Common +import Assistant.WebApp +import Assistant.DaemonStatus +import Utility.NotificationBroadcaster +import Utility.Yesod + +import Yesod +import Data.Text (Text) +import qualified Data.Text as T + +{- Add to any widget to make it auto-update using long polling. + - + - The widget should have a html element with an id=ident, which will be + - replaced when it's updated. + - + - The geturl route should return the notifier url to use for polling. + - + - ms_delay is how long to delay between AJAX updates + - ms_startdelay is how long to delay before updating with AJAX at the start + -} +autoUpdate :: Text -> Route WebApp -> Int -> Int -> Widget +autoUpdate ident geturl ms_delay ms_startdelay = do + let delay = show ms_delay + let startdelay = show ms_startdelay + addScript $ StaticR longpolling_js + $(widgetFile "longpolling") + +{- Notifier urls are requested by the javascript, to avoid allocation + - of NotificationIds when noscript pages are loaded. This constructs a + - notifier url for a given Route and NotificationBroadcaster. + -} +notifierUrl :: (NotificationId -> Route WebApp) -> (DaemonStatus -> NotificationBroadcaster) -> Handler RepPlain +notifierUrl route selector = do + (urlbits, _params) <- renderRoute . route <$> newNotifier selector + webapp <- getYesod + return $ RepPlain $ toContent $ T.concat + [ "/" + , T.intercalate "/" urlbits + , "?auth=" + , secretToken webapp + ] + +getNotifierTransfersR :: Handler RepPlain +getNotifierTransfersR = notifierUrl TransfersR transferNotifier + +getNotifierSideBarR :: Handler RepPlain +getNotifierSideBarR = notifierUrl SideBarR alertNotifier diff --git a/Assistant/WebApp/SideBar.hs b/Assistant/WebApp/SideBar.hs new file mode 100644 index 0000000000..4df0c8d550 --- /dev/null +++ b/Assistant/WebApp/SideBar.hs @@ -0,0 +1,84 @@ +{- git-annex assistant webapp sidebar + - + - Copyright 2012 Joey Hess <joey@kitenet.net> + - + - Licensed under the GNU GPL version 3 or higher. + -} + +{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-} + +module Assistant.WebApp.SideBar where + +import Assistant.Common +import Assistant.WebApp +import Assistant.WebApp.Notifications +import Assistant.DaemonStatus +import Assistant.Alert hiding (Widget) +import Utility.NotificationBroadcaster +import Utility.Yesod + +import Yesod +import Data.Text (Text) +import qualified Data.Map as M + +sideBarDisplay :: Widget +sideBarDisplay = do + let content = do + {- Any yesod message appears as the first alert. -} + maybe noop rendermessage =<< lift getMessage + + {- Add newest alerts to the sidebar. -} + webapp <- lift getYesod + alertpairs <- M.toList . alertMap + <$> liftIO (getDaemonStatus $ daemonStatus webapp) + mapM_ renderalert $ + take displayAlerts $ reverse $ sortAlertPairs alertpairs + let ident = "sidebar" + $(widgetFile "sidebar") + autoUpdate ident NotifierSideBarR (10 :: Int) (10 :: Int) + where + bootstrapclass Activity = "alert-info" + bootstrapclass Warning = "alert" + bootstrapclass Error = "alert-error" + bootstrapclass Success = "alert-success" + bootstrapclass Message = "alert-info" + + renderalert (alertid, alert) = addalert + alertid + (alertClosable alert) + (alertBlockDisplay alert) + (bootstrapclass $ alertClass alert) + (alertHeader alert) + $ case alertMessage alert of + StringAlert s -> [whamlet|#{s}|] + WidgetAlert w -> w alert + + rendermessage msg = addalert firstAlertId True False + "alert-info" Nothing [whamlet|#{msg}|] + + addalert :: AlertId -> Bool -> Bool -> Text -> Maybe String -> Widget -> Widget + addalert i closable block divclass heading widget = do + let alertid = show i + let closealert = CloseAlert i + $(widgetFile "alert") + +{- Called by client to get a sidebar display. + - + - Returns a div, which will be inserted into the calling page. + - + - Note that the head of the widget is not included, only its + - body is. To get the widget head content, the widget is also + - inserted onto all pages. + -} +getSideBarR :: NotificationId -> Handler RepHtml +getSideBarR nid = do + waitNotifier alertNotifier nid + + page <- widgetToPageContent sideBarDisplay + hamletToRepHtml $ [hamlet|^{pageBody page}|] + +{- Called by the client to close an alert. -} +getCloseAlert :: AlertId -> Handler () +getCloseAlert i = do + webapp <- getYesod + void $ liftIO $ removeAlert (daemonStatus webapp) i diff --git a/Assistant/WebApp/routes b/Assistant/WebApp/routes new file mode 100644 index 0000000000..75f1ad7c78 --- /dev/null +++ b/Assistant/WebApp/routes @@ -0,0 +1,13 @@ +/ HomeR GET +/noscript NoScriptR GET +/noscriptauto NoScriptAutoR GET +/config ConfigR GET +/addrepository AddRepositoryR GET + +/transfers/#NotificationId TransfersR GET +/sidebar/#NotificationId SideBarR GET +/notifier/transfers NotifierTransfersR GET +/notifier/sidebar NotifierSideBarR GET +/closealert/#AlertId CloseAlert GET + +/static StaticR Static getStatic From 5fed026bcdaa0724acd2640193e341bb8358980b Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Tue, 31 Jul 2012 01:24:49 -0400 Subject: [PATCH 199/331] reorg templates --- Assistant/WebApp/Configurators.hs | 2 +- Assistant/WebApp/DashBoard.hs | 8 ++++---- Assistant/WebApp/Notifications.hs | 2 +- Assistant/WebApp/SideBar.hs | 4 ++-- templates/{ => configurators}/intro.hamlet | 0 templates/{dashboard.hamlet => dashboard/main.hamlet} | 0 templates/{ => dashboard}/metarefresh.hamlet | 0 templates/{ => dashboard}/transfers.hamlet | 0 templates/{ => notifications}/longpolling.julius | 0 templates/{ => sidebar}/alert.hamlet | 0 templates/{sidebar.hamlet => sidebar/main.hamlet} | 0 11 files changed, 8 insertions(+), 8 deletions(-) rename templates/{ => configurators}/intro.hamlet (100%) rename templates/{dashboard.hamlet => dashboard/main.hamlet} (100%) rename templates/{ => dashboard}/metarefresh.hamlet (100%) rename templates/{ => dashboard}/transfers.hamlet (100%) rename templates/{ => notifications}/longpolling.julius (100%) rename templates/{ => sidebar}/alert.hamlet (100%) rename templates/{sidebar.hamlet => sidebar/main.hamlet} (100%) diff --git a/Assistant/WebApp/Configurators.hs b/Assistant/WebApp/Configurators.hs index be6f12db3c..e3f0275d9a 100644 --- a/Assistant/WebApp/Configurators.hs +++ b/Assistant/WebApp/Configurators.hs @@ -38,7 +38,7 @@ introDisplay ident = do let notenough = n < 2 let barelyenough = n == 2 let morethanenough = n > 2 - $(widgetFile "intro") + $(widgetFile "configurators/intro") lift $ modifyWebAppState $ \s -> s { showIntro = False } where counter = map show ([1..] :: [Int]) diff --git a/Assistant/WebApp/DashBoard.hs b/Assistant/WebApp/DashBoard.hs index 5df68c93b6..2961dabd35 100644 --- a/Assistant/WebApp/DashBoard.hs +++ b/Assistant/WebApp/DashBoard.hs @@ -45,9 +45,9 @@ transfersDisplay warnNoScript = do if null transfers then ifM (lift $ showIntro <$> getWebAppState) ( introDisplay ident - , $(widgetFile "transfers") + , $(widgetFile "dashboard/transfers") ) - else $(widgetFile "transfers") + else $(widgetFile "dashboard/transfers") {- Called by client to get a display of currently in process transfers. - @@ -69,7 +69,7 @@ dashboard :: Bool -> Widget dashboard warnNoScript = do sideBarDisplay let content = transfersDisplay warnNoScript - $(widgetFile "dashboard") + $(widgetFile "dashboard/main") getHomeR :: Handler RepHtml getHomeR = defaultLayout $ dashboard True @@ -80,7 +80,7 @@ getNoScriptAutoR = defaultLayout $ do let ident = NoScriptR let delayseconds = 3 :: Int let this = NoScriptAutoR - toWidgetHead $(hamletFile $ hamletTemplate "metarefresh") + toWidgetHead $(hamletFile $ hamletTemplate "dashboard/metarefresh") dashboard False {- Same as HomeR, except no autorefresh at all (and no noscript warning). -} diff --git a/Assistant/WebApp/Notifications.hs b/Assistant/WebApp/Notifications.hs index 1e7c0176a0..3aa56424a4 100644 --- a/Assistant/WebApp/Notifications.hs +++ b/Assistant/WebApp/Notifications.hs @@ -34,7 +34,7 @@ autoUpdate ident geturl ms_delay ms_startdelay = do let delay = show ms_delay let startdelay = show ms_startdelay addScript $ StaticR longpolling_js - $(widgetFile "longpolling") + $(widgetFile "notifications/longpolling") {- Notifier urls are requested by the javascript, to avoid allocation - of NotificationIds when noscript pages are loaded. This constructs a diff --git a/Assistant/WebApp/SideBar.hs b/Assistant/WebApp/SideBar.hs index 4df0c8d550..2c630324c4 100644 --- a/Assistant/WebApp/SideBar.hs +++ b/Assistant/WebApp/SideBar.hs @@ -34,7 +34,7 @@ sideBarDisplay = do mapM_ renderalert $ take displayAlerts $ reverse $ sortAlertPairs alertpairs let ident = "sidebar" - $(widgetFile "sidebar") + $(widgetFile "sidebar/main") autoUpdate ident NotifierSideBarR (10 :: Int) (10 :: Int) where bootstrapclass Activity = "alert-info" @@ -60,7 +60,7 @@ sideBarDisplay = do addalert i closable block divclass heading widget = do let alertid = show i let closealert = CloseAlert i - $(widgetFile "alert") + $(widgetFile "sidebar/alert") {- Called by client to get a sidebar display. - diff --git a/templates/intro.hamlet b/templates/configurators/intro.hamlet similarity index 100% rename from templates/intro.hamlet rename to templates/configurators/intro.hamlet diff --git a/templates/dashboard.hamlet b/templates/dashboard/main.hamlet similarity index 100% rename from templates/dashboard.hamlet rename to templates/dashboard/main.hamlet diff --git a/templates/metarefresh.hamlet b/templates/dashboard/metarefresh.hamlet similarity index 100% rename from templates/metarefresh.hamlet rename to templates/dashboard/metarefresh.hamlet diff --git a/templates/transfers.hamlet b/templates/dashboard/transfers.hamlet similarity index 100% rename from templates/transfers.hamlet rename to templates/dashboard/transfers.hamlet diff --git a/templates/longpolling.julius b/templates/notifications/longpolling.julius similarity index 100% rename from templates/longpolling.julius rename to templates/notifications/longpolling.julius diff --git a/templates/alert.hamlet b/templates/sidebar/alert.hamlet similarity index 100% rename from templates/alert.hamlet rename to templates/sidebar/alert.hamlet diff --git a/templates/sidebar.hamlet b/templates/sidebar/main.hamlet similarity index 100% rename from templates/sidebar.hamlet rename to templates/sidebar/main.hamlet From 2c8bbdf307899683ea8e2d934ec0ed2bfa3bc3d4 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Tue, 31 Jul 2012 02:30:26 -0400 Subject: [PATCH 200/331] made navbar work also added an About page and a stub Config page. --- Assistant/Threads/WebApp.hs | 1 + Assistant/WebApp.hs | 44 +++++++++++++++++++++------- Assistant/WebApp/Configurators.hs | 7 ++--- Assistant/WebApp/DashBoard.hs | 13 ++++---- Assistant/WebApp/Documentation.hs | 22 ++++++++++++++ Assistant/WebApp/routes | 1 + templates/bootstrap.hamlet | 1 + templates/configurators/main.hamlet | 3 ++ templates/documentation/about.hamlet | 16 ++++++++++ templates/page.hamlet | 8 ++--- 10 files changed, 89 insertions(+), 27 deletions(-) create mode 100644 Assistant/WebApp/Documentation.hs create mode 100644 templates/configurators/main.hamlet create mode 100644 templates/documentation/about.hamlet diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 7b794b6ebf..ca81498f4a 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -16,6 +16,7 @@ import Assistant.WebApp.DashBoard import Assistant.WebApp.SideBar import Assistant.WebApp.Notifications import Assistant.WebApp.Configurators +import Assistant.WebApp.Documentation import Assistant.ThreadedMonad import Assistant.DaemonStatus import Assistant.TransferQueue diff --git a/Assistant/WebApp.hs b/Assistant/WebApp.hs index d3989a68af..fc40ca5bfb 100644 --- a/Assistant/WebApp.hs +++ b/Assistant/WebApp.hs @@ -39,18 +39,40 @@ data WebApp = WebApp , webAppState :: TMVar WebAppState } -instance Yesod WebApp where - defaultLayout content = do - webapp <- getYesod - page <- widgetToPageContent $ do - addStylesheet $ StaticR css_bootstrap_css - addStylesheet $ StaticR css_bootstrap_responsive_css - addScript $ StaticR jquery_full_js - addScript $ StaticR js_bootstrap_dropdown_js - addScript $ StaticR js_bootstrap_modal_js - $(widgetFile "page") - hamletToRepHtml $(hamletFile $ hamletTemplate "bootstrap") +data NavBarItem = DashBoard | Config | About + deriving (Eq) +navBarName :: NavBarItem -> Text +navBarName DashBoard = "Dashboard" +navBarName Config = "Configuration" +navBarName About = "About" + +navBarRoute :: NavBarItem -> Route WebApp +navBarRoute DashBoard = HomeR +navBarRoute Config = ConfigR +navBarRoute About = AboutR + +navBar :: Maybe NavBarItem -> [(Text, Route WebApp, Bool)] +navBar r = map details [DashBoard, Config, About] + where + details i = (navBarName i, navBarRoute i, Just i == r) + +{- Used instead of defaultContent; highlights the current page if it's + - on the navbar. -} +bootstrap :: Maybe NavBarItem -> Widget -> Handler RepHtml +bootstrap navbaritem content = do + webapp <- getYesod + page <- widgetToPageContent $ do + addStylesheet $ StaticR css_bootstrap_css + addStylesheet $ StaticR css_bootstrap_responsive_css + addScript $ StaticR jquery_full_js + addScript $ StaticR js_bootstrap_dropdown_js + addScript $ StaticR js_bootstrap_modal_js + let navbar = navBar navbaritem + $(widgetFile "page") + hamletToRepHtml $(hamletFile $ hamletTemplate "bootstrap") + +instance Yesod WebApp where {- Require an auth token be set when accessing any (non-static route) -} isAuthorized _ _ = checkAuthToken secretToken diff --git a/Assistant/WebApp/Configurators.hs b/Assistant/WebApp/Configurators.hs index e3f0275d9a..47a9b687e6 100644 --- a/Assistant/WebApp/Configurators.hs +++ b/Assistant/WebApp/Configurators.hs @@ -44,13 +44,12 @@ introDisplay ident = do counter = map show ([1..] :: [Int]) getConfigR :: Handler RepHtml -getConfigR = defaultLayout $ do +getConfigR = bootstrap (Just Config) $ do sideBarDisplay setTitle "Configuration" - [whamlet|<a href="@{HomeR}">main|] + $(widgetFile "configurators/main") getAddRepositoryR :: Handler RepHtml -getAddRepositoryR = defaultLayout $ do +getAddRepositoryR = bootstrap (Just Config) $ do sideBarDisplay setTitle "Add repository" - [whamlet|<a href="@{HomeR}">main|] diff --git a/Assistant/WebApp/DashBoard.hs b/Assistant/WebApp/DashBoard.hs index 2961dabd35..f80fb87878 100644 --- a/Assistant/WebApp/DashBoard.hs +++ b/Assistant/WebApp/DashBoard.hs @@ -72,18 +72,17 @@ dashboard warnNoScript = do $(widgetFile "dashboard/main") getHomeR :: Handler RepHtml -getHomeR = defaultLayout $ dashboard True +getHomeR = bootstrap (Just DashBoard) $ dashboard True + +{- Same as HomeR, except no autorefresh at all (and no noscript warning). -} +getNoScriptR :: Handler RepHtml +getNoScriptR = bootstrap (Just DashBoard) $ dashboard False {- Same as HomeR, except with autorefreshing via meta refresh. -} getNoScriptAutoR :: Handler RepHtml -getNoScriptAutoR = defaultLayout $ do +getNoScriptAutoR = bootstrap (Just DashBoard) $ do let ident = NoScriptR let delayseconds = 3 :: Int let this = NoScriptAutoR toWidgetHead $(hamletFile $ hamletTemplate "dashboard/metarefresh") dashboard False - -{- Same as HomeR, except no autorefresh at all (and no noscript warning). -} -getNoScriptR :: Handler RepHtml -getNoScriptR = defaultLayout $ - dashboard False diff --git a/Assistant/WebApp/Documentation.hs b/Assistant/WebApp/Documentation.hs new file mode 100644 index 0000000000..b0a9e4d98c --- /dev/null +++ b/Assistant/WebApp/Documentation.hs @@ -0,0 +1,22 @@ +{- git-annex assistant webapp documentation + - + - Copyright 2012 Joey Hess <joey@kitenet.net> + - + - Licensed under the GNU GPL version 3 or higher. + -} + +{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-} + +module Assistant.WebApp.Documentation where + +import Assistant.WebApp +import Assistant.WebApp.SideBar +import Utility.Yesod + +import Yesod + +getAboutR :: Handler RepHtml +getAboutR = bootstrap (Just About) $ do + sideBarDisplay + setTitle "About git-annex" + $(widgetFile "documentation/about") diff --git a/Assistant/WebApp/routes b/Assistant/WebApp/routes index 75f1ad7c78..5a1550b240 100644 --- a/Assistant/WebApp/routes +++ b/Assistant/WebApp/routes @@ -3,6 +3,7 @@ /noscriptauto NoScriptAutoR GET /config ConfigR GET /addrepository AddRepositoryR GET +/about AboutR GET /transfers/#NotificationId TransfersR GET /sidebar/#NotificationId SideBarR GET diff --git a/templates/bootstrap.hamlet b/templates/bootstrap.hamlet index 13aefd486a..cf686f8433 100644 --- a/templates/bootstrap.hamlet +++ b/templates/bootstrap.hamlet @@ -7,3 +7,4 @@ $doctype 5 ^{pageHead page} <body> ^{pageBody page} + <div #modal></div> diff --git a/templates/configurators/main.hamlet b/templates/configurators/main.hamlet new file mode 100644 index 0000000000..150e08981a --- /dev/null +++ b/templates/configurators/main.hamlet @@ -0,0 +1,3 @@ +<div .span9 .hero-unit> + <h2> + Sorry, no configuration is implemented yet... diff --git a/templates/documentation/about.hamlet b/templates/documentation/about.hamlet new file mode 100644 index 0000000000..6236fb22cf --- /dev/null +++ b/templates/documentation/about.hamlet @@ -0,0 +1,16 @@ +<div .span9 .hero-unit> + <h2> + git-annex watches over your files + <p> + It will automatically notice changes, and keep files in sync between # + repositories and devices. + <p> + For full details, see # + <a href="http://git-annex.branchable.com/">the git-annex website</a>. + <hr> + git-annex is © 2010-2012 Joey Hess. It is free software, licensed # + under the terms of the GNU General Public License, version 3 or above. # + Its development was made possible by # + <a href="http://git-annex.branchable.com/design/assistant/thanks/"> + many excellent people + . diff --git a/templates/page.hamlet b/templates/page.hamlet index 67b19aaf71..d9fee6eafc 100644 --- a/templates/page.hamlet +++ b/templates/page.hamlet @@ -4,10 +4,9 @@ <a .brand href="#"> git-annex <ul .nav> - <li .active> - <a href="#">Dashboard</a> - <li> - <a href="@{ConfigR}">Config</a> + $forall (name, route, isactive) <- navbar + <li :isactive:.active> + <a href="@{route}">#{name}</a> <ul .nav .pull-right> <li .dropdown #menu1> <a .dropdown-toggle data-toggle="dropdown" href="#menu1"> @@ -21,4 +20,3 @@ <div .container-fluid> <div .row-fluid> ^{content} -<div #modal></div> From c77411053b1a4cbe865c1da4db70f1be2cbf5346 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Tue, 31 Jul 2012 02:33:51 -0400 Subject: [PATCH 201/331] remove clickability on brand --- templates/page.hamlet | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/templates/page.hamlet b/templates/page.hamlet index d9fee6eafc..8a2df1e4ba 100644 --- a/templates/page.hamlet +++ b/templates/page.hamlet @@ -1,7 +1,7 @@ <div .navbar .navbar-fixed-top> <div .navbar-inner> <div .container> - <a .brand href="#"> + <a .brand> git-annex <ul .nav> $forall (name, route, isactive) <- navbar From 02b345249b06ec8e03c261a5574401ca8eaa530e Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Tue, 31 Jul 2012 02:35:01 -0400 Subject: [PATCH 202/331] stub --- Assistant/WebApp/Configurators.hs | 1 + templates/configurators/addrepository.hamlet | 3 +++ 2 files changed, 4 insertions(+) create mode 100644 templates/configurators/addrepository.hamlet diff --git a/Assistant/WebApp/Configurators.hs b/Assistant/WebApp/Configurators.hs index 47a9b687e6..0930741e28 100644 --- a/Assistant/WebApp/Configurators.hs +++ b/Assistant/WebApp/Configurators.hs @@ -53,3 +53,4 @@ getAddRepositoryR :: Handler RepHtml getAddRepositoryR = bootstrap (Just Config) $ do sideBarDisplay setTitle "Add repository" + $(widgetFile "configurators/addrepository") diff --git a/templates/configurators/addrepository.hamlet b/templates/configurators/addrepository.hamlet new file mode 100644 index 0000000000..150e08981a --- /dev/null +++ b/templates/configurators/addrepository.hamlet @@ -0,0 +1,3 @@ +<div .span9 .hero-unit> + <h2> + Sorry, no configuration is implemented yet... From f0a88e120367fb68f36e316361c14639c338f8c3 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Tue, 31 Jul 2012 02:36:18 -0400 Subject: [PATCH 203/331] change url --- Assistant/WebApp/routes | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Assistant/WebApp/routes b/Assistant/WebApp/routes index 5a1550b240..69e6078b02 100644 --- a/Assistant/WebApp/routes +++ b/Assistant/WebApp/routes @@ -2,7 +2,7 @@ /noscript NoScriptR GET /noscriptauto NoScriptAutoR GET /config ConfigR GET -/addrepository AddRepositoryR GET +/config/addrepository AddRepositoryR GET /about AboutR GET /transfers/#NotificationId TransfersR GET From e9d9d9d5ea36c9d20913470079db9ea8ac0db994 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Tue, 31 Jul 2012 03:10:16 -0400 Subject: [PATCH 204/331] add icons --- Assistant/Alert.hs | 16 ++++------------ Assistant/WebApp/SideBar.hs | 7 ++++--- static/img/glyphicons-halflings-white.png | Bin 0 -> 4352 bytes static/img/glyphicons-halflings.png | Bin 0 -> 4352 bytes templates/documentation/about.hamlet | 3 ++- templates/sidebar/alert.hamlet | 4 ++++ 6 files changed, 14 insertions(+), 16 deletions(-) create mode 100644 static/img/glyphicons-halflings-white.png create mode 100644 static/img/glyphicons-halflings.png diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs index 9a0bba8ae5..0412dfe519 100644 --- a/Assistant/Alert.hs +++ b/Assistant/Alert.hs @@ -34,6 +34,7 @@ data Alert = Alert , alertBlockDisplay :: Bool , alertClosable :: Bool , alertPriority :: AlertPriority + , alertIcon :: Maybe String } type AlertPair = (AlertId, Alert) @@ -108,26 +109,15 @@ makeAlertFiller success alert | otherwise = alert { alertClass = if c == Activity then c' else c , alertPriority = Filler - , alertHeader = finished <$> h - , alertMessage = massage m , alertClosable = True + , alertIcon = Just $ if success then "ok" else "exclamation-sign" } where - h = alertHeader alert - m = alertMessage alert c = alertClass alert c' | success = Success | otherwise = Error - massage (WidgetAlert w) = WidgetAlert w -- renders old on its own - massage (StringAlert s) = StringAlert $ - maybe (finished s) (const s) h - - finished s - | success = s ++ ": Ok" - | otherwise = s ++ ": Failed" - isFiller :: Alert -> Bool isFiller alert = alertPriority alert == Filler @@ -163,6 +153,7 @@ baseActivityAlert = Alert , alertBlockDisplay = False , alertClosable = False , alertPriority = Medium + , alertIcon = Just "refresh" } activityAlert :: Maybe String -> String -> Alert @@ -220,4 +211,5 @@ sanityCheckFixAlert msg = Alert , alertBlockDisplay = True , alertPriority = High , alertClosable = True + , alertIcon = Just "exclamation-sign" } diff --git a/Assistant/WebApp/SideBar.hs b/Assistant/WebApp/SideBar.hs index 2c630324c4..a4b8378979 100644 --- a/Assistant/WebApp/SideBar.hs +++ b/Assistant/WebApp/SideBar.hs @@ -49,15 +49,16 @@ sideBarDisplay = do (alertBlockDisplay alert) (bootstrapclass $ alertClass alert) (alertHeader alert) + (alertIcon alert) $ case alertMessage alert of StringAlert s -> [whamlet|#{s}|] WidgetAlert w -> w alert rendermessage msg = addalert firstAlertId True False - "alert-info" Nothing [whamlet|#{msg}|] + "alert-info" Nothing (Just "exclamation-sign") [whamlet|#{msg}|] - addalert :: AlertId -> Bool -> Bool -> Text -> Maybe String -> Widget -> Widget - addalert i closable block divclass heading widget = do + addalert :: AlertId -> Bool -> Bool -> Text -> Maybe String -> Maybe String -> Widget -> Widget + addalert i closable block divclass heading icon widget = do let alertid = show i let closealert = CloseAlert i $(widgetFile "sidebar/alert") diff --git a/static/img/glyphicons-halflings-white.png b/static/img/glyphicons-halflings-white.png new file mode 100644 index 0000000000000000000000000000000000000000..a20760bfde58d1c92cee95116059fba03c68d689 GIT binary patch literal 4352 zcmd6r_dnEu|G?izMxtxU%uI5!l8nr<BF?zWUS(u;&WdwZC0F)1B-!J<$%*WB$U3Xi z$ta3LaXK6#>)ZF&&*%FGe4jtO*5mbhJzhV&et11z&&^B?xH$MZ007{+ZK!Jj01(PQ zJBFS4pH$0DefCd1HM@h*JNkcsi%oOXzj>qsEle$eQ7ApHL(XYdn5Y$Lk_3-J9p9d) zFeVfl3J47_g1XaoDXWsnBp9ZzZ74CI9RN-Nw{>+8A&#rBpZgc9WX2H3Ssv6doZP?t zS!g}lGvW1<9%?dj_G_x}3WUMN(8(x{a6_pd0yiUsf^67GGS50uSB*ORe5x6}qAf1z z@Q;2y4G{Lb?f21p)uTpChN&4q%^blZ2IsusUOhk)pe0<chGtjyTP-b6%vl?4F2xqG zOU>yxPD6oHKXWSj<y;3B&r^tK>v8&2pMdnegiQUtoXt1U0MmWAWu2&>3j$eb^qKNV z_(`JQZP&mXLT@U%-2rPy!7r|*Y1oAdlarltaUyq+yq^|d{B9_>t@Rd#@_KW9w_6P$ z^Dv8(Hi8pDJK{r0Iqq*va$cL=isZh0=1)wIoQ^vYPs$<T2#x2Kj^?$few0Pe4I~zZ zeAYbg0c0)2OtIx}d)C`Mw&~<64nQ!Uk8$^SW6e!?j1HfU4$&%i_`y~2R>(rBz$+DY z`y}1}`M%-da686<lVV-dk8h2*Tn8V7;-njKI(p4zUJy$ofY$z#INdRf(>`}zw_w>8 z!BcqxVTim*F)-}$segV$ON*!Zl~dhX@Rz^K2Xu<c1P8u4bp<yQO?OQj^dKZcE}xh_ z<z&gNJz{ZTTu3nGIcR;qG9;?^M0kG|PuThGH1+;j!xXDN6I_*@xL=@r$xRBuVh{MN zIUGEgxYJ(DFHKoLGF3_xPSW_^TT*1w(&gCNFdnv^AMnNFK6+ia>rh<1-vjImult%O z!-WXvkA_agVuhluW};J;#r>)?^uHS;G?a?j;(z?Y^FTwOA?tzLFvQDf&X8}9s7Wh< znEfd_vPyF_V`?>kR`w_h@+%59oKa;NPVGUo52QjisO-|$cYE(VNmm#+`#T5a;gh|Z z8A0^l3UwQMn0J3x<h`4-5?ApmemDp`8K)X6T0efPN*-~cf<tL>XWL7tY~Ox<iRkdJ zU|072zio5s?pAI0%Yx0uJh1f5i7VKWaFIaB;45=yji!1nH9<de2OLj_y{&41?nyPO zUrZT8xW#w*TQ5)($;JeSp2Pgrams&!r<Pe}#(LDg-blL{ESlmQ?a5Th4_;WRJR+4E zw6tQreDz+4bser4GB#?<roQ`hsw<hwcyHa9dkP0IO=6)WWkTxg{$NTm-b*c?j2_ul zyuRy=77P?tF`%S2aa=XEJa>Au=_hGvp@_%SZKA)ec-h-dfwIhS3jGBLL6e6Os;1LR zRDG&3TF`HV*n{&*H!oTSsLq!U5xV5!Yr6I_!*VhmwC3a2BOYfWH13AtVY|n5jv49e zcb0xCCZnt0i$>-S$k9J@-c!8wG#siu(Lg<MtkAtqhD8bV`jR^%b&>y_r1nfy+}!<h zAF+SdUhcuD`9zF%pRIHymB_I~)P%%~M=eQ#Ic#<Zr+NPzGTI`9;4khM^2h2PqMd?5 zGH>W9g-ucwp=&Hs1=Vs4i_q;dQL$8~Uq2BVA4o4uY!6}S`xH(Qec+{mJD~qgg@6W8 zipi@Z!ZR+Kr_)u&G);pG$tg$8#KPrsl&N3(m($NAU&9ogH9rVfW<4Mw>^7$&96g<9 zHQzekG9T5SS7DVm7EFY%CjChhfRyap4+d;+^0ng^B)~xKFG^7d2oOo|R8uY&S|X0@ znAGMb^rFQwGPTzsFQ8ZK4S@WO(8`6T+$Yt9{jGMd?jrTeb|_!Un`n9xDZu-fW+_aJ z4Uyy_$)`Ot!~doWUHW`(?F!iYvc5+g-(W9X<-tX*h%6(f;+A(OQ@w{WYSiq&pjKnN z)tSH~5g)03sKk)U+&GyP*?86fusX1ttpH1ng8ruC6UOddM~t>0wvZh}1cW%&7{tT$ zze(TwkA~V|_~nL{6YE#^RUC__Mx26zo*w(EfK2Q@R6xo`VkJKs^Eax`&*O*bw~*ap zyaqA_p(~(POY{H5+NIgewtB{|(%ML_wR8o);^XGTQ|{*J>74v>{_iyU;U*NTN}A%` z`8ltg(&furYlb!j%1ra!KPSiG<VRTwPDN9f5*7>mJ>f4c!bkAtjb_qmQ+aVB(QohO zRo@%)1krVtMPgkT6&3T*u`XO8pE&-!!u((3qVnraj|gN5aDxvqtrPs*MCZcO3i^Qt zI7$&BFr)50exhv11)82?u`ab0FgUSw;dpbnAtmz4k^&Nx`xMQ$5(JW}ry%)ry+DV> zS)TWjtXz7V6iK5$ghFuPiT>;;fAp)oy%%7grs4UwqU5+Ms96%`wU=YU5W-UGw(6iq z2GhB=Zw49;Yu<#7=soc@tZvYFIVNfkRPsCT&;76cYOONM<!9yYT8XS_j|<f)GAw6X z_w&Wq9xu5;px-$u*_Z^YS22HQpD*L|Z1fb)`d&qCQ^smb{5_5>wv!v*e#(X?l7eB- z&pWvVcaO;IKDg7C8bZ-+Hm`g>n_WC6%BL=CZlc``M{0T;%eYQ4t}V%m20okR=HET) z@)@WU_}tJOqiH7w2K%l<a?3NQ^6bZPnFJ<Mk`|jLP2*o$M^nx2160!F+h^quABnz; zAF6)v=cSvmebPJaPi4k%(nh|zGG@U(va!x`)nhbzOU0MkhuA%7v6ZH!EaE%H>pe0P z^FhhCX$ufUPCq4?C1A8ZSrVz=$~!VZ>;=kb8eaI;S1TKb|E9j*muthJe2||9pYYI$ zR@lkEo?K76^_v{llrL+?Swi1koJYJqG_-g!v?$ITb=q4#Rk--)f<yZAd%OCYe=RDW z4aV9=2rZm-rEPrLKA|1kuMv{%I=`DA(f6L;GQJ=_TAoYWBDl;}XZ0E+YfGjvp>ABD zh4Ibu7+f~5HEzy@7xo<qj_3c_D9C_vmh4{K98*=04-QLt1~2F@dBZe-l2GMsk#;A` zYHOcLf#^)Gn+{G3Q4YowOIK^&zQ|LTx89&c{IWvimdkFT8nJ{0X1}p;P(C>P^f$=} z+D3gYZ3W>%>m=U)p#UNOPPd&2cD&<J9<&QiV~vk5R%jVK^J1%HQ}`fxWs9c=2}L>; zxb{vXTzpCjcJAOEA_~=RX^_BM+_BYW*T{zzM(3TosvFOmf6Kp0IerP4`MuBgFdrkZ zf9X~m0O$toCckMn8klZDxWKr2%FHNk1VLQE)$!{Hz9{*a@TaZjC7kKsC1dIUx*6AQ zJFZc8p~!CewW(VvE@yaTPFt-6n+dZ@TM582m7=-#9JoDOH#zYPe{)-Lza89t+w#Zd zvQ3k$)Q)mPF)g)_+v$Gqgq~*RwGeBn{vhp!IPgkixW8WY)H`S{&~om!keO$Sum=oY zTatGW#*O^aVU<^!#et91z~$IYa;_C@J7+V)`<1b_lh`8FHOAgc=Az}lf)k%5xTMrv zr6uV%eKaU~wvi7pU)MeB7<DU@<PM)Ua&x<*j67UgrpKP|!tXx2R%YzH<LQn0XK>HK z2D;27Dik%)-q@hK-!I|N(cl`lAF^EIv0C-t$d1qtFnKIkcMW<4b%Lzf3Y+~~qB7`< zj);HTQS0Oex%zA170>?kRVA_m_*O?rZRpS3v{+O+cifN7Eb&>$Z==vGKh1V)C`qGu z_u8y<#N3Wp&$V^@T??GnE&RN^IyXM)r0h(gS3;b2pt0O!eNIt4{;3H~V5Ln7vs>8{ ziqqZL4Nwlvj4CtEv0>;Fw~D>LB_+-ecI)tiR%a!^GI3BawvNQGz4#b|_d<K40`zom zmZ%w0mYHcNzK(Ivg#;79zJA3Qs(emYQh|-Y&A>f&`e||2k;K}WnvU!Dx=0#ue(=U# zK&pYNNf5RQZOveUm+;dQ*FIA0&#`?@z*bBhUgr(n9_FpoHPB2pI8iMpW|sF*D{+75 z-k;nba~m^}=b7P$<BGu%3I<`>FAF1)S!oDKtNG-`%h{XQi6=SMH5GZ%8j?ugqt~!K zw<hNaHlewKU9pKh0n@^4X=DQ<4~UnDj4@h3>vA_m(*=EI<IgUo)z0l9R@mb|@QOas zWU>ssFVW0EZ;o=u#R5gBB$CUL+->U32;2PM2O(drij20XBy|hH+=bu!0*KIKBj%c+ z^{)B`3$NB2yp-IHf02C#Fw!(;S&rR%2P<?W3i)a{Hv71$$mqNwIwWJTc5XCVCY(ZM zZEUT%{m1IMAyv+ZxJdeiWsFSau%`*Ji4gu)?i`XAkA6AeCLD>q(!<`Q=u&+_V4eCe z?!d0m@n<F6bnzf#{rI&DDtbzb{#Q?q`iI`Fv^=Q#{GVsrKi@5H!=Yk{`KU+uXc?t@ zxGi_IMbsNpVL63R9MI#c?&2tT**S1&xk6UXV{?VrG2Vb8uwy$l2i~-P)jArRJvd+p zAMPX_jhyzm3a}Qc-9M){f2vD<`B3X9uKLW{DLodF&IsV$kXKT%@Qtp6|3s@S0+S=% zV+#X9n<D=<XzlauBx&tS1|?-doY!<IKSZPJ`vt2XRD)VP6|a+O3xDEZOZR$X3e5-S zuOL@^Te?HwRm63Ch16HfZ|^W=1@ax6$xAQ(4$2J*D69D!1&Ss_Wp=KanXxf%3)jB= zyl{(zRa6B4dz*qTVGFnQ#lf#G^~(Orm6*fvz@t#mixM85R=piy5ZZ)?<t2uZj~#Q1 z%87M&!_4Xmtg&aKmcnz`(+k~CS_9jg?1HcPF4&*jQGA1B5O}@9G995LTJuL|d}-c# zRi6~5UoNF~Ng3*RH>dhMu%QZ`ERBCD+uU~%h<WLJg$(5L-k}}ce*Ymz9%AWcG8~o) zrgMWKP5N71i-Vz&u9fBxjTT}~QT7=y$EdDt>>+E^Qd;Cz=IlGV(IwUrOz(+1Gkd7O z$HME|^+mAGBc4k(2jEj5$g30r-BUoK@Nn!*Td)5USoe+IZ-x9)#yd)sD}2Z?2{4@) zb|)xsK&pqOpB;+H#gbf^Pto29M<2Y>dU5pAF4p{+j=oBZ$2EXA*xI~AM@g20H7o_x z{2-Kc;SRpcxLXzU)a53ZoX%ndB^i8=>Sf&{i6CYkGSkvLj0<@C-!VKm#iX8dws__S zKp`T~rIAfaogJ!tV(~rs5)ctD#A};YXgPNI`<5=nWQjnIf<=1Pzn2y$C8yUkFKhwM z@%Ah?L`DM^@d<2evu->Oo=SVaiR<1GjYwe^G2)XY`l$Q%4H`|PpFA($N_8=6uOr0s zj+)C5x<cICx<i}#5D8LZ3LNFG7uU}%Q5<kbowYRV6Bs|^frDu{l2XM2Lj-Yh_!|?f z+a6@mRKb9j3p<Zh$+a4#UQQYhPF@-a9mWMpS)m;R6VEWV!i;mbS?{`eur*GS8_tX$ jEfLfZC2@~9k9g`Sv9u1yERTOL1mL!wsczLx=g0p8M%V6I literal 0 HcmV?d00001 diff --git a/static/img/glyphicons-halflings.png b/static/img/glyphicons-halflings.png new file mode 100644 index 0000000000000000000000000000000000000000..92d4445dfd0af414835467132cf50c7c38a303af GIT binary patch literal 4352 zcmc(jSvb@I*TDbCl4#mw&6;FnOR{7wTf|sqB70@Y*4Sf=t&%DGGDxy7<4<NH`!>in zwn`&QQOr<`27|~lU*GNfe)r$+;%v`3=Q$VW;ymZMrG+ssw-7e~0K7L%46Ffwh5XNs z<6`?KHS^P-{ZmgZZ@~?jOs2~JH%~nY@PG5j1zTI#0Amn(L8qe2oETm=+B^jogFL!D zS!ISRHW3ybWQ6o&?2=byQi)JhfBSH9PzL~<0B#!S!^50cUq25lRnLyYPq06zWw>~J z`$KJG?wJet%MCZ1y81U)c?UzG;{mBi?no2aAHvt8L__Xy66K$DAupSD_4^VSeG;vA zGhrY7dmCA}Zg<=d*dvUYvYMo40k!iu>o|-n)q^ld6Q(6yBtUWr1GY<4vK2?uoeS|r zT(a}}&NC3;#Lv8{0Y$f=#j|95fZYUrx?foCUQ)KvUf$-LSb+6D%%)z#|1KO+ZTgw~ zNbE_n|4p~xYoc$edOQF-XOS;%<r!#dmHF{5#RTzN2!T(FFMc;x+SmC=Km>evzdNi3 zk@(r9h#R5FpacG)j3VDRRz>g49u-o5A=@X`M=nQQ@W&MqFu3+}8)vIJ<N(sT_Zk8X zMLcU+@C0(GanqcI+g=S0kMDE|mIlGu&c=CozOm!OJr0PRi4D`Obo#+t^;Xncwa7ai zdh<9v@cF*U;YbI{iHB@gJAiGAx>yezf?(vDF#3iq72Yg1rU0$uCw``L1fzH6tU=MT zJ)FP#7~BMLoosB<>)Y`BnyxN?%PW`qwa_nrmk;P<^+|3lA$<ii8%uY~81lp=vs^qj zbHc@jPjA%v+=Qq|+H=tEesx$(-?7Mn9R7&2+ZkE|b0%rF{pOe&2PywxrLyZ}ob?{? zS!X14D0!!&R7j4z&a_ZX7E96o-d9#)-rDWl);JNdUKsSn^M1g(Sofin)_^D2A6fsk zK%N&KDHIEtjz^2e+RnzNElc?mvW&i)!L?OOITL^U!tz7HAYtpl+few+Se~$Nk0>cC z!KnRdI-*8rENgl-h*t3^hviocbR?_BCX&(%?-)#H*`RRAUES@w^(0ey@bvFIq^EE0 zYIYPpa4Xz>{9(cUIq~=IuByDHtJskc@OXkoyhOvqjT$BRxhihe#hq<$(TaV?g(bYx zzk*$b_y4xdrKd-u!#@W)7x%!%FE62JOZu)fTpnAUKW94KXQKo9lR9BoI`nN#BV<pu zN$Y&tINUw4JJ60wNhX=$oO%xnS0~8-36@e}lO69__j)7adZ<L2U#u5vwGeo2shUYF zH*Rf1efjD`jdvTV8a6X+&!xQkbfP<z!gz1jlz##Puuh>NL^WLc-2PBnDb`!FkQ6Yw zt8#VMCqN`vOx>8A-pqa3!sg7$vF4w|C29%3h5O_{d+D-|gED!U;S&A}5QU_Uz%?vp zmMBIPvj7qQQG74PJJYIU8KAgcJcJvNO0O6=%8w|@chXvpUX6O34cERMj)m?X)jwit zWYksusgx8zcrOv1Kd4Cm%yUoW#?wfM-ee=?*pXt7dU<wL(ECgNtn7KAcQSgjF$wec z&wNDxS$nw$r4-^(dj0lt)f7DU5?+TTQ7UFh7R=*xI5;Wr=aA7JB?^0SzgQ^V;4r`? zBrN-yp=!hwMFq0PE?Y!UWLSr9S4c>vyZrhI*Zx3!VQzm2&D<yRh#LVfjXeOPcj~wR z5UG;7Ix04MSLbA=`nZloXfY{`*@7=#K0}`VWppv~RO%H}$!V*DNHvZFBHUqfI?CD0 zbx!B4^9`#pqXl&iB{Pv^*lNn33}KeCeaE4o?M=ZBEL9o|=KG==a{vbsI4@1LO3@|! z=#F_^eo|k6WLCD`I?D^lB}ZeRa3j2$+MNG{fZN~d@a`$my6AxPBfp8Irx1gDj_8y_ zB{|_Ko-%@Zv$H~Px&z9e&#zqq`(8HmN?{uv#cDixDOJ%G_;k$j?o_(Za8|9R0~pd~ zhP6EvoFeWkI{=X$R-d0BaUhyb8w0in4s%stxoODXOl;El?W^#yR`?d86Ax#>k2i(z zv;J?=_W|Z`2Nb*9*m`XJ^1ixr>GY^eNXXM8UzHKbJ%`E&g=n<QM>C-&t%U{b2>k}4 zM^eC8z9@VJ)NO6~zgW94x7psn_*GsP&AXPV>|c7+3V*`GDl?NuNHOr8_5jSBY+FrJ zxxFy&omakmacj-wPLUexLeI~s2^i^7j<QS1^o69wqChX$OY6u{tW}exT*h=kf_UuP z+XaMs<6dAuy-kT^H%eXIYHYk4Q!FTjJ*&L%*Q})SYV#u;NgCV`gwN=QJ~!7t_q2+B zpbd_ZMR9D%dyk)}nec)ZXV~q^?S+kxZJj&X5@|w?zO<x_02M#Q3a*5JM8Y&n;d~#^ zX?>diy$lDh;U-ze^bf8Wq&_j48xx9sRj~I0?AI|l`&NRKa0xj_M7{QQP8x>W$llZ# z^2}mA)Bep^+iA@Qw-LK1wT3nbnW#j??18HOX9M~EwO_4MW54*U(nB|yBja(g7FnMC zblZNR)Y{`EcNWNZ9&#=!$@W#;-?`_@7{fb;%BTG<Be%)pb!CB`M;1FsO>aNt!jg%h zP{`+<{G!`T5|=OLq>Z*{Z2O&8zMn16ACVB$Qm``DYk?tjJdb2uC7aci<-`J?E%OU+ zGrN5UtA#%|w#4Z;NP?k$>n!<|SrjF%qnK<QD=|fvQ-`MgFRin=cJ~1?W$Nv-%7>36 z-X#tb9{hRfZswTsPVZBN8H~75sHKLYIz~6u+pKzy#crwlQTpM#$E~+Abk)TD#sz#v zXX8Go`ZaF>B8Zu%M9U<U?k5{O<y&QE7KlDa9?QUr-S}#I$LYUm81UoWaH<><;>RXE zbfFb@39Y9#&~E%DMKl*GIPjFwcNZ7nuMbVEpA0WbvBjM9QA!sp{YiDoe131&NawG0 z)w7{^`zTTBX*b%&r|n~U@dMgnxo!))g;D+Qg=`Xw5@VHk^{hiH?Dbc#u;gsXHzn0i z2)8o6*&Kl>6tpGG-xYv<M}QNBKQ@Z8AUtKe=QqbSl$Amw(w@PJ2Fl*B4kD#B1X|@h zND6v-C(>B-r`9coW<<#c<0|E=wQpY(XerrkkfVOt!t*N?wvbI|9F@&~JQ7q2jXe2H zCW^MvkWX8I-=%fo@BdI{A^py@pAB`s<yjfB3(la;jxJW|8b9;qtmahyAaiMpzZU^P zxD>hd&A{*amKE*X!a7A2Yu?Z%f;af$36@t#hgGI$UAqZQr>(vfUM3&C0L=d07kpTV z65hXXqa6SYLUvQ%beIm#w8HN~d3!4?$?iB2Owr|ut8l>>rMSqaZB}JGncrpN>H)eX z?`{XC$$(nou>9J>y&RJ_GCHrPS%%Jr+GeZ-p;^lV`1YLmyxKN-u#7+}dnx}N%zgXH z$CV1rQyi4eN)t(4&9Ix9{_jMeW*4;LYis@>9EQ2Es^gfy-VKyn0lc8i{7q3yuQV}F zD6Fom;2?qz@ukzYpge~g8?BAWbC}{;E82F=WrGc<q3x&8B^qmty_aky%YQ{CKTGq< zYP!kE(69SylMU^oAELgld(|`QSIDWIzU`!z4rh5Kn4EmCqu{yU{SIwx=mqDK8w<~1 zUPFy^`6*;La<HSR(O`c-+NrbAEnz=wxz=;F=D$%Gr5~UQ*wG%^^eW0ENv91u_qR-a z$S)u&@oi_Fi#yBZUxTms_h&AvlAOS|`l_14f97W-V>0;?er)DQ&9VG84bSn{>9B(k zwM%!e%*jQ~?@0DuS;yYC#^~O_E+}d7VN;GP%ockmCFlj4DNZ%yl_X-Hn$v_=+Er1z z)xF^ugN@xFweaki3bVXB3?uwjsn55R<b|OgeId~Hv@}>D1&YMi6B+jBAEU6|0Y1ne zLxbyOnkM9BHX2f}bHa<7WG>P_pz=aP(B)D(uo1i&yvId9DaA3GTsK?WdG%g5Q5z-% zUfT;wH`Xu@LDvM>F<4<`LiFUdk7UO)oS&1>Rnv!81;V#S1gZ^;byAIw5fmjY3m)nw z?+@SmlmBCWV>bFM8|-jGB{WLeI3o9DaWo<)11@8`kh*v=cN0DNB+st4sz6R#2I0qi z4c&8ZcAexDoiEyzoZJ((D9)8bG%^Z+MCs@_Q)++#Uvn&7#CI<7^ioFM{2qLTEAfMX z#1kD>oACS6EsTK8F}{R&pahvhyt|}$lX5-EzVP=!*jL*U(=7^7%UUF#`g>m(9)4uh zN+-O*&B&PgYQ520)x+!;$#)PXM`Kgq-o1CQLPsDGuSVi?k7|gIEtmv^WewHMkLAio zl1Us*ZM8T5*j_cED4OCIiNDZ{(dj&{3{g&T+~4Y*L((GimlI~v8Q&*2;zNurHxdEX zDgWY5T-u#~Rw6AH53<&eUOA_3sJa+<`S@61`0Z+&gPPC(dA9xY-3vCHs+QQ8y<*H| zq`~2~B6ACGIIhlq0<JP>$V=$vE_&HDcwxCpLD6$_1>ZT*h{SQByL1NMw0+fOj?Wz& zFvJdbQkbJBeJ=wX#hUle7%rUXR$4yPWhM|#t(`DrC+d#^K8*!sRn%{Eee5S%bqSan z?Gaxb6y6;Dw^4Ura3@7~UnV3ahsAZxfc!%uwqZbo@PGj7@>ji1sVn}8fiB(aiz~Jo zTDXK*@oVh~gVo^Iu~o8PQNMj6)RalL?o3^H@pnjZNLWoX&@@;gDJHvX&C-&SZCkAF z?Pux@B3eZQ037cWb&FZMuP+XLz1yG`s8)?SoCs!ygWlxG$PB`Eka2i37Fv)TK{|58 zJti;S=?xo)8?eTei(HD#<H{`dIBo}QZ*qye7Ch&8W=G`>f`Jq8j>vX~5NRzRU9sf_ z>oxtdr~$>ax+OJ;^X)vsSztp0JYJsoQlX{)JP`NN^%4mv6u3oW-hBTdM2W@5-Fze> z9n9nd!<vn@x)+DSqur{lShQR5c_q20z&z9X_VI@tF-sZITiJ8(=%yDq%20jBZq4o? zgCC2nZ#R@cyO{hJ?i_$meOX?m;pkq%(#414r`r1hpFn%A^?fTAk~P~=C0`Omj7x)= z_=sB}!Gp5B>;qg7R6d&M#&&}CPAvA|mF^4XPltG`XZl9!t)5o^flxcEGJRDAZjOjF zQ0Iea%DG$E3bP&!(93|2RCY3l5t3s3J*JOik0=hGeaJ@3@H8tD7<k9<<dKwp&eQ6Z z9|U0$hb)b5lItCim6MC_Nf&^qL{S0zjAEPdi{G~l$mUBpQVcZOtKq$za5*WnwuQO{ zxF$NXUlSh-TEr%CuFbjgKX@wV^CqEZM<ObXOWagY0q?8j*FR)BnR)!IQXA#2X-7RS zQDDqU9@ib_?%osL+z(HZl~m@gbUVL(W{K>CVRqHg&`+R3j0a8@kqB}PI}{$m!yRab zvul5lL(>3*TF>n~)*#hsmwUTtKRAA2Fnk0PENdI!9GrZLu@zyKzs+&m-IKFviqv>& kg1Lm#gqI~e;$iYPkmG5c&N-g{UI@TVLkokN>#mRg2V?7pi2wiq literal 0 HcmV?d00001 diff --git a/templates/documentation/about.hamlet b/templates/documentation/about.hamlet index 6236fb22cf..af48a0b102 100644 --- a/templates/documentation/about.hamlet +++ b/templates/documentation/about.hamlet @@ -10,7 +10,8 @@ <hr> git-annex is © 2010-2012 Joey Hess. It is free software, licensed # under the terms of the GNU General Public License, version 3 or above. # - Its development was made possible by # + <br> + <i class="icon-heart"></i> Its development was made possible by # <a href="http://git-annex.branchable.com/design/assistant/thanks/"> many excellent people . diff --git a/templates/sidebar/alert.hamlet b/templates/sidebar/alert.hamlet index 8fa77eac1d..84126c3810 100644 --- a/templates/sidebar/alert.hamlet +++ b/templates/sidebar/alert.hamlet @@ -1,6 +1,10 @@ <div .alert .fade .in .#{divclass} :block:.alert-block ##{alertid} :closable:onclick="(function( $ ) { $.get('@{closealert}') })( jQuery );"> $if closable <a .close data-dismiss="alert">×</a> + $case icon + $of Nothing + $of Just name + <i class="icon-#{name}"></i> # $maybe h <- heading $if block <h4 class="alert-heading">#{h}</h4> From b9b009787662cda4948b3c9706b8897587d05d8a Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Tue, 31 Jul 2012 11:19:40 -0400 Subject: [PATCH 205/331] tweak types so the webapp can run without a threadstate when outside an annex --- Assistant/Threads/WebApp.hs | 2 +- Assistant/WebApp.hs | 12 +++++++++++- Assistant/WebApp/Configurators.hs | 3 +-- Assistant/WebApp/DashBoard.hs | 3 +-- 4 files changed, 14 insertions(+), 6 deletions(-) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index ca81498f4a..9cdbae451c 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -59,7 +59,7 @@ webAppThread st dstatus transferqueue onstartup = do token <- genRandomToken s <- newWebAppState return $ WebApp - { threadState = st + { threadState = Just st , daemonStatus = dstatus , transferQueue = transferqueue , secretToken = pack token diff --git a/Assistant/WebApp.hs b/Assistant/WebApp.hs index fc40ca5bfb..f7fb7bb6ef 100644 --- a/Assistant/WebApp.hs +++ b/Assistant/WebApp.hs @@ -30,7 +30,7 @@ staticFiles "static" mkYesodData "WebApp" $(parseRoutesFile "Assistant/WebApp/routes") data WebApp = WebApp - { threadState :: ThreadState + { threadState :: Maybe ThreadState , daemonStatus :: DaemonStatusHandle , transferQueue :: TransferQueue , secretToken :: Text @@ -104,6 +104,16 @@ modifyWebAppState a = go =<< webAppState <$> getYesod v <- takeTMVar s putTMVar s $ a v +{- Runs an Annex action from the webapp. + - + - When the webapp is run outside a git-annex repository, the fallback + - value is returned. + -} +runAnnex :: forall sub a. a -> Annex a -> GHandler sub WebApp a +runAnnex fallback a = maybe (return fallback) go =<< threadState <$> getYesod + where + go st = liftIO $ runThreadState st a + waitNotifier :: forall sub. (DaemonStatus -> NotificationBroadcaster) -> NotificationId -> GHandler sub WebApp () waitNotifier selector nid = do notifier <- getNotifier selector diff --git a/Assistant/WebApp/Configurators.hs b/Assistant/WebApp/Configurators.hs index 0930741e28..ee3209ce25 100644 --- a/Assistant/WebApp/Configurators.hs +++ b/Assistant/WebApp/Configurators.hs @@ -12,7 +12,6 @@ module Assistant.WebApp.Configurators where import Assistant.Common import Assistant.WebApp import Assistant.WebApp.SideBar -import Assistant.ThreadedMonad import Utility.Yesod import qualified Remote import Logs.Web (webUUID) @@ -27,7 +26,7 @@ introDisplay :: Text -> Widget introDisplay ident = do webapp <- lift getYesod let reldir = relDir webapp - l <- liftIO $ runThreadState (threadState webapp) $ do + l <- lift $ runAnnex [] $ do u <- getUUID rs <- map Remote.uuid <$> Remote.remoteList rs' <- snd <$> trustPartition DeadTrusted rs diff --git a/Assistant/WebApp/DashBoard.hs b/Assistant/WebApp/DashBoard.hs index f80fb87878..9a9fccdaa4 100644 --- a/Assistant/WebApp/DashBoard.hs +++ b/Assistant/WebApp/DashBoard.hs @@ -14,7 +14,6 @@ import Assistant.WebApp import Assistant.WebApp.SideBar import Assistant.WebApp.Notifications import Assistant.WebApp.Configurators -import Assistant.ThreadedMonad import Assistant.DaemonStatus import Assistant.TransferQueue import Utility.NotificationBroadcaster @@ -35,7 +34,7 @@ import qualified Data.Map as M transfersDisplay :: Bool -> Widget transfersDisplay warnNoScript = do webapp <- lift getYesod - current <- liftIO $ runThreadState (threadState webapp) $ + current <- lift $ runAnnex [] $ M.toList . currentTransfers <$> liftIO (getDaemonStatus $ daemonStatus webapp) queued <- liftIO $ getTransferQueue $ transferQueue webapp From 04794eafc0f0fd09e645247136fe557fd80bfb55 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Tue, 31 Jul 2012 12:17:31 -0400 Subject: [PATCH 206/331] webapp now starts up when run not in a git repo --- Assistant.hs | 4 +- Assistant/Threads/WebApp.hs | 55 ++++++++++++++-------------- Assistant/WebApp.hs | 2 +- Assistant/WebApp/Configurators.hs | 1 - Command/WebApp.hs | 31 ++++++++++++---- templates/bootstrap.hamlet | 6 ++- templates/configurators/intro.hamlet | 51 +++++++++++++------------- templates/page.hamlet | 21 ++++++----- 8 files changed, 96 insertions(+), 75 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index 22a87fe8cc..4bb85975b8 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -122,7 +122,7 @@ import Utility.ThreadScheduler import Control.Concurrent -startDaemon :: Bool -> Bool -> Maybe (IO ()) -> Annex () +startDaemon :: Bool -> Bool -> Maybe (FilePath -> IO ()) -> Annex () startDaemon assistant foreground webappwaiter | foreground = do showStart (if assistant then "assistant" else "watch") "." @@ -155,7 +155,7 @@ startDaemon assistant foreground webappwaiter , mountWatcherThread st dstatus scanremotes , transferScannerThread st dstatus scanremotes transferqueue #ifdef WITH_WEBAPP - , webAppThread st dstatus transferqueue webappwaiter + , webAppThread (Just st) dstatus transferqueue webappwaiter #endif , watchThread st dstatus transferqueue changechan ] diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index 9cdbae451c..ad2bff8923 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -1,4 +1,4 @@ -{- git-annex assistant webapp +{- git-annex assistant webapp thread - - Copyright 2012 Joey Hess <joey@kitenet.net> - @@ -38,47 +38,46 @@ thisThread = "WebApp" mkYesodDispatch "WebApp" $(parseRoutesFile "Assistant/WebApp/routes") -webAppThread :: ThreadState -> DaemonStatusHandle -> TransferQueue -> Maybe (IO ()) -> IO () -webAppThread st dstatus transferqueue onstartup = do - webapp <- mkWebApp +webAppThread :: (Maybe ThreadState) -> DaemonStatusHandle -> TransferQueue -> Maybe (FilePath -> IO ()) -> IO () +webAppThread mst dstatus transferqueue onstartup = do + webapp <- WebApp + <$> pure mst + <*> pure dstatus + <*> pure transferqueue + <*> (pack <$> genRandomToken) + <*> getreldir mst + <*> pure $(embed "static") + <*> newWebAppState app <- toWaiAppPlain webapp app' <- ifM debugEnabled ( return $ httpDebugLogger app , return app ) - runWebApp app' $ \port -> do - runThreadState st $ writeHtmlShim webapp port - maybe noop id onstartup + runWebApp app' $ \port -> case mst of + Nothing -> withTempFile "webapp.html" $ \tmpfile _ -> go port webapp tmpfile + Just st -> go port webapp =<< runThreadState st (fromRepo gitAnnexHtmlShim) where - mkWebApp = do + getreldir Nothing = return Nothing + getreldir (Just st) = do dir <- absPath =<< runThreadState st (fromRepo repoPath) home <- myHomeDir - let reldir = if dirContains home dir + return $ Just $ if dirContains home dir then relPathDirToFile home dir else dir - token <- genRandomToken - s <- newWebAppState - return $ WebApp - { threadState = Just st - , daemonStatus = dstatus - , transferQueue = transferqueue - , secretToken = pack token - , relDir = reldir - , getStatic = $(embed "static") - , webAppState = s - } + go port webapp htmlshim = do + writeHtmlShim webapp port htmlshim + maybe noop (\a -> a htmlshim) onstartup {- Creates a html shim file that's used to redirect into the webapp, - to avoid exposing the secretToken when launching the web browser. -} -writeHtmlShim :: WebApp -> PortNumber -> Annex () -writeHtmlShim webapp port = do - liftIO $ debug thisThread ["running on port", show port] - htmlshim <- fromRepo gitAnnexHtmlShim - liftIO $ viaTmp go htmlshim $ genHtmlShim webapp port +writeHtmlShim :: WebApp -> PortNumber -> FilePath -> IO () +writeHtmlShim webapp port file = do + debug thisThread ["running on port", show port] + viaTmp go file $ genHtmlShim webapp port where - go file content = do - h <- openFile file WriteMode - modifyFileMode file $ removeModes [groupReadMode, otherReadMode] + go tmpfile content = do + h <- openFile tmpfile WriteMode + modifyFileMode tmpfile $ removeModes [groupReadMode, otherReadMode] hPutStr h content hClose h diff --git a/Assistant/WebApp.hs b/Assistant/WebApp.hs index f7fb7bb6ef..2a1fcb6b42 100644 --- a/Assistant/WebApp.hs +++ b/Assistant/WebApp.hs @@ -34,7 +34,7 @@ data WebApp = WebApp , daemonStatus :: DaemonStatusHandle , transferQueue :: TransferQueue , secretToken :: Text - , relDir :: FilePath + , relDir :: Maybe FilePath , getStatic :: Static , webAppState :: TMVar WebAppState } diff --git a/Assistant/WebApp/Configurators.hs b/Assistant/WebApp/Configurators.hs index ee3209ce25..66d92ebc04 100644 --- a/Assistant/WebApp/Configurators.hs +++ b/Assistant/WebApp/Configurators.hs @@ -25,7 +25,6 @@ import Data.Text (Text) introDisplay :: Text -> Widget introDisplay ident = do webapp <- lift getYesod - let reldir = relDir webapp l <- lift $ runAnnex [] $ do u <- getUUID rs <- map Remote.uuid <$> Remote.remoteList diff --git a/Command/WebApp.hs b/Command/WebApp.hs index ee1274f97d..6755763b32 100644 --- a/Command/WebApp.hs +++ b/Command/WebApp.hs @@ -10,12 +10,19 @@ module Command.WebApp where import Common.Annex import Command import Assistant +import Assistant.DaemonStatus +import Assistant.TransferQueue +import Assistant.Threads.WebApp import Utility.WebApp +import Utility.ThreadScheduler import Utility.Daemon (checkDaemon) import qualified Command.Watch +import Control.Concurrent.STM + def :: [Command] -def = [withOptions [Command.Watch.foregroundOption, Command.Watch.stopOption] $ +def = [oneShot $ noRepo firstRun $ dontCheck repoExists $ + withOptions [Command.Watch.foregroundOption, Command.Watch.stopOption] $ command "webapp" paramNothing seek "launch webapp"] seek :: [CommandSeek] @@ -30,8 +37,8 @@ start foreground stopdaemon = notBareRepo $ do else do f <- liftIO . absPath =<< fromRepo gitAnnexHtmlShim ifM (checkpid <&&> checkshim f) $ - ( liftIO $ go f - , startDaemon True foreground $ Just $ go f + ( liftIO $ openBrowser f + , startDaemon True foreground $ Just openBrowser ) stop where @@ -39,7 +46,17 @@ start foreground stopdaemon = notBareRepo $ do pidfile <- fromRepo gitAnnexPidFile liftIO $ isJust <$> checkDaemon pidfile checkshim f = liftIO $ doesFileExist f - go f = unlessM (runBrowser url) $ - error $ "failed to start web browser on url " ++ url - where - url = "file://" ++ f + +openBrowser :: FilePath -> IO () +openBrowser htmlshim = unlessM (runBrowser url) $ + error $ "failed to start web browser on url " ++ url + where + url = "file://" ++ htmlshim + +firstRun :: IO () +firstRun = do + dstatus <- atomically . newTMVar =<< newDaemonStatus + transferqueue <- newTransferQueue + webAppThread Nothing dstatus transferqueue $ Just $ \f -> do + openBrowser f + waitForTermination diff --git a/templates/bootstrap.hamlet b/templates/bootstrap.hamlet index cf686f8433..f743a0d463 100644 --- a/templates/bootstrap.hamlet +++ b/templates/bootstrap.hamlet @@ -1,7 +1,11 @@ $doctype 5 <html> <head> - <title>#{relDir webapp} #{pageTitle page} + <title> + $maybe reldir <- relDir webapp + #{reldir} #{pageTitle page} + $nothing + #{pageTitle page} <link rel="icon" href=@{StaticR favicon_ico} type="image/x-icon"> <meta name="viewport" content="width=device-width,initial-scale=1.0"> ^{pageHead page} diff --git a/templates/configurators/intro.hamlet b/templates/configurators/intro.hamlet index ecb15f39cc..5062346a85 100644 --- a/templates/configurators/intro.hamlet +++ b/templates/configurators/intro.hamlet @@ -1,27 +1,28 @@ <div .span9 ##{ident} .hero-unit> - <h2> - git-annex is watching over your files in <small><tt>#{reldir}</tt></small> - <p> - It will automatically notice changes, and keep files in sync between # - $if notenough - repositories on your devices ... - <h2> - But no other repositories are set up yet. - <a .btn .btn-primary .btn-large href="@{AddRepositoryR}">Add another repository</a> - $else - $if barelyenough - <span .badge .badge-warning>#{numrepos}</span> + $maybe reldir <- relDir webapp + <h2> + git-annex is watching over your files in <small><tt>#{reldir}</tt></small> + <p> + It will automatically notice changes, and keep files in sync between # + $if notenough + repositories on your devices ... + <h2> + But no other repositories are set up yet. + <a .btn .btn-primary .btn-large href="@{AddRepositoryR}">Add another repository</a> $else - <span .badge .badge-success>#{numrepos}</span> - \ repositories and devices: - <table .table .table-striped .table-condensed> - <tbody> - $forall (num, name) <- remotelist - <tr> - <td> - #{num} - <td> - #{name} - <a .btn .btn-primary .btn-large href="@{AddRepositoryR}">Add another repository</a> - <p> - Or just sit back, watch the magic, and get on with using your files. + $if barelyenough + <span .badge .badge-warning>#{numrepos}</span> + $else + <span .badge .badge-success>#{numrepos}</span> + \ repositories and devices: + <table .table .table-striped .table-condensed> + <tbody> + $forall (num, name) <- remotelist + <tr> + <td> + #{num} + <td> + #{name} + <a .btn .btn-primary .btn-large href="@{AddRepositoryR}">Add another repository</a> + <p> + Or just sit back, watch the magic, and get on with using your files. diff --git a/templates/page.hamlet b/templates/page.hamlet index 8a2df1e4ba..29a091110a 100644 --- a/templates/page.hamlet +++ b/templates/page.hamlet @@ -7,16 +7,17 @@ $forall (name, route, isactive) <- navbar <li :isactive:.active> <a href="@{route}">#{name}</a> - <ul .nav .pull-right> - <li .dropdown #menu1> - <a .dropdown-toggle data-toggle="dropdown" href="#menu1"> - Current Repository: #{relDir webapp} - <b .caret></b> - <ul .dropdown-menu> - <li><a href="#">#{relDir webapp}</a></li> - <li .divider></li> - <li><a href="@{AddRepositoryR}">Add another repository</a></li> - + $maybe reldir <- relDir webapp + <ul .nav .pull-right> + <li .dropdown #menu1> + <a .dropdown-toggle data-toggle="dropdown" href="#menu1"> + Current Repository: #{reldir} + <b .caret></b> + <ul .dropdown-menu> + <li><a href="#">#{reldir}</a></li> + <li .divider></li> + <li><a href="@{AddRepositoryR}">Add another repository</a></li> + $nothing <div .container-fluid> <div .row-fluid> ^{content} From 1efb0d109ee425b53b76e92ee69c5ec7bf6cf979 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Tue, 31 Jul 2012 12:20:31 -0400 Subject: [PATCH 207/331] don't start webapp when in a git repo that has not been git-annex initted Maybe later it can prompt if they want to use the repo with git-annex, but for now this is a sane easy choice. --- Command/WebApp.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Command/WebApp.hs b/Command/WebApp.hs index 6755763b32..a3294911f9 100644 --- a/Command/WebApp.hs +++ b/Command/WebApp.hs @@ -21,7 +21,7 @@ import qualified Command.Watch import Control.Concurrent.STM def :: [Command] -def = [oneShot $ noRepo firstRun $ dontCheck repoExists $ +def = [oneShot $ noRepo firstRun $ withOptions [Command.Watch.foregroundOption, Command.Watch.stopOption] $ command "webapp" paramNothing seek "launch webapp"] From 0d3686972d9b08b061f86b3e38fb681becf1c833 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Tue, 31 Jul 2012 12:33:52 -0400 Subject: [PATCH 208/331] form --- templates/configurators/intro.hamlet | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/templates/configurators/intro.hamlet b/templates/configurators/intro.hamlet index 5062346a85..be451a91fe 100644 --- a/templates/configurators/intro.hamlet +++ b/templates/configurators/intro.hamlet @@ -26,3 +26,12 @@ <a .btn .btn-primary .btn-large href="@{AddRepositoryR}">Add another repository</a> <p> Or just sit back, watch the magic, and get on with using your files. + $nothing + <h2> + Creating a git-annex repository + <p> + Files in this repository will managed by git-annex, # + and kept in sync with your repositories on other devices. + <form .form-inline> + <input type="text" .input-xlarge placeholder="directory"> # + <button type="submit" .btn .btn-primary .btn-large>Make Repository</button> From c70496dc7f89f07e05bea0257b7d93986dd61d89 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Tue, 31 Jul 2012 14:23:17 -0400 Subject: [PATCH 209/331] improve first run screen --- Assistant/WebApp.hs | 19 ++++++++++++++----- Assistant/WebApp/Configurators.hs | 16 ++++++++++++---- Assistant/WebApp/DashBoard.hs | 7 +++++-- templates/configurators/addrepository.hamlet | 17 +++++++++++++++-- templates/configurators/intro.hamlet | 9 --------- 5 files changed, 46 insertions(+), 22 deletions(-) diff --git a/Assistant/WebApp.hs b/Assistant/WebApp.hs index 2a1fcb6b42..3351aa48fe 100644 --- a/Assistant/WebApp.hs +++ b/Assistant/WebApp.hs @@ -52,25 +52,34 @@ navBarRoute DashBoard = HomeR navBarRoute Config = ConfigR navBarRoute About = AboutR -navBar :: Maybe NavBarItem -> [(Text, Route WebApp, Bool)] -navBar r = map details [DashBoard, Config, About] - where - details i = (navBarName i, navBarRoute i, Just i == r) +defaultNavBar :: [NavBarItem] +defaultNavBar = [DashBoard, Config, About] + +firstRunNavBar :: [NavBarItem] +firstRunNavBar = [Config, About] + +selectNavBar :: Handler [NavBarItem] +selectNavBar = ifM (inFirstRun) (return firstRunNavBar, return defaultNavBar) + +inFirstRun :: Handler Bool +inFirstRun = isNothing . threadState <$> getYesod {- Used instead of defaultContent; highlights the current page if it's - on the navbar. -} bootstrap :: Maybe NavBarItem -> Widget -> Handler RepHtml bootstrap navbaritem content = do webapp <- getYesod + navbar <- map navdetails <$> selectNavBar page <- widgetToPageContent $ do addStylesheet $ StaticR css_bootstrap_css addStylesheet $ StaticR css_bootstrap_responsive_css addScript $ StaticR jquery_full_js addScript $ StaticR js_bootstrap_dropdown_js addScript $ StaticR js_bootstrap_modal_js - let navbar = navBar navbaritem $(widgetFile "page") hamletToRepHtml $(hamletFile $ hamletTemplate "bootstrap") + where + navdetails i = (navBarName i, navBarRoute i, Just i == navbaritem) instance Yesod WebApp where {- Require an auth token be set when accessing any (non-static route) -} diff --git a/Assistant/WebApp/Configurators.hs b/Assistant/WebApp/Configurators.hs index 66d92ebc04..9fe10aff92 100644 --- a/Assistant/WebApp/Configurators.hs +++ b/Assistant/WebApp/Configurators.hs @@ -41,14 +41,22 @@ introDisplay ident = do where counter = map show ([1..] :: [Int]) +addRepository :: Bool -> Widget +addRepository firstrun = do + setTitle $ if firstrun then "Getting started" else "Add repository" + $(widgetFile "configurators/addrepository") + getConfigR :: Handler RepHtml getConfigR = bootstrap (Just Config) $ do sideBarDisplay - setTitle "Configuration" - $(widgetFile "configurators/main") + ifM (lift inFirstRun) + ( addRepository True + , do + setTitle "Configuration" + $(widgetFile "configurators/main") + ) getAddRepositoryR :: Handler RepHtml getAddRepositoryR = bootstrap (Just Config) $ do sideBarDisplay - setTitle "Add repository" - $(widgetFile "configurators/addrepository") + addRepository False diff --git a/Assistant/WebApp/DashBoard.hs b/Assistant/WebApp/DashBoard.hs index 9a9fccdaa4..f4f56a4763 100644 --- a/Assistant/WebApp/DashBoard.hs +++ b/Assistant/WebApp/DashBoard.hs @@ -71,11 +71,14 @@ dashboard warnNoScript = do $(widgetFile "dashboard/main") getHomeR :: Handler RepHtml -getHomeR = bootstrap (Just DashBoard) $ dashboard True +getHomeR = ifM (inFirstRun) + ( redirect ConfigR + , bootstrap (Just DashBoard) $ dashboard True + ) {- Same as HomeR, except no autorefresh at all (and no noscript warning). -} getNoScriptR :: Handler RepHtml -getNoScriptR = bootstrap (Just DashBoard) $ dashboard False +getNoScriptR = bootstrap (Just DashBoard) $ dashboard False {- Same as HomeR, except with autorefreshing via meta refresh. -} getNoScriptAutoR :: Handler RepHtml diff --git a/templates/configurators/addrepository.hamlet b/templates/configurators/addrepository.hamlet index 150e08981a..20ece28067 100644 --- a/templates/configurators/addrepository.hamlet +++ b/templates/configurators/addrepository.hamlet @@ -1,3 +1,16 @@ <div .span9 .hero-unit> - <h2> - Sorry, no configuration is implemented yet... + $if firstrun + <h2> + Welcome to git-annex! + <p> + There's just one thing to do before you can start using the power # + and convenience of git-annex. + <h2> + Create a git-annex repository + <p> + Files in this repository will managed by git-annex, # + and kept in sync with your repositories on other devices. + <form .form-inline> + <i class="icon-folder-open"></i> # + <input type="text" .input-xlarge placeholder="directory"> # + <button type="submit" .btn .btn-primary .btn-large>Make Repository</button> diff --git a/templates/configurators/intro.hamlet b/templates/configurators/intro.hamlet index be451a91fe..5062346a85 100644 --- a/templates/configurators/intro.hamlet +++ b/templates/configurators/intro.hamlet @@ -26,12 +26,3 @@ <a .btn .btn-primary .btn-large href="@{AddRepositoryR}">Add another repository</a> <p> Or just sit back, watch the magic, and get on with using your files. - $nothing - <h2> - Creating a git-annex repository - <p> - Files in this repository will managed by git-annex, # - and kept in sync with your repositories on other devices. - <form .form-inline> - <input type="text" .input-xlarge placeholder="directory"> # - <button type="submit" .btn .btn-primary .btn-large>Make Repository</button> From bcf5c81593f26a253b514224e3326defd6fa0a8d Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Tue, 31 Jul 2012 16:19:24 -0400 Subject: [PATCH 210/331] when run in uninitialized git repo, do firstrun My $HOME is in git, let's make it work :) --- Command/WebApp.hs | 10 ++++++---- Init.hs | 5 +++++ 2 files changed, 11 insertions(+), 4 deletions(-) diff --git a/Command/WebApp.hs b/Command/WebApp.hs index a3294911f9..e2442c37ec 100644 --- a/Command/WebApp.hs +++ b/Command/WebApp.hs @@ -16,12 +16,13 @@ import Assistant.Threads.WebApp import Utility.WebApp import Utility.ThreadScheduler import Utility.Daemon (checkDaemon) +import Init import qualified Command.Watch import Control.Concurrent.STM def :: [Command] -def = [oneShot $ noRepo firstRun $ +def = [oneShot $ noRepo firstRun $ dontCheck repoExists $ withOptions [Command.Watch.foregroundOption, Command.Watch.stopOption] $ command "webapp" paramNothing seek "launch webapp"] @@ -34,14 +35,15 @@ start :: Bool -> Bool -> CommandStart start foreground stopdaemon = notBareRepo $ do if stopdaemon then stopDaemon - else do + else ifM (isInitialized) ( go , liftIO firstRun ) + stop + where + go = do f <- liftIO . absPath =<< fromRepo gitAnnexHtmlShim ifM (checkpid <&&> checkshim f) $ ( liftIO $ openBrowser f , startDaemon True foreground $ Just openBrowser ) - stop - where checkpid = do pidfile <- fromRepo gitAnnexPidFile liftIO $ isJust <$> checkDaemon pidfile diff --git a/Init.hs b/Init.hs index bddcc696e0..8c000cc413 100644 --- a/Init.hs +++ b/Init.hs @@ -7,6 +7,7 @@ module Init ( ensureInitialized, + isInitialized, initialize, uninitialize ) where @@ -45,6 +46,10 @@ ensureInitialized = getVersion >>= maybe needsinit checkVersion , error "First run: git-annex init" ) +{- Checks if a repository is initialized. Does not check version for ugrade. -} +isInitialized :: Annex Bool +isInitialized = maybe Annex.Branch.hasSibling (const $ return True) =<< getVersion + {- set up a git pre-commit hook, if one is not already present -} gitPreCommitHookWrite :: Annex () gitPreCommitHookWrite = unlessBare $ do From 4b5ffe8f9b84c20912871b0dfe627d041ce2d99f Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Tue, 31 Jul 2012 17:57:08 -0400 Subject: [PATCH 211/331] implemented the addrepository form shiny! --- Assistant/WebApp.hs | 12 ++++++ Assistant/WebApp/Configurators.hs | 43 ++++++++++++++++---- Assistant/WebApp/routes | 3 +- templates/configurators/addrepository.hamlet | 7 ++-- 4 files changed, 53 insertions(+), 12 deletions(-) diff --git a/Assistant/WebApp.hs b/Assistant/WebApp.hs index 3351aa48fe..c2a021246e 100644 --- a/Assistant/WebApp.hs +++ b/Assistant/WebApp.hs @@ -95,6 +95,11 @@ instance Yesod WebApp where makeSessionBackend = webAppSessionBackend jsLoader _ = BottomOfHeadBlocking +instance RenderMessage WebApp FormMessage where + renderMessage _ _ = defaultFormMessage + +type Form x = Html -> MForm WebApp WebApp (FormResult x, Widget) + data WebAppState = WebAppState { showIntro :: Bool } @@ -145,3 +150,10 @@ instance PathPiece NotificationId where instance PathPiece AlertId where toPathPiece = pack . show fromPathPiece = readish . unpack + +{- Adds the auth parameter as a hidden field on a form. Must be put into + - every form. -} +webAppFormAuthToken :: Widget +webAppFormAuthToken = do + webapp <- lift getYesod + [whamlet|<input type="hidden" name="auth" value="#{secretToken webapp}">|] diff --git a/Assistant/WebApp/Configurators.hs b/Assistant/WebApp/Configurators.hs index 9fe10aff92..69bf92fdb3 100644 --- a/Assistant/WebApp/Configurators.hs +++ b/Assistant/WebApp/Configurators.hs @@ -19,7 +19,7 @@ import Logs.Trust import Annex.UUID (getUUID) import Yesod -import Data.Text (Text) +import Data.Text (Text, pack) {- An intro message, list of repositories, and nudge to make more. -} introDisplay :: Text -> Widget @@ -41,10 +41,44 @@ introDisplay ident = do where counter = map show ([1..] :: [Int]) +data RepositoryPath = RepositoryPath Text + deriving Show + +addRepositoryForm :: Form RepositoryPath +addRepositoryForm msg = do + cwd <- liftIO $ getCurrentDirectory + (pathRes, pathView) <- mreq textField "" (Just $ pack cwd) + let widget = do + webAppFormAuthToken + toWidget [julius| +$(function() { + $('##{fvId pathView}').focus(); +}) +|] + [whamlet| +#{msg} +<p> + <div .input-prepend .input-append> + <span .add-on> + <i .icon-folder-open></i> + ^{fvInput pathView} + <button type=submit .btn> + Make Repository +|] + return (RepositoryPath <$> pathRes, widget) + addRepository :: Bool -> Widget addRepository firstrun = do setTitle $ if firstrun then "Getting started" else "Add repository" - $(widgetFile "configurators/addrepository") + ((res, form), enctype) <- lift $ runFormGet addRepositoryForm + case res of + FormSuccess (RepositoryPath p) -> error $ "TODO" ++ show p + _ -> $(widgetFile "configurators/addrepository") + +getAddRepositoryR :: Handler RepHtml +getAddRepositoryR = bootstrap (Just Config) $ do + sideBarDisplay + addRepository False getConfigR :: Handler RepHtml getConfigR = bootstrap (Just Config) $ do @@ -55,8 +89,3 @@ getConfigR = bootstrap (Just Config) $ do setTitle "Configuration" $(widgetFile "configurators/main") ) - -getAddRepositoryR :: Handler RepHtml -getAddRepositoryR = bootstrap (Just Config) $ do - sideBarDisplay - addRepository False diff --git a/Assistant/WebApp/routes b/Assistant/WebApp/routes index 69e6078b02..95813edb6f 100644 --- a/Assistant/WebApp/routes +++ b/Assistant/WebApp/routes @@ -1,9 +1,10 @@ / HomeR GET /noscript NoScriptR GET /noscriptauto NoScriptAutoR GET +/about AboutR GET + /config ConfigR GET /config/addrepository AddRepositoryR GET -/about AboutR GET /transfers/#NotificationId TransfersR GET /sidebar/#NotificationId SideBarR GET diff --git a/templates/configurators/addrepository.hamlet b/templates/configurators/addrepository.hamlet index 20ece28067..7af450b877 100644 --- a/templates/configurators/addrepository.hamlet +++ b/templates/configurators/addrepository.hamlet @@ -10,7 +10,6 @@ <p> Files in this repository will managed by git-annex, # and kept in sync with your repositories on other devices. - <form .form-inline> - <i class="icon-folder-open"></i> # - <input type="text" .input-xlarge placeholder="directory"> # - <button type="submit" .btn .btn-primary .btn-large>Make Repository</button> + <p> + <form .form-inline enctype=#{enctype}> + ^{form} From c950e8fba0de95f3a102b2653f70457fc8f19ab3 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Tue, 31 Jul 2012 18:33:19 -0400 Subject: [PATCH 212/331] move out to template --- Assistant/WebApp/Configurators.hs | 20 +++---------------- Makefile | 4 ++-- .../configurators/addrepository/form.hamlet | 8 ++++++++ 3 files changed, 13 insertions(+), 19 deletions(-) create mode 100644 templates/configurators/addrepository/form.hamlet diff --git a/Assistant/WebApp/Configurators.hs b/Assistant/WebApp/Configurators.hs index 69bf92fdb3..6a467692a2 100644 --- a/Assistant/WebApp/Configurators.hs +++ b/Assistant/WebApp/Configurators.hs @@ -48,24 +48,10 @@ addRepositoryForm :: Form RepositoryPath addRepositoryForm msg = do cwd <- liftIO $ getCurrentDirectory (pathRes, pathView) <- mreq textField "" (Just $ pack cwd) - let widget = do + let form = do webAppFormAuthToken - toWidget [julius| -$(function() { - $('##{fvId pathView}').focus(); -}) -|] - [whamlet| -#{msg} -<p> - <div .input-prepend .input-append> - <span .add-on> - <i .icon-folder-open></i> - ^{fvInput pathView} - <button type=submit .btn> - Make Repository -|] - return (RepositoryPath <$> pathRes, widget) + $(widgetFile "configurators/addrepository/form") + return (RepositoryPath <$> pathRes, form) addRepository :: Bool -> Widget addRepository firstrun = do diff --git a/Makefile b/Makefile index a6fdab7ca7..8eef53f30e 100644 --- a/Makefile +++ b/Makefile @@ -6,7 +6,7 @@ FEATURES=-DWITH_ASSISTANT -DWITH_S3 -DWITH_WEBAPP bins=git-annex mans=git-annex.1 git-annex-shell.1 sources=Build/SysConfig.hs Utility/Touch.hs Utility/Mounts.hs -thfiles=Assistant/Threads/WebApp.hs +thfiles=Assistant/Threads/WebApp.hs $(shell find Assistant/WebApp*) all=$(bins) $(mans) docs OS:=$(shell uname | sed 's/[-_].*//') @@ -58,7 +58,7 @@ Build/SysConfig.hs: configure.hs Build/TestConfig.hs Build/Configure.hs # Force GHC to rebuild template haskell files whenever includes # change -$(thfiles): $(shell echo templates/* static/*) +$(thfiles): $(shell find templates static) $(thfiles): touch $(thfiles) diff --git a/templates/configurators/addrepository/form.hamlet b/templates/configurators/addrepository/form.hamlet new file mode 100644 index 0000000000..fa5d07f2d6 --- /dev/null +++ b/templates/configurators/addrepository/form.hamlet @@ -0,0 +1,8 @@ +#{msg} +<p> + <div .input-prepend .input-append> + <span .add-on> + <i .icon-folder-open></i> + ^{fvInput pathView} + <button type=submit .btn> + Make Repository From bab80bf24ada54f8dec2a35bbb77219441719f6a Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Tue, 31 Jul 2012 20:56:10 -0400 Subject: [PATCH 213/331] full input validation for repository path Expands ~ , checks for every crazy input problem I can think of --- Assistant/WebApp/Configurators.hs | 58 ++++++++++++++++++- .../configurators/addrepository/form.hamlet | 3 + 2 files changed, 60 insertions(+), 1 deletion(-) diff --git a/Assistant/WebApp/Configurators.hs b/Assistant/WebApp/Configurators.hs index 6a467692a2..59acb763a6 100644 --- a/Assistant/WebApp/Configurators.hs +++ b/Assistant/WebApp/Configurators.hs @@ -20,6 +20,8 @@ import Annex.UUID (getUUID) import Yesod import Data.Text (Text, pack) +import qualified Data.Text as T +import Data.Char {- An intro message, list of repositories, and nudge to make more. -} introDisplay :: Text -> Widget @@ -44,10 +46,64 @@ introDisplay ident = do data RepositoryPath = RepositoryPath Text deriving Show +{- Custom field display for a RepositoryPath, with an icon etc. + - + - Validates that the path entered is not empty, and is a safe value + - to use as a repository. -} +repositoryPathField :: forall sub. Bool -> Field sub WebApp Text +repositoryPathField autofocus = Field { fieldParse = parse, fieldView = view } + where + view idAttr nameAttr attrs val isReq = + [whamlet|<input type="text" *{attrs} id="#{idAttr}" name="#{nameAttr}" :isReq:required :autofocus:autofocus value="#{either id id val}">|] + + parse [path] + | T.null path = nopath + | otherwise = liftIO $ checkRepositoryPath path + parse [] = return $ Right Nothing + parse _ = nopath + + nopath = return $ Left "Enter a location for the repository" + +{- As well as checking the path for a lot of silly things, tilde is + - expanded in the returned path. -} +checkRepositoryPath :: Text -> IO (Either (SomeMessage WebApp) (Maybe Text)) +checkRepositoryPath p = do + home <- myHomeDir + let basepath = expandTilde home $ T.unpack p + path <- absPath basepath + let parent = parentDir path + problems <- catMaybes <$> mapM runcheck + [ (return $ path == "/", "Enter the full path to use for the repository.") + , (return $ all isSpace basepath, "A blank path? Seems unlikely.") + , (doesFileExist path, "A file already exists with that name.") + , (return $ path == home, "Sorry, using git-annex for your whole home directory is not currently supported.") + , (not <$> doesDirectoryExist parent, "Parent directory does not exist.") + , (cannotWrite path, "Cannot write a repository there.") + ] + return $ + case headMaybe problems of + Nothing -> Right $ Just $ T.pack basepath + Just prob -> Left prob + where + runcheck (chk, msg) = ifM (chk) + ( return $ Just msg + , return Nothing + ) + cannotWrite path = do + tocheck <- ifM (doesDirectoryExist path) + (return path, return $ parentDir path) + not <$> (catchBoolIO $ fileAccess tocheck False True False) + expandTilde home ('~':path) = home </> path + expandTilde _ path = path + addRepositoryForm :: Form RepositoryPath addRepositoryForm msg = do cwd <- liftIO $ getCurrentDirectory - (pathRes, pathView) <- mreq textField "" (Just $ pack cwd) + (pathRes, pathView) <- mreq (repositoryPathField True) "" (Just $ pack $ cwd ++ "/") + let (err, errmsg) = case pathRes of + FormMissing -> (False, "") + FormFailure l -> (True, concat $ map T.unpack l) + FormSuccess _ -> (False, "") let form = do webAppFormAuthToken $(widgetFile "configurators/addrepository/form") diff --git a/templates/configurators/addrepository/form.hamlet b/templates/configurators/addrepository/form.hamlet index fa5d07f2d6..e72dbcf431 100644 --- a/templates/configurators/addrepository/form.hamlet +++ b/templates/configurators/addrepository/form.hamlet @@ -6,3 +6,6 @@ ^{fvInput pathView} <button type=submit .btn> Make Repository +$if err + <div .alert .alert-error> + #{errmsg} From e81e8913d9c663cbe680224e6237433e7508e7d3 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Tue, 31 Jul 2012 21:06:30 -0400 Subject: [PATCH 214/331] default repository location Unifying poll results, it's Annex in lowercase. :) When cwd is HOME, use ~/Desktop/annex, unless there's no Desktop directory; then use use ~/annex If cwd is not $HOME, use cwd --- Assistant/WebApp/Configurators.hs | 20 +++++++++++++++++--- 1 file changed, 17 insertions(+), 3 deletions(-) diff --git a/Assistant/WebApp/Configurators.hs b/Assistant/WebApp/Configurators.hs index 59acb763a6..d646e6fb78 100644 --- a/Assistant/WebApp/Configurators.hs +++ b/Assistant/WebApp/Configurators.hs @@ -19,7 +19,7 @@ import Logs.Trust import Annex.UUID (getUUID) import Yesod -import Data.Text (Text, pack) +import Data.Text (Text) import qualified Data.Text as T import Data.Char @@ -96,10 +96,24 @@ checkRepositoryPath p = do expandTilde home ('~':path) = home </> path expandTilde _ path = path +{- If run in the home directory, default to putting it in ~/Desktop/annex, + - when a Desktop directory exists, and ~/annex otherwise. + - + - If run in another directory, the user probably wants to put it there. -} +defaultRepositoryPath :: IO FilePath +defaultRepositoryPath = do + cwd <- liftIO $ getCurrentDirectory + home <- myHomeDir + if home == cwd + then ifM (doesDirectoryExist $ home </> "Desktop") + (return "~/Desktop/annex", return "~") + else return cwd + addRepositoryForm :: Form RepositoryPath addRepositoryForm msg = do - cwd <- liftIO $ getCurrentDirectory - (pathRes, pathView) <- mreq (repositoryPathField True) "" (Just $ pack $ cwd ++ "/") + path <- T.pack . addTrailingPathSeparator + <$> liftIO defaultRepositoryPath + (pathRes, pathView) <- mreq (repositoryPathField True) ""(Just path) let (err, errmsg) = case pathRes of FormMissing -> (False, "") FormFailure l -> (True, concat $ map T.unpack l) From b9afb7785e84ba03cb44a9b6962dbd01feaa4aae Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Tue, 31 Jul 2012 21:12:58 -0400 Subject: [PATCH 215/331] typo --- Assistant/WebApp/Configurators.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Assistant/WebApp/Configurators.hs b/Assistant/WebApp/Configurators.hs index d646e6fb78..69108e46e2 100644 --- a/Assistant/WebApp/Configurators.hs +++ b/Assistant/WebApp/Configurators.hs @@ -106,7 +106,7 @@ defaultRepositoryPath = do home <- myHomeDir if home == cwd then ifM (doesDirectoryExist $ home </> "Desktop") - (return "~/Desktop/annex", return "~") + (return "~/Desktop/annex", return "~/annex") else return cwd addRepositoryForm :: Form RepositoryPath From 1efe4f3332680be5ad9d5d496939d6757fbd2b0a Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Tue, 31 Jul 2012 21:34:29 -0400 Subject: [PATCH 216/331] only use smart default on first run --- Assistant/WebApp/Configurators.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/Assistant/WebApp/Configurators.hs b/Assistant/WebApp/Configurators.hs index 69108e46e2..b9630b10a5 100644 --- a/Assistant/WebApp/Configurators.hs +++ b/Assistant/WebApp/Configurators.hs @@ -96,15 +96,15 @@ checkRepositoryPath p = do expandTilde home ('~':path) = home </> path expandTilde _ path = path -{- If run in the home directory, default to putting it in ~/Desktop/annex, - - when a Desktop directory exists, and ~/annex otherwise. +{- On first run, if run in the home directory, default to putting it in + - ~/Desktop/annex, when a Desktop directory exists, and ~/annex otherwise. - - If run in another directory, the user probably wants to put it there. -} -defaultRepositoryPath :: IO FilePath -defaultRepositoryPath = do +defaultRepositoryPath :: Bool -> IO FilePath +defaultRepositoryPath firstrun = do cwd <- liftIO $ getCurrentDirectory home <- myHomeDir - if home == cwd + if home == cwd && firstRun then ifM (doesDirectoryExist $ home </> "Desktop") (return "~/Desktop/annex", return "~/annex") else return cwd @@ -112,7 +112,7 @@ defaultRepositoryPath = do addRepositoryForm :: Form RepositoryPath addRepositoryForm msg = do path <- T.pack . addTrailingPathSeparator - <$> liftIO defaultRepositoryPath + <$> liftIO defaultRepositoryPath =<< lift inFirstRun (pathRes, pathView) <- mreq (repositoryPathField True) ""(Just path) let (err, errmsg) = case pathRes of FormMissing -> (False, "") From ecc168aba30a0477381bcd2037c8d301368f3449 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Wed, 1 Aug 2012 16:10:26 -0400 Subject: [PATCH 217/331] implemented firstrun repository creation and redirection to full webapp Some of the trickiest code I've possibly ever written. --- Assistant.hs | 24 +++++++++------- Assistant/Threads/WebApp.hs | 22 +++++++++++---- Assistant/WebApp.hs | 1 + Assistant/WebApp/Configurators.hs | 41 ++++++++++++++++++++++++--- Command/WebApp.hs | 47 +++++++++++++++++++++++++++---- 5 files changed, 110 insertions(+), 25 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index 4bb85975b8..be84fab55e 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -122,7 +122,10 @@ import Utility.ThreadScheduler import Control.Concurrent -startDaemon :: Bool -> Bool -> Maybe (FilePath -> IO ()) -> Annex () +stopDaemon :: Annex () +stopDaemon = liftIO . Utility.Daemon.stopDaemon =<< fromRepo gitAnnexPidFile + +startDaemon :: Bool -> Bool -> Maybe (Url -> FilePath -> IO ()) -> Annex () startDaemon assistant foreground webappwaiter | foreground = do showStart (if assistant then "assistant" else "watch") "." @@ -132,10 +135,15 @@ startDaemon assistant foreground webappwaiter pidfile <- fromRepo gitAnnexPidFile go $ Utility.Daemon.daemonize logfd (Just pidfile) False where - go daemonize = withThreadState $ \st -> do - checkCanWatch - dstatus <- startDaemonStatus - liftIO $ daemonize $ run dstatus st + go d = startAssistant assistant d webappwaiter + +startAssistant :: Bool -> (IO () -> IO ()) -> Maybe (Url -> FilePath -> IO ()) -> Annex () +startAssistant assistant daemonize webappwaiter = do + withThreadState $ \st -> do + checkCanWatch + dstatus <- startDaemonStatus + liftIO $ daemonize $ run dstatus st + where run dstatus st = do changechan <- newChangeChan commitchan <- newCommitChan @@ -155,12 +163,8 @@ startDaemon assistant foreground webappwaiter , mountWatcherThread st dstatus scanremotes , transferScannerThread st dstatus scanremotes transferqueue #ifdef WITH_WEBAPP - , webAppThread (Just st) dstatus transferqueue webappwaiter + , webAppThread (Just st) dstatus transferqueue Nothing webappwaiter #endif , watchThread st dstatus transferqueue changechan ] - debug "Assistant" ["all threads started"] waitForTermination - -stopDaemon :: Annex () -stopDaemon = liftIO . Utility.Daemon.stopDaemon =<< fromRepo gitAnnexPidFile diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index ad2bff8923..a5484b5bec 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -38,8 +38,16 @@ thisThread = "WebApp" mkYesodDispatch "WebApp" $(parseRoutesFile "Assistant/WebApp/routes") -webAppThread :: (Maybe ThreadState) -> DaemonStatusHandle -> TransferQueue -> Maybe (FilePath -> IO ()) -> IO () -webAppThread mst dstatus transferqueue onstartup = do +type Url = String + +webAppThread + :: (Maybe ThreadState) + -> DaemonStatusHandle + -> TransferQueue + -> Maybe (IO String) + -> Maybe (Url -> FilePath -> IO ()) + -> IO () +webAppThread mst dstatus transferqueue postfirstrun onstartup = do webapp <- WebApp <$> pure mst <*> pure dstatus @@ -48,6 +56,7 @@ webAppThread mst dstatus transferqueue onstartup = do <*> getreldir mst <*> pure $(embed "static") <*> newWebAppState + <*> pure postfirstrun app <- toWaiAppPlain webapp app' <- ifM debugEnabled ( return $ httpDebugLogger app @@ -66,7 +75,7 @@ webAppThread mst dstatus transferqueue onstartup = do else dir go port webapp htmlshim = do writeHtmlShim webapp port htmlshim - maybe noop (\a -> a htmlshim) onstartup + maybe noop (\a -> a (myUrl webapp port) htmlshim) onstartup {- Creates a html shim file that's used to redirect into the webapp, - to avoid exposing the secretToken when launching the web browser. -} @@ -85,5 +94,8 @@ writeHtmlShim webapp port file = do genHtmlShim :: WebApp -> PortNumber -> String genHtmlShim webapp port = renderHtml $(shamletFile $ hamletTemplate "htmlshim") where - url = "http://localhost:" ++ show port ++ - "/?auth=" ++ unpack (secretToken webapp) + url = myUrl webapp port + +myUrl :: WebApp -> PortNumber -> Url +myUrl webapp port = "http://localhost:" ++ show port ++ + "/?auth=" ++ unpack (secretToken webapp) diff --git a/Assistant/WebApp.hs b/Assistant/WebApp.hs index c2a021246e..1b767c642d 100644 --- a/Assistant/WebApp.hs +++ b/Assistant/WebApp.hs @@ -37,6 +37,7 @@ data WebApp = WebApp , relDir :: Maybe FilePath , getStatic :: Static , webAppState :: TMVar WebAppState + , postFirstRun :: Maybe (IO String) } data NavBarItem = DashBoard | Config | About diff --git a/Assistant/WebApp/Configurators.hs b/Assistant/WebApp/Configurators.hs index b9630b10a5..5c2a1f25ed 100644 --- a/Assistant/WebApp/Configurators.hs +++ b/Assistant/WebApp/Configurators.hs @@ -17,11 +17,16 @@ import qualified Remote import Logs.Web (webUUID) import Logs.Trust import Annex.UUID (getUUID) +import Init +import qualified Git.Construct +import qualified Git.Config +import qualified Annex import Yesod import Data.Text (Text) import qualified Data.Text as T import Data.Char +import System.Posix.Directory {- An intro message, list of repositories, and nudge to make more. -} introDisplay :: Text -> Widget @@ -104,7 +109,7 @@ defaultRepositoryPath :: Bool -> IO FilePath defaultRepositoryPath firstrun = do cwd <- liftIO $ getCurrentDirectory home <- myHomeDir - if home == cwd && firstRun + if home == cwd && firstrun then ifM (doesDirectoryExist $ home </> "Desktop") (return "~/Desktop/annex", return "~/annex") else return cwd @@ -112,8 +117,8 @@ defaultRepositoryPath firstrun = do addRepositoryForm :: Form RepositoryPath addRepositoryForm msg = do path <- T.pack . addTrailingPathSeparator - <$> liftIO defaultRepositoryPath =<< lift inFirstRun - (pathRes, pathView) <- mreq (repositoryPathField True) ""(Just path) + <$> (liftIO . defaultRepositoryPath =<< lift inFirstRun) + (pathRes, pathView) <- mreq (repositoryPathField True) "" (Just path) let (err, errmsg) = case pathRes of FormMissing -> (False, "") FormFailure l -> (True, concat $ map T.unpack l) @@ -128,8 +133,36 @@ addRepository firstrun = do setTitle $ if firstrun then "Getting started" else "Add repository" ((res, form), enctype) <- lift $ runFormGet addRepositoryForm case res of - FormSuccess (RepositoryPath p) -> error $ "TODO" ++ show p + FormSuccess (RepositoryPath p) -> go $ T.unpack p _ -> $(widgetFile "configurators/addrepository") + where + go path + | firstrun = lift $ startFullAssistant path + | otherwise = error "TODO" + +{- Bootstraps from first run mode to a fully running assistant in a + - repository, by running the postFirstRun callback, which returns the + - url to the new webapp. -} +startFullAssistant :: FilePath -> Handler () +startFullAssistant path = do + webapp <- getYesod + url <- liftIO $ do + makeRepo path + changeWorkingDirectory path + putStrLn "pre run" + r <- fromJust $ postFirstRun webapp + putStrLn $ "got " ++ r + return r + redirect $ T.pack url + +{- Makes a new git-annex repository. -} +makeRepo :: FilePath -> IO () +makeRepo path = do + unlessM (boolSystem "git" [Param "init", Param "--quiet", File path]) $ + error "git init failed!" + g <- Git.Config.read =<< Git.Construct.fromPath path + state <- Annex.new g + Annex.eval state $ initialize $ Just "new repo" getAddRepositoryR :: Handler RepHtml getAddRepositoryR = bootstrap (Just Config) $ do diff --git a/Command/WebApp.hs b/Command/WebApp.hs index e2442c37ec..0ddf65c589 100644 --- a/Command/WebApp.hs +++ b/Command/WebApp.hs @@ -14,11 +14,13 @@ import Assistant.DaemonStatus import Assistant.TransferQueue import Assistant.Threads.WebApp import Utility.WebApp -import Utility.ThreadScheduler import Utility.Daemon (checkDaemon) import Init import qualified Command.Watch +import qualified Git.CurrentRepo +import qualified Annex +import Control.Concurrent import Control.Concurrent.STM def :: [Command] @@ -42,7 +44,8 @@ start foreground stopdaemon = notBareRepo $ do f <- liftIO . absPath =<< fromRepo gitAnnexHtmlShim ifM (checkpid <&&> checkshim f) $ ( liftIO $ openBrowser f - , startDaemon True foreground $ Just openBrowser + , startDaemon True foreground $ Just $ + const openBrowser ) checkpid = do pidfile <- fromRepo gitAnnexPidFile @@ -53,12 +56,44 @@ openBrowser :: FilePath -> IO () openBrowser htmlshim = unlessM (runBrowser url) $ error $ "failed to start web browser on url " ++ url where - url = "file://" ++ htmlshim + url = fileUrl htmlshim +fileUrl :: FilePath -> String +fileUrl file = "file://" ++ file + +{- Run the webapp without a repository, which prompts the user, makes one, + - changes to it, starts the regular assistant, and redirects the + - browser to its url. + - + - This is a very tricky dance -- The first webapp calls the signaler, + - which signals the main thread when it's ok to continue by writing to a + - MVar. The main thread starts the second webapp, and uses its callback + - to write its url back to the MVar, from where the signaler retrieves it, + - returning it to the first webapp, which does the redirect. + - + - Note that it's important that mainthread never terminates! Much + - of this complication is due to needing to keep the mainthread running. + -} firstRun :: IO () firstRun = do dstatus <- atomically . newTMVar =<< newDaemonStatus transferqueue <- newTransferQueue - webAppThread Nothing dstatus transferqueue $ Just $ \f -> do - openBrowser f - waitForTermination + v <- newEmptyMVar + let callback a = Just $ a v + webAppThread Nothing dstatus transferqueue (callback signaler) (callback mainthread) + where + signaler v = do + putMVar v "" + putStrLn "signaler waiting..." + r <- takeMVar v + putStrLn "signaler got value" + return r + mainthread v _url htmlshim = do + openBrowser htmlshim + + _wait <- takeMVar v + + state <- Annex.new =<< Git.CurrentRepo.get + Annex.eval state $ + startAssistant True id $ Just $ sendurlback v + sendurlback v url _htmlshim = putMVar v url From 8181b38ef6060103953ce464d03e9cfd75c45663 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Wed, 1 Aug 2012 16:29:38 -0400 Subject: [PATCH 218/331] write pid file even when running in foreground This prevents multiple runs of the assistant in the foreground, and lets --stop stop foregrounded runs too. The webapp firstrun case also now writes a pid file, once it's made the git repo to put it in. --- Assistant.hs | 1 + Command/WebApp.hs | 8 ++++++-- Utility/Daemon.hs | 16 ++++++++-------- 3 files changed, 15 insertions(+), 10 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index be84fab55e..21414e721e 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -129,6 +129,7 @@ startDaemon :: Bool -> Bool -> Maybe (Url -> FilePath -> IO ()) -> Annex () startDaemon assistant foreground webappwaiter | foreground = do showStart (if assistant then "assistant" else "watch") "." + liftIO . Utility.Daemon.lockPidFile =<< fromRepo gitAnnexPidFile go id | otherwise = do logfd <- liftIO . openLog =<< fromRepo gitAnnexLogFile diff --git a/Command/WebApp.hs b/Command/WebApp.hs index 0ddf65c589..61de2c2f19 100644 --- a/Command/WebApp.hs +++ b/Command/WebApp.hs @@ -14,7 +14,7 @@ import Assistant.DaemonStatus import Assistant.TransferQueue import Assistant.Threads.WebApp import Utility.WebApp -import Utility.Daemon (checkDaemon) +import Utility.Daemon (checkDaemon, lockPidFile) import Init import qualified Command.Watch import qualified Git.CurrentRepo @@ -94,6 +94,10 @@ firstRun = do _wait <- takeMVar v state <- Annex.new =<< Git.CurrentRepo.get - Annex.eval state $ + Annex.eval state $ do + dummydaemonize startAssistant True id $ Just $ sendurlback v sendurlback v url _htmlshim = putMVar v url + {- Set up the pid file in the new repo. -} + dummydaemonize = do + liftIO . lockPidFile =<< fromRepo gitAnnexPidFile diff --git a/Utility/Daemon.hs b/Utility/Daemon.hs index 3386ea4434..ba2b2c9c3c 100644 --- a/Utility/Daemon.hs +++ b/Utility/Daemon.hs @@ -27,7 +27,7 @@ daemonize logfd pidfile changedirectory a = do _ <- forkProcess child2 out child2 = do - maybe noop (lockPidFile alreadyrunning) pidfile + maybe noop lockPidFile pidfile when changedirectory $ setCurrentDirectory "/" nullfd <- openFd "/dev/null" ReadOnly Nothing defaultFileFlags @@ -39,28 +39,28 @@ daemonize logfd pidfile changedirectory a = do redir newh h = do closeFd h dupTo newh h - alreadyrunning = error "Daemon is already running." out = exitImmediately ExitSuccess {- Locks the pid file, with an exclusive, non-blocking lock. - - Runs an action on failure. On success, writes the pid to the file, - - fully atomically. -} -lockPidFile :: IO () -> FilePath -> IO () -lockPidFile onfailure file = do + - Writes the pid to the file, fully atomically. + - Fails if the pid file is already locked by another process. -} +lockPidFile :: FilePath -> IO () +lockPidFile file = do fd <- openFd file ReadWrite (Just stdFileMode) defaultFileFlags locked <- catchMaybeIO $ setLock fd (WriteLock, AbsoluteSeek, 0, 0) fd' <- openFd newfile ReadWrite (Just stdFileMode) defaultFileFlags { trunc = True } locked' <- catchMaybeIO $ setLock fd' (WriteLock, AbsoluteSeek, 0, 0) case (locked, locked') of - (Nothing, _) -> onfailure - (_, Nothing) -> onfailure + (Nothing, _) -> alreadyrunning + (_, Nothing) -> alreadyrunning _ -> do _ <- fdWrite fd' =<< show <$> getProcessID renameFile newfile file closeFd fd where newfile = file ++ ".new" + alreadyrunning = error "Daemon is already running." {- Checks if the daemon is running, by checking that the pid file - is locked by the same process that is listed in the pid file. From 7606f3e7c1cc1b13445d04d11372c197fb6a3f13 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Wed, 1 Aug 2012 16:31:16 -0400 Subject: [PATCH 219/331] cleanup --- Assistant/WebApp/Configurators.hs | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/Assistant/WebApp/Configurators.hs b/Assistant/WebApp/Configurators.hs index 5c2a1f25ed..e1fcfcd971 100644 --- a/Assistant/WebApp/Configurators.hs +++ b/Assistant/WebApp/Configurators.hs @@ -149,10 +149,7 @@ startFullAssistant path = do url <- liftIO $ do makeRepo path changeWorkingDirectory path - putStrLn "pre run" - r <- fromJust $ postFirstRun webapp - putStrLn $ "got " ++ r - return r + fromJust $ postFirstRun webapp redirect $ T.pack url {- Makes a new git-annex repository. -} From ca512f1450d919397b6eb4fbc54e32e70677c8f7 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Wed, 1 Aug 2012 16:34:17 -0400 Subject: [PATCH 220/331] always run webapp in foreground --- Command/WebApp.hs | 16 ++++++---------- 1 file changed, 6 insertions(+), 10 deletions(-) diff --git a/Command/WebApp.hs b/Command/WebApp.hs index 61de2c2f19..20b914b7af 100644 --- a/Command/WebApp.hs +++ b/Command/WebApp.hs @@ -25,16 +25,15 @@ import Control.Concurrent.STM def :: [Command] def = [oneShot $ noRepo firstRun $ dontCheck repoExists $ - withOptions [Command.Watch.foregroundOption, Command.Watch.stopOption] $ + withOptions [Command.Watch.stopOption] $ command "webapp" paramNothing seek "launch webapp"] seek :: [CommandSeek] seek = [withFlag Command.Watch.stopOption $ \stopdaemon -> - withFlag Command.Watch.foregroundOption $ \foreground -> - withNothing $ start foreground stopdaemon] + withNothing $ start stopdaemon] -start :: Bool -> Bool -> CommandStart -start foreground stopdaemon = notBareRepo $ do +start :: Bool -> CommandStart +start stopdaemon = notBareRepo $ do if stopdaemon then stopDaemon else ifM (isInitialized) ( go , liftIO firstRun ) @@ -44,7 +43,7 @@ start foreground stopdaemon = notBareRepo $ do f <- liftIO . absPath =<< fromRepo gitAnnexHtmlShim ifM (checkpid <&&> checkshim f) $ ( liftIO $ openBrowser f - , startDaemon True foreground $ Just $ + , startDaemon True True $ Just $ const openBrowser ) checkpid = do @@ -84,10 +83,7 @@ firstRun = do where signaler v = do putMVar v "" - putStrLn "signaler waiting..." - r <- takeMVar v - putStrLn "signaler got value" - return r + takeMVar v mainthread v _url htmlshim = do openBrowser htmlshim From d7a2600edd1989934c61ae5a80fdc2ee385d49c5 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Wed, 1 Aug 2012 16:40:38 -0400 Subject: [PATCH 221/331] webapp is no longer a daemon Remove --foreground and --stop options from it. --- Command/WebApp.hs | 13 ++++--------- doc/git-annex.mdwn | 4 ++-- 2 files changed, 6 insertions(+), 11 deletions(-) diff --git a/Command/WebApp.hs b/Command/WebApp.hs index 20b914b7af..f143d8667b 100644 --- a/Command/WebApp.hs +++ b/Command/WebApp.hs @@ -16,7 +16,6 @@ import Assistant.Threads.WebApp import Utility.WebApp import Utility.Daemon (checkDaemon, lockPidFile) import Init -import qualified Command.Watch import qualified Git.CurrentRepo import qualified Annex @@ -25,18 +24,14 @@ import Control.Concurrent.STM def :: [Command] def = [oneShot $ noRepo firstRun $ dontCheck repoExists $ - withOptions [Command.Watch.stopOption] $ command "webapp" paramNothing seek "launch webapp"] seek :: [CommandSeek] -seek = [withFlag Command.Watch.stopOption $ \stopdaemon -> - withNothing $ start stopdaemon] +seek = [withNothing start] -start :: Bool -> CommandStart -start stopdaemon = notBareRepo $ do - if stopdaemon - then stopDaemon - else ifM (isInitialized) ( go , liftIO firstRun ) +start :: CommandStart +start = notBareRepo $ do + ifM (isInitialized) ( go , liftIO firstRun ) stop where go = do diff --git a/doc/git-annex.mdwn b/doc/git-annex.mdwn index 282b1fda50..0a6df035be 100644 --- a/doc/git-annex.mdwn +++ b/doc/git-annex.mdwn @@ -192,8 +192,8 @@ subdirectories). * webapp - Opens a web browser, viewing the git-annex assistant's web app. - (If the assistant is not already running, it will be automatically started.) + Runs a web app, that allows easy setup of a git-annex repository, + and control of the git-annex assistant. # REPOSITORY SETUP COMMANDS From bdd5fe4170afe3e6ca0cd2f72c1522d2cf4f8bb1 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Wed, 1 Aug 2012 17:01:04 -0400 Subject: [PATCH 222/331] fix the watch command to not run the whole assistant heh :) --- Assistant.hs | 31 ++++++++++++++++++------------- 1 file changed, 18 insertions(+), 13 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index 21414e721e..6af6c6639e 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -152,20 +152,25 @@ startAssistant assistant daemonize webappwaiter = do transferqueue <- newTransferQueue transferslots <- newTransferSlots scanremotes <- newScanRemoteMap - mapM_ forkIO - [ commitThread st changechan commitchan transferqueue dstatus - , pushThread st dstatus commitchan pushmap - , pushRetryThread st dstatus pushmap - , mergeThread st - , transferWatcherThread st dstatus - , transfererThread st dstatus transferqueue transferslots - , daemonStatusThread st dstatus - , sanityCheckerThread st dstatus transferqueue changechan - , mountWatcherThread st dstatus scanremotes - , transferScannerThread st dstatus scanremotes transferqueue + mapM_ startthread + [ watch $ commitThread st changechan commitchan transferqueue dstatus + , assist $ pushThread st dstatus commitchan pushmap + , assist $ pushRetryThread st dstatus pushmap + , assist $ mergeThread st + , assist $ transferWatcherThread st dstatus + , assist $ transfererThread st dstatus transferqueue transferslots + , assist $ daemonStatusThread st dstatus + , assist $ sanityCheckerThread st dstatus transferqueue changechan + , assist $ mountWatcherThread st dstatus scanremotes + , assist $ transferScannerThread st dstatus scanremotes transferqueue #ifdef WITH_WEBAPP - , webAppThread (Just st) dstatus transferqueue Nothing webappwaiter + , assist $ webAppThread (Just st) dstatus transferqueue Nothing webappwaiter #endif - , watchThread st dstatus transferqueue changechan + , watch $ watchThread st dstatus transferqueue changechan ] waitForTermination + watch a = (True, a) + assist a = (False, a) + startthread (watcher, a) + | watcher || assistant = void $ forkIO a + | otherwise = noop From 89ec253a6a02addca9293815966454a9646dcf0d Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Wed, 1 Aug 2012 20:27:45 -0400 Subject: [PATCH 223/331] implement enough of the fdo specs to be able to write desktop menu files to the appropriate system or local user directory --- Utility/FreeDesktop.hs | 94 ++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 94 insertions(+) create mode 100644 Utility/FreeDesktop.hs diff --git a/Utility/FreeDesktop.hs b/Utility/FreeDesktop.hs new file mode 100644 index 0000000000..ce3501766c --- /dev/null +++ b/Utility/FreeDesktop.hs @@ -0,0 +1,94 @@ +{- Freedesktop.org specifications + - + - http://standards.freedesktop.org/basedir-spec/latest/ + - http://standards.freedesktop.org/desktop-entry-spec/latest/ + - http://standards.freedesktop.org/menu-spec/latest/ + - + - Copyright 2012 Joey Hess <joey@kitenet.net> + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Utility.DesktopMenu ( + DesktopEntry, + genDesktopEntry, + buildDesktopMenuFile, + writeDesktopMenuFile, + userDesktopMenuFilePath, + systemDesktopMenuFilePath +) where + +import Utility.Exception +import Utility.Directory +import Utility.Path + +import System.IO +import System.Environment +import System.Directory +import System.FilePath +import Data.List +import Data.String.Utils + +type DesktopEntry = [(Key, Value)] + +type Key = String + +data Value = StringV String | BoolV Bool | NumericV Float | ListV [Value] + +toString :: Value -> String +toString (StringV s) = s +toString (BoolV b) + | b = "true" + | otherwise = "false" +toString(NumericV f) = show f +toString (ListV l) + | null l = "" + | otherwise = (intercalate ";" $ map (escapesemi . toString) l) ++ ";" + where + escapesemi = join "\\;" . split ";" + +genDesktopEntry :: String -> String -> Bool -> FilePath -> FilePath -> [String] -> DesktopEntry +genDesktopEntry name comment terminal program icon categories = + [ item "Encoding" StringV "UTF-8" + , item "Type" StringV "Application" + , item "Version" NumericV 1.0 + , item "Name" StringV name + , item "Comment" StringV comment + , item "Terminal" BoolV terminal + , item "Exec" StringV program + , item "Icon" StringV icon + , item "Categories" ListV (map StringV categories) + ] + where + item x c y = (x, c y) + +buildDesktopMenuFile :: DesktopEntry -> String +buildDesktopMenuFile d = unlines ("[Desktop Entry]" : map keyvalue d) ++ "\n" + where + keyvalue (k, v) = k ++ "=" ++ toString v + +writeDesktopMenuFile :: DesktopEntry -> String -> IO () +writeDesktopMenuFile d file = do + createDirectoryIfMissing True (parentDir file) + writeFile file $ buildDesktopMenuFile d + +userDesktopMenuFilePath :: String -> IO FilePath +userDesktopMenuFilePath basename = do + datadir <- userDataDir + return $ datadir </> "applications" </> basename + +systemDesktopMenuFilePath :: String -> FilePath +systemDesktopMenuFilePath basename = "/usr/share/applications" </> basename + +userDataDir :: IO FilePath +userDataDir = do + dir <- xdgEnv "DATA_HOME" =<< myHomeDir + return $ dir </> ".local" </> "share" + +userConfigDir :: IO FilePath +userConfigDir = do + dir <- xdgEnv "DATA_HOME" =<< myHomeDir + return $ dir </> ".config" + +xdgEnv :: String -> String -> IO String +xdgEnv envbase def = catchDefaultIO (getEnv $ "XDG_" ++ envbase) def From 9422e274897eb7581f453cb4374c326f0bf83d4f Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Wed, 1 Aug 2012 20:49:02 -0400 Subject: [PATCH 224/331] installing desktop file working Not hooked up to either Makefile or cabal yet --- Build/Desktop.hs | 34 ++++++++++++++++++++++++++++++++++ Utility/FreeDesktop.hs | 18 ++++++++++-------- 2 files changed, 44 insertions(+), 8 deletions(-) create mode 100644 Build/Desktop.hs diff --git a/Build/Desktop.hs b/Build/Desktop.hs new file mode 100644 index 0000000000..b35b0c0104 --- /dev/null +++ b/Build/Desktop.hs @@ -0,0 +1,34 @@ +{- Generating and installing a desktop menu entry file. + - + - Copyright 2012 Joey Hess <joey@kitenet.net> + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Build.Desktop where + +import Utility.Exception +import Utility.FreeDesktop + +import Control.Applicative +import System.Environment +import System.Posix.User + +{- The command can be either just "git-annex", or the full path to use + - to run it. -} +desktop :: FilePath -> DesktopEntry +desktop command = genDesktopEntry + "Git Annex" + "Track and sync the files in your Git Annex" + False + (command ++ " webapp") + ["Network", "FileTransfer"] + +writeDesktop :: DesktopEntry -> IO () +writeDesktop d = do + destdir <- catchDefaultIO (getEnv "DESTDIR") "" + uid <- fromIntegral <$> getRealUserID + dest <- if uid /= 0 + then userDesktopMenuFilePath "git-annex" + else return $ systemDesktopMenuFilePath "git-annex" + writeDesktopMenuFile d dest diff --git a/Utility/FreeDesktop.hs b/Utility/FreeDesktop.hs index ce3501766c..5e38d382d5 100644 --- a/Utility/FreeDesktop.hs +++ b/Utility/FreeDesktop.hs @@ -9,7 +9,7 @@ - Licensed under the GNU GPL version 3 or higher. -} -module Utility.DesktopMenu ( +module Utility.FreeDesktop ( DesktopEntry, genDesktopEntry, buildDesktopMenuFile, @@ -47,16 +47,14 @@ toString (ListV l) where escapesemi = join "\\;" . split ";" -genDesktopEntry :: String -> String -> Bool -> FilePath -> FilePath -> [String] -> DesktopEntry -genDesktopEntry name comment terminal program icon categories = - [ item "Encoding" StringV "UTF-8" - , item "Type" StringV "Application" +genDesktopEntry :: String -> String -> Bool -> FilePath -> [String] -> DesktopEntry +genDesktopEntry name comment terminal program categories = + [ item "Type" StringV "Application" , item "Version" NumericV 1.0 , item "Name" StringV name , item "Comment" StringV comment , item "Terminal" BoolV terminal , item "Exec" StringV program - , item "Icon" StringV icon , item "Categories" ListV (map StringV categories) ] where @@ -75,10 +73,14 @@ writeDesktopMenuFile d file = do userDesktopMenuFilePath :: String -> IO FilePath userDesktopMenuFilePath basename = do datadir <- userDataDir - return $ datadir </> "applications" </> basename + return $ datadir </> "applications" </> desktopfile basename systemDesktopMenuFilePath :: String -> FilePath -systemDesktopMenuFilePath basename = "/usr/share/applications" </> basename +systemDesktopMenuFilePath basename = + "/usr/share/applications" </> desktopfile basename + +desktopfile :: FilePath -> FilePath +desktopfile f = f ++ ".desktop" userDataDir :: IO FilePath userDataDir = do From ed07546288733a13129a866ce70ea2f94d6259cb Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Wed, 1 Aug 2012 21:04:15 -0400 Subject: [PATCH 225/331] add template-haskell build-dep for webapp --- git-annex.cabal | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/git-annex.cabal b/git-annex.cabal index afa8814253..de417a4a1e 100644 --- a/git-annex.cabal +++ b/git-annex.cabal @@ -76,7 +76,8 @@ Executable git-annex if flag(Webapp) Build-Depends: yesod, yesod-static, yesod-default, case-insensitive, http-types, transformers, wai, wai-logger, warp, blaze-builder, - blaze-html, blaze-markup, crypto-api, hamlet, clientsession + blaze-html, blaze-markup, crypto-api, hamlet, clientsession, + template-haskell CPP-Options: -DWITH_WEBAPP if os(darwin) From e78b13c42807f598d9dd7e449a5980c26f731f72 Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Wed, 1 Aug 2012 21:04:25 -0400 Subject: [PATCH 226/331] hook desktop menu file installation into makefile and cabal --- Build/{Desktop.hs => InstallDesktopFile.hs} | 7 ++++++- Makefile | 1 + Setup.hs | 8 ++++++++ 3 files changed, 15 insertions(+), 1 deletion(-) rename Build/{Desktop.hs => InstallDesktopFile.hs} (84%) diff --git a/Build/Desktop.hs b/Build/InstallDesktopFile.hs similarity index 84% rename from Build/Desktop.hs rename to Build/InstallDesktopFile.hs index b35b0c0104..b4a56a2cbd 100644 --- a/Build/Desktop.hs +++ b/Build/InstallDesktopFile.hs @@ -5,7 +5,7 @@ - Licensed under the GNU GPL version 3 or higher. -} -module Build.Desktop where +module Build.InstallDesktopFile where import Utility.Exception import Utility.FreeDesktop @@ -32,3 +32,8 @@ writeDesktop d = do then userDesktopMenuFilePath "git-annex" else return $ systemDesktopMenuFilePath "git-annex" writeDesktopMenuFile d dest + +main = getArgs >>= go + where + go [] = error "specify git-annex command" + go (command:_) = writeDesktop $ desktop command diff --git a/Makefile b/Makefile index 8eef53f30e..bd8aa4f3f6 100644 --- a/Makefile +++ b/Makefile @@ -86,6 +86,7 @@ install: all install-docs install -d $(DESTDIR)$(PREFIX)/bin install $(bins) $(DESTDIR)$(PREFIX)/bin ln -sf git-annex $(DESTDIR)$(PREFIX)/bin/git-annex-shell + runghc Build/InstallDesktopFile.hs $(PREFIX)/bin/git-annex || true test: $(sources) $(clibs) @if ! $(GHCMAKE) -O0 test $(clibs); then \ diff --git a/Setup.hs b/Setup.hs index 80d23cc878..4451e86455 100644 --- a/Setup.hs +++ b/Setup.hs @@ -10,6 +10,7 @@ import Distribution.PackageDescription (PackageDescription(..)) import Distribution.Verbosity (Verbosity) import System.FilePath +import qualified Build.InstallDesktopFile as InstallDesktopFile import qualified Build.Configure as Configure main = defaultMainWithHooks simpleUserHooks @@ -25,6 +26,7 @@ myPostInst :: Args -> InstallFlags -> PackageDescription -> LocalBuildInfo -> IO myPostInst _ (InstallFlags { installVerbosity }) pkg lbi = do installGitAnnexShell dest verbosity pkg lbi installManpages dest verbosity pkg lbi + installDesktopFile dest verbosity pkg lbi where dest = NoCopyDest verbosity = fromFlag installVerbosity @@ -47,3 +49,9 @@ installManpages copyDest verbosity pkg lbi = srcManpages = zip (repeat srcManDir) manpages srcManDir = "" manpages = ["git-annex.1", "git-annex-shell.1"] + +installDesktopFile :: CopyDest -> Verbosity -> PackageDescription -> LocalBuildInfo -> IO () +installDesktopFile copyDest verbosity pkg lbi = + InstallDesktopFile.writeDesktop $ InstallDesktopFile.desktop $ dstBinDir </> "git-annex" + where + dstBinDir = bindir $ absoluteInstallDirs pkg lbi copyDest From ffeb060002cd33b7db0fc03b1abacc7b2762b88e Mon Sep 17 00:00:00 2001 From: Joey Hess <joey@kitenet.net> Date: Wed, 1 Aug 2012 21:26:36 -0400 Subject: [PATCH 227/331] don't use hamlet for htmlshim This allows me to not build-depend on blaze-markup, which was causing me some trouble when tring to build with cabal on debian. Seems debian ships Text.Blaze.Renderer.String in two packages. --- Assistant/Threads/WebApp.hs | 26 +++++++++++++++++--------- git-annex.cabal | 2 +- templates/htmlshim.hamlet | 7 ------- 3 files changed, 18 insertions(+), 17 deletions(-) delete mode 100644 templates/htmlshim.hamlet diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index a5484b5bec..e8de408a13 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -21,16 +21,13 @@ import Assistant.ThreadedMonad import Assistant.DaemonStatus import Assistant.TransferQueue import Utility.WebApp -import Utility.Yesod import Utility.FileMode import Utility.TempFile import Git import Yesod import Yesod.Static -import Text.Hamlet import Network.Socket (PortNumber) -import Text.Blaze.Renderer.String import Data.Text (pack, unpack) thisThread :: String @@ -75,7 +72,7 @@ webAppThread mst dstatus transferqueue postfirstrun onstartup = do else dir go port webapp htmlshim = do writeHtmlShim webapp port htmlshim - maybe noop (\a -> a (myUrl webapp port) htmlshim) onstartup + maybe noop (\a -> a (myUrl webapp port "/") htmlshim) onstartup {- Creates a html shim file that's used to redirect into the webapp, - to avoid exposing the secretToken when launching the web browser. -} @@ -92,10 +89,21 @@ writeHtmlShim webapp port file = do {- TODO: generate this static file using Yesod. -} genHtmlShim :: WebApp -> PortNumber -> String -genHtmlShim webapp port = renderHtml $(shamletFile $ hamletTemplate "htmlshim") +genHtmlShim webapp port = unlines + [ "<html>" + , "<head>" + , "<title>Starting webapp..." + , "" + , "" + , "

" + , "Starting webapp..." + , "

" + , "" + , "" + ] where - url = myUrl webapp port + url = myUrl webapp port "/" -myUrl :: WebApp -> PortNumber -> Url -myUrl webapp port = "http://localhost:" ++ show port ++ - "/?auth=" ++ unpack (secretToken webapp) +myUrl :: WebApp -> PortNumber -> FilePath -> Url +myUrl webapp port page = "http://localhost:" ++ show port ++ page ++ + "?auth=" ++ unpack (secretToken webapp) diff --git a/git-annex.cabal b/git-annex.cabal index de417a4a1e..ec96bdc328 100644 --- a/git-annex.cabal +++ b/git-annex.cabal @@ -76,7 +76,7 @@ Executable git-annex if flag(Webapp) Build-Depends: yesod, yesod-static, yesod-default, case-insensitive, http-types, transformers, wai, wai-logger, warp, blaze-builder, - blaze-html, blaze-markup, crypto-api, hamlet, clientsession, + blaze-html, crypto-api, hamlet, clientsession, template-haskell CPP-Options: -DWITH_WEBAPP diff --git a/templates/htmlshim.hamlet b/templates/htmlshim.hamlet deleted file mode 100644 index 073b69c1bd..0000000000 --- a/templates/htmlshim.hamlet +++ /dev/null @@ -1,7 +0,0 @@ -$doctype 5 - - - - -

- Starting webapp... From 23fe661d37ceb6c7bf754e9dc8fd5dda89793b63 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 1 Aug 2012 23:31:53 -0400 Subject: [PATCH 228/331] install autostart file too --- Build/InstallDesktopFile.hs | 29 +++++++++++++++++++++-------- Setup.hs | 2 +- Utility/FreeDesktop.hs | 29 +++++++++++++++++++---------- 3 files changed, 41 insertions(+), 19 deletions(-) diff --git a/Build/InstallDesktopFile.hs b/Build/InstallDesktopFile.hs index b4a56a2cbd..a08743f3da 100644 --- a/Build/InstallDesktopFile.hs +++ b/Build/InstallDesktopFile.hs @@ -1,4 +1,5 @@ -{- Generating and installing a desktop menu entry file. +{- Generating and installing a desktop menu entry file + - and a desktop autostart file. - - Copyright 2012 Joey Hess - @@ -24,16 +25,28 @@ desktop command = genDesktopEntry (command ++ " webapp") ["Network", "FileTransfer"] -writeDesktop :: DesktopEntry -> IO () -writeDesktop d = do +autostart :: FilePath -> DesktopEntry +autostart command = genDesktopEntry + "Git Annex Assistant" + "Autostart" + False + (command ++ " assistant --autostart") + [] + +writeDesktop :: String -> IO () +writeDesktop command = do destdir <- catchDefaultIO (getEnv "DESTDIR") "" uid <- fromIntegral <$> getRealUserID - dest <- if uid /= 0 - then userDesktopMenuFilePath "git-annex" - else return $ systemDesktopMenuFilePath "git-annex" - writeDesktopMenuFile d dest + + datadir <- if uid /= 0 then userDataDir else return systemDataDir + writeDesktopMenuFile (desktop command) $ + desktopMenuFilePath "git-annex" datadir + + configdir <- if uid /= 0 then userConfigDir else return systemConfigDir + writeDesktopMenuFile (autostart command) $ + autoStartPath "git-annex" configdir main = getArgs >>= go where go [] = error "specify git-annex command" - go (command:_) = writeDesktop $ desktop command + go (command:_) = writeDesktop command diff --git a/Setup.hs b/Setup.hs index 4451e86455..06390975bb 100644 --- a/Setup.hs +++ b/Setup.hs @@ -52,6 +52,6 @@ installManpages copyDest verbosity pkg lbi = installDesktopFile :: CopyDest -> Verbosity -> PackageDescription -> LocalBuildInfo -> IO () installDesktopFile copyDest verbosity pkg lbi = - InstallDesktopFile.writeDesktop $ InstallDesktopFile.desktop $ dstBinDir "git-annex" + InstallDesktopFile.writeDesktop $ dstBinDir "git-annex" where dstBinDir = bindir $ absoluteInstallDirs pkg lbi copyDest diff --git a/Utility/FreeDesktop.hs b/Utility/FreeDesktop.hs index 5e38d382d5..5bab4950ab 100644 --- a/Utility/FreeDesktop.hs +++ b/Utility/FreeDesktop.hs @@ -14,8 +14,12 @@ module Utility.FreeDesktop ( genDesktopEntry, buildDesktopMenuFile, writeDesktopMenuFile, - userDesktopMenuFilePath, - systemDesktopMenuFilePath + desktopMenuFilePath, + autoStartPath, + systemDataDir, + systemConfigDir, + userDataDir, + userConfigDir ) where import Utility.Exception @@ -70,18 +74,23 @@ writeDesktopMenuFile d file = do createDirectoryIfMissing True (parentDir file) writeFile file $ buildDesktopMenuFile d -userDesktopMenuFilePath :: String -> IO FilePath -userDesktopMenuFilePath basename = do - datadir <- userDataDir - return $ datadir "applications" desktopfile basename +desktopMenuFilePath :: String -> FilePath -> FilePath +desktopMenuFilePath basename datadir = + datadir "applications" desktopfile basename -systemDesktopMenuFilePath :: String -> FilePath -systemDesktopMenuFilePath basename = - "/usr/share/applications" desktopfile basename +autoStartPath :: String -> FilePath -> FilePath +autoStartPath basename configdir = + configdir "autostart" desktopfile basename desktopfile :: FilePath -> FilePath desktopfile f = f ++ ".desktop" +systemDataDir :: FilePath +systemDataDir = "/usr/share" + +systemConfigDir :: FilePath +systemConfigDir = "/etc/xdg" + userDataDir :: IO FilePath userDataDir = do dir <- xdgEnv "DATA_HOME" =<< myHomeDir @@ -89,7 +98,7 @@ userDataDir = do userConfigDir :: IO FilePath userConfigDir = do - dir <- xdgEnv "DATA_HOME" =<< myHomeDir + dir <- xdgEnv "CONFIG_HOME" =<< myHomeDir return $ dir ".config" xdgEnv :: String -> String -> IO String From 60da0d6ad28bff7c601ba631a8ec65030f940367 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 2 Aug 2012 00:42:33 -0400 Subject: [PATCH 229/331] full autostart support git annex assistant --autostart will start separate daemons in each listed autostart repo running the webapp outside any git-annex repo will open it on the first listed autostart repo --- Assistant/WebApp/Configurators.hs | 6 +++- Build/InstallDesktopFile.hs | 4 +++ Command/Assistant.hs | 58 +++++++++++++++++++++++++++++-- Command/Watch.hs | 9 ++--- Command/WebApp.hs | 39 ++++++++++++++++----- Locations/UserConfig.hs | 26 ++++++++++++++ Utility/FreeDesktop.hs | 2 -- doc/git-annex.mdwn | 13 +++++-- 8 files changed, 134 insertions(+), 23 deletions(-) create mode 100644 Locations/UserConfig.hs diff --git a/Assistant/WebApp/Configurators.hs b/Assistant/WebApp/Configurators.hs index e1fcfcd971..01245b4bc1 100644 --- a/Assistant/WebApp/Configurators.hs +++ b/Assistant/WebApp/Configurators.hs @@ -21,6 +21,7 @@ import Init import qualified Git.Construct import qualified Git.Config import qualified Annex +import Locations.UserConfig import Yesod import Data.Text (Text) @@ -159,7 +160,10 @@ makeRepo path = do error "git init failed!" g <- Git.Config.read =<< Git.Construct.fromPath path state <- Annex.new g - Annex.eval state $ initialize $ Just "new repo" + Annex.eval state $ initialize $ Just "new repo" -- TODO better description + autostart <- autoStartFile + createDirectoryIfMissing True (parentDir autostart) + appendFile autostart $ path ++ "\n" getAddRepositoryR :: Handler RepHtml getAddRepositoryR = bootstrap (Just Config) $ do diff --git a/Build/InstallDesktopFile.hs b/Build/InstallDesktopFile.hs index a08743f3da..3bc796315a 100644 --- a/Build/InstallDesktopFile.hs +++ b/Build/InstallDesktopFile.hs @@ -46,6 +46,10 @@ writeDesktop command = do writeDesktopMenuFile (autostart command) $ autoStartPath "git-annex" configdir + programfile <- programFile + createDirectoryIfMissing True (parentDir programFile) + writeFile programfile command + main = getArgs >>= go where go [] = error "specify git-annex command" diff --git a/Command/Assistant.hs b/Command/Assistant.hs index 60eac5d219..24cc3ec6c9 100644 --- a/Command/Assistant.hs +++ b/Command/Assistant.hs @@ -7,12 +7,66 @@ module Command.Assistant where +import Common.Annex import Command +import qualified Option import qualified Command.Watch +import Init +import Locations.UserConfig + +import System.Environment +import System.Posix.Directory def :: [Command] -def = [withOptions [Command.Watch.foregroundOption, Command.Watch.stopOption] $ +def = [noRepo checkAutoStart $ dontCheck repoExists $ + withOptions [Command.Watch.foregroundOption, Command.Watch.stopOption, autoStartOption] $ command "assistant" paramNothing seek "automatically handle changes"] +autoStartOption :: Option +autoStartOption = Option.flag [] "autostart" "start in known repositories" + seek :: [CommandSeek] -seek = Command.Watch.mkSeek True +seek = [withFlag Command.Watch.stopOption $ \stopdaemon -> + withFlag Command.Watch.foregroundOption $ \foreground -> + withFlag autoStartOption $ \autostart -> + withNothing $ start foreground stopdaemon autostart] + +start :: Bool -> Bool -> Bool -> CommandStart +start foreground stopdaemon autostart + | autostart = do + liftIO $ autoStart + stop + | otherwise = do + ensureInitialized + Command.Watch.start True foreground stopdaemon + +{- Run outside a git repository. Check to see if any parameter is + - --autostart and enter autostart mode. -} +checkAutoStart :: IO () +checkAutoStart = ifM (any (== "--autostart") <$> getArgs) + ( autoStart + , error "Not in a git repository." + ) + +autoStart :: IO () +autoStart = do + autostartfile <- autoStartFile + let nothing = error $ "Nothing listed in " ++ autostartfile + ifM (doesFileExist autostartfile) + ( do + dirs <- lines <$> readFile autostartfile + programfile <- programFile + program <- catchDefaultIO (readFile programfile) "git-annex" + when (null dirs) nothing + forM_ dirs $ \d -> do + putStrLn $ "git-annex autostart in " ++ d + ifM (catchBoolIO $ go program d) + ( putStrLn "ok" + , putStrLn "failed" + ) + , nothing + ) + where + go program dir = do + changeWorkingDirectory dir + boolSystem program [Param "assistant"] diff --git a/Command/Watch.hs b/Command/Watch.hs index 61c859106f..eb70ef6b10 100644 --- a/Command/Watch.hs +++ b/Command/Watch.hs @@ -16,13 +16,10 @@ def :: [Command] def = [withOptions [foregroundOption, stopOption] $ command "watch" paramNothing seek "watch for changes"] -mkSeek :: Bool -> [CommandSeek] -mkSeek assistant = [withFlag stopOption $ \stopdaemon -> - withFlag foregroundOption $ \foreground -> - withNothing $ start assistant foreground stopdaemon] - seek :: [CommandSeek] -seek = mkSeek False +seek = [withFlag stopOption $ \stopdaemon -> + withFlag foregroundOption $ \foreground -> + withNothing $ start False foreground stopdaemon] foregroundOption :: Option foregroundOption = Option.flag [] "foreground" "do not daemonize" diff --git a/Command/WebApp.hs b/Command/WebApp.hs index f143d8667b..d3153f6304 100644 --- a/Command/WebApp.hs +++ b/Command/WebApp.hs @@ -18,12 +18,14 @@ import Utility.Daemon (checkDaemon, lockPidFile) import Init import qualified Git.CurrentRepo import qualified Annex +import Locations.UserConfig +import System.Posix.Directory import Control.Concurrent import Control.Concurrent.STM def :: [Command] -def = [oneShot $ noRepo firstRun $ dontCheck repoExists $ +def = [oneShot $ noRepo startNoRepo $ dontCheck repoExists $ command "webapp" paramNothing seek "launch webapp"] seek :: [CommandSeek] @@ -31,7 +33,7 @@ seek = [withNothing start] start :: CommandStart start = notBareRepo $ do - ifM (isInitialized) ( go , liftIO firstRun ) + ifM (isInitialized) ( go , liftIO startNoRepo ) stop where go = do @@ -46,14 +48,24 @@ start = notBareRepo $ do liftIO $ isJust <$> checkDaemon pidfile checkshim f = liftIO $ doesFileExist f -openBrowser :: FilePath -> IO () -openBrowser htmlshim = unlessM (runBrowser url) $ - error $ "failed to start web browser on url " ++ url - where - url = fileUrl htmlshim +{- When run without a repo, see if there is an autoStartFile, + - and if so, start the first available listed repository. + - If not, it's our first time being run! -} +startNoRepo :: IO () +startNoRepo = do + autostartfile <- autoStartFile + ifM (doesFileExist autostartfile) ( autoStart autostartfile , firstRun ) -fileUrl :: FilePath -> String -fileUrl file = "file://" ++ file +autoStart :: FilePath -> IO () +autoStart autostartfile = do + dirs <- lines <$> readFile autostartfile + edirs <- filterM doesDirectoryExist dirs + case edirs of + [] -> firstRun -- what else can I do? Nothing works.. + (d:_) -> do + changeWorkingDirectory d + state <- Annex.new =<< Git.CurrentRepo.get + void $ Annex.eval state $ doCommand start {- Run the webapp without a repository, which prompts the user, makes one, - changes to it, starts the regular assistant, and redirects the @@ -92,3 +104,12 @@ firstRun = do {- Set up the pid file in the new repo. -} dummydaemonize = do liftIO . lockPidFile =<< fromRepo gitAnnexPidFile + +openBrowser :: FilePath -> IO () +openBrowser htmlshim = unlessM (runBrowser url) $ + error $ "failed to start web browser on url " ++ url + where + url = fileUrl htmlshim + +fileUrl :: FilePath -> String +fileUrl file = "file://" ++ file diff --git a/Locations/UserConfig.hs b/Locations/UserConfig.hs new file mode 100644 index 0000000000..9b04aed619 --- /dev/null +++ b/Locations/UserConfig.hs @@ -0,0 +1,26 @@ +{- git-annex user config files + - + - Copyright 2012 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Locations.UserConfig where + +import Utility.FreeDesktop + +import System.FilePath + +{- ~/.config/git-annex/file -} +userConfigFile :: FilePath -> IO FilePath +userConfigFile file = do + dir <- userConfigDir + return $ dir "git-annex" file + +autoStartFile :: IO FilePath +autoStartFile = userConfigFile "autostart" + +{- The path to git-annex is written here; which is useful when cabal + - has installed it to some aweful non-PATH location. -} +programFile :: IO FilePath +programFile = userConfigFile "program" diff --git a/Utility/FreeDesktop.hs b/Utility/FreeDesktop.hs index 5bab4950ab..784473b275 100644 --- a/Utility/FreeDesktop.hs +++ b/Utility/FreeDesktop.hs @@ -23,10 +23,8 @@ module Utility.FreeDesktop ( ) where import Utility.Exception -import Utility.Directory import Utility.Path -import System.IO import System.Environment import System.Directory import System.FilePath diff --git a/doc/git-annex.mdwn b/doc/git-annex.mdwn index 0a6df035be..6a1c70a4c3 100644 --- a/doc/git-annex.mdwn +++ b/doc/git-annex.mdwn @@ -809,10 +809,17 @@ For example, this makes two copies be needed for wav files: # FILES -These files are used by git-annex, in your git repository: +These files are used by git-annex: -`.git/annex/objects/` contains the annexed file contents that are currently -available. Annexed files in your git repository symlink to that content. +`.git/annex/objects/` in your git repository contains the annexed file +contents that are currently available. Annexed files in your git +repository symlink to that content. + +`.git/annex/` in your git repository contains other run-time information +used by git-annex. + +`~/.config/git-annex/autostart` is a list of git repositories +to start the git-annex assistant in. # SEE ALSO From adf5789c1b6c80549d28284834b91a1cbddc90c9 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 2 Aug 2012 07:47:20 -0400 Subject: [PATCH 230/331] fix bugs, add desktop dir --- Utility/FreeDesktop.hs | 29 ++++++++++++++++++++--------- 1 file changed, 20 insertions(+), 9 deletions(-) diff --git a/Utility/FreeDesktop.hs b/Utility/FreeDesktop.hs index 784473b275..f2168077a9 100644 --- a/Utility/FreeDesktop.hs +++ b/Utility/FreeDesktop.hs @@ -19,7 +19,8 @@ module Utility.FreeDesktop ( systemDataDir, systemConfigDir, userDataDir, - userConfigDir + userConfigDir, + userDesktopDir ) where import Utility.Exception @@ -72,10 +73,14 @@ writeDesktopMenuFile d file = do createDirectoryIfMissing True (parentDir file) writeFile file $ buildDesktopMenuFile d +{- Path to use for a desktop menu file, in either the systemDataDir or + - the userDataDir -} desktopMenuFilePath :: String -> FilePath -> FilePath desktopMenuFilePath basename datadir = datadir "applications" desktopfile basename +{- Path to use for a desktop autostart file, in either the systemDataDir + - or the userDataDir -} autoStartPath :: String -> FilePath -> FilePath autoStartPath basename configdir = configdir "autostart" desktopfile basename @@ -83,21 +88,27 @@ autoStartPath basename configdir = desktopfile :: FilePath -> FilePath desktopfile f = f ++ ".desktop" +{- Directory used for installation of system wide data files.. -} systemDataDir :: FilePath systemDataDir = "/usr/share" +{- Directory used for installation of system wide config files. -} systemConfigDir :: FilePath systemConfigDir = "/etc/xdg" +{- Directory for user data files. -} userDataDir :: IO FilePath -userDataDir = do - dir <- xdgEnv "DATA_HOME" =<< myHomeDir - return $ dir ".local" "share" +userDataDir = xdgEnvHome "DATA_HOME" ".local/share" +{- Directory for user config files. -} userConfigDir :: IO FilePath -userConfigDir = do - dir <- xdgEnv "CONFIG_HOME" =<< myHomeDir - return $ dir ".config" +userConfigDir = xdgEnvHome "CONFIG_HOME" ".config" -xdgEnv :: String -> String -> IO String -xdgEnv envbase def = catchDefaultIO (getEnv $ "XDG_" ++ envbase) def +{- Directory for the user's Desktop, may be localized. -} +userDesktopDir :: IO FilePath +userDesktopDir = xdgEnvHome "DESKTOP_DIR" "Desktop" + +xdgEnvHome :: String -> String -> IO String +xdgEnvHome envbase homedef = do + home <- myHomeDir + catchDefaultIO (getEnv $ "XDG_" ++ envbase) (home homedef) From 112ce4f49c95022d1afe83bd31f4af35a01f877c Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 2 Aug 2012 07:47:39 -0400 Subject: [PATCH 231/331] support XDG_DATA_DIR --- Assistant/WebApp/Configurators.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/Assistant/WebApp/Configurators.hs b/Assistant/WebApp/Configurators.hs index 01245b4bc1..1c7ea7cf41 100644 --- a/Assistant/WebApp/Configurators.hs +++ b/Assistant/WebApp/Configurators.hs @@ -111,8 +111,10 @@ defaultRepositoryPath firstrun = do cwd <- liftIO $ getCurrentDirectory home <- myHomeDir if home == cwd && firstrun - then ifM (doesDirectoryExist $ home "Desktop") - (return "~/Desktop/annex", return "~/annex") + then do + desktop <- userDesktopDir + ifM (doesDirectoryExist desktop) + (relHome (desktop "annex"), return "~/annex") else return cwd addRepositoryForm :: Form RepositoryPath From 9a038b4a9b62824646bf4e876ed9017a1128aa56 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 2 Aug 2012 07:47:50 -0400 Subject: [PATCH 232/331] better ~/ handling --- Assistant/Threads/WebApp.hs | 9 +++------ Assistant/WebApp/Configurators.hs | 1 + Utility/Path.hs | 8 ++++++++ 3 files changed, 12 insertions(+), 6 deletions(-) diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs index e8de408a13..7ea7314e0f 100644 --- a/Assistant/Threads/WebApp.hs +++ b/Assistant/Threads/WebApp.hs @@ -64,12 +64,9 @@ webAppThread mst dstatus transferqueue postfirstrun onstartup = do Just st -> go port webapp =<< runThreadState st (fromRepo gitAnnexHtmlShim) where getreldir Nothing = return Nothing - getreldir (Just st) = do - dir <- absPath =<< runThreadState st (fromRepo repoPath) - home <- myHomeDir - return $ Just $ if dirContains home dir - then relPathDirToFile home dir - else dir + getreldir (Just st) = Just <$> + (relHome =<< absPath + =<< runThreadState st (fromRepo repoPath)) go port webapp htmlshim = do writeHtmlShim webapp port htmlshim maybe noop (\a -> a (myUrl webapp port "/") htmlshim) onstartup diff --git a/Assistant/WebApp/Configurators.hs b/Assistant/WebApp/Configurators.hs index 1c7ea7cf41..08a1f60d3e 100644 --- a/Assistant/WebApp/Configurators.hs +++ b/Assistant/WebApp/Configurators.hs @@ -22,6 +22,7 @@ import qualified Git.Construct import qualified Git.Config import qualified Annex import Locations.UserConfig +import Utility.FreeDesktop import Yesod import Data.Text (Text) diff --git a/Utility/Path.hs b/Utility/Path.hs index 76fbc6c4a4..209ff1b0f2 100644 --- a/Utility/Path.hs +++ b/Utility/Path.hs @@ -132,6 +132,14 @@ runPreserveOrder a files = preserveOrder files <$> a files myHomeDir :: IO FilePath myHomeDir = homeDirectory <$> (getUserEntryForID =<< getEffectiveUserID) +{- Converts paths in the home directory to use ~/ -} +relHome :: FilePath -> IO String +relHome path = do + home <- myHomeDir + return $ if dirContains home path + then "~/" ++ relPathDirToFile home path + else path + {- Checks if a command is available in PATH. -} inPath :: String -> IO Bool inPath command = getSearchPath >>= anyM indir From 22d7447cede9b8eb43ab552700092b74726e8c60 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 2 Aug 2012 07:55:10 -0400 Subject: [PATCH 233/331] fix tilde expansion --- Assistant/WebApp/Configurators.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Assistant/WebApp/Configurators.hs b/Assistant/WebApp/Configurators.hs index 08a1f60d3e..9c308dee14 100644 --- a/Assistant/WebApp/Configurators.hs +++ b/Assistant/WebApp/Configurators.hs @@ -100,7 +100,7 @@ checkRepositoryPath p = do tocheck <- ifM (doesDirectoryExist path) (return path, return $ parentDir path) not <$> (catchBoolIO $ fileAccess tocheck False True False) - expandTilde home ('~':path) = home path + expandTilde home ('~':'/':path) = home path expandTilde _ path = path {- On first run, if run in the home directory, default to putting it in From 3695cab949ccd6096f3ce1c121a909416851462c Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 2 Aug 2012 09:00:13 -0400 Subject: [PATCH 234/331] avoid showing alert when there are no remotes to push to --- Assistant/Threads/Pusher.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/Assistant/Threads/Pusher.hs b/Assistant/Threads/Pusher.hs index 3fe85673bc..ab0274db1d 100644 --- a/Assistant/Threads/Pusher.hs +++ b/Assistant/Threads/Pusher.hs @@ -54,8 +54,9 @@ pushThread st dstatus commitchan pushmap = do if shouldPush now commits then do remotes <- knownRemotes <$> getDaemonStatus dstatus - void $ alertWhile dstatus (pushAlert remotes) $ - pushToRemotes thisThread now st (Just pushmap) remotes + unless (null remotes) $ + void $ alertWhile dstatus (pushAlert remotes) $ + pushToRemotes thisThread now st (Just pushmap) remotes else do debug thisThread [ "delaying push of" From 191ee3b697cfefd4061c2a398b4c6a021895bacd Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 2 Aug 2012 09:03:04 -0400 Subject: [PATCH 235/331] awesome alert combining Now an alert tracks files that have recently been added. As a large file is added, it will have its own alert, that then combines with the tracker when dones. Also used for combining sanity checker alerts, as it could possibly want to display a lot. --- Assistant/Alert.hs | 72 +++++++++++++++++++++++++++++----- Assistant/Threads/Committer.hs | 16 ++++---- 2 files changed, 72 insertions(+), 16 deletions(-) diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs index 0412dfe519..5877ba069c 100644 --- a/Assistant/Alert.hs +++ b/Assistant/Alert.hs @@ -27,6 +27,15 @@ data AlertPriority = Filler | Low | Medium | High | Pinned {- An alert can be a simple message, or an arbitrary Yesod Widget. -} data AlertMessage = StringAlert String | WidgetAlert (Alert -> Widget) +{- An alert can have an name, which is used to combine it with other similar + - alerts. -} +data AlertName = AddFileAlert | DownloadFailedAlert | SanityCheckFixAlert + deriving (Eq) + +{- The first alert is the new alert, the second is an old alert. + - Should return a modified version of the old alert. -} +type AlertCombiner = Maybe (Alert -> Alert -> Maybe Alert) + data Alert = Alert { alertClass :: AlertClass , alertHeader :: Maybe String @@ -35,6 +44,8 @@ data Alert = Alert , alertClosable :: Bool , alertPriority :: AlertPriority , alertIcon :: Maybe String + , alertCombiner :: AlertCombiner + , alertName :: Maybe AlertName } type AlertPair = (AlertId, Alert) @@ -123,17 +134,21 @@ isFiller alert = alertPriority alert == Filler {- Converts a given alert into filler, manipulating it in the AlertMap. - - - Any old filler that looks the same as the reference alert is removed. + - Any old filler that looks the same as the reference alert is removed, + - or, if the input alert has an alertCombine that combines it with + - old filler, the old filler is replaced with the result, and the + - input alert is removed. - - Old filler alerts are pruned once maxAlerts is reached. -} convertToFiller :: AlertId -> Bool -> AlertMap -> AlertMap convertToFiller i success m = case M.lookup i m of Nothing -> m - Just al -> + Just al -> let al' = makeAlertFiller success al - in pruneBloat $ M.filterWithKey (pruneSame al') $ - M.insertWith' const i al' m + in case alertCombiner al' of + Nothing -> updatePrune al' + Just combiner -> updateCombine combiner al' where pruneSame ref k al = k == i || not (effectivelySameAlert ref al) pruneBloat m' @@ -144,6 +159,13 @@ convertToFiller i success m = case M.lookup i m of pruneold l = let (f, rest) = partition (\(_, al) -> isFiller al) l in drop bloat f ++ rest + updatePrune al = pruneBloat $ M.filterWithKey (pruneSame al) $ + M.insertWith' const i al m + updateCombine combiner al = + let combined = M.mapMaybe (combiner al) m + in if M.null combined + then updatePrune al + else M.delete i $ M.union combined m baseActivityAlert :: Alert baseActivityAlert = Alert @@ -154,6 +176,8 @@ baseActivityAlert = Alert , alertClosable = False , alertPriority = Medium , alertIcon = Just "refresh" + , alertCombiner = Nothing + , alertName = Nothing } activityAlert :: Maybe String -> String -> Alert @@ -203,13 +227,43 @@ sanityCheckFixAlert :: String -> Alert sanityCheckFixAlert msg = Alert { alertClass = Warning , alertHeader = Just "Fixed a problem" - , alertMessage = StringAlert $ unwords - [ "The daily sanity check found and fixed a problem:" - , msg - , "If these problems persist, consider filing a bug report." - ] + , alertMessage = StringAlert $ unlines [ alerthead, msg, alertfoot ] , alertBlockDisplay = True , alertPriority = High , alertClosable = True , alertIcon = Just "exclamation-sign" + , alertName = Just SanityCheckFixAlert + , alertCombiner = messageCombiner combinemessage } + where + alerthead = "The daily sanity check found and fixed a problem:" + alertfoot = "If these problems persist, consider filing a bug report." + combinemessage (StringAlert new) (StringAlert old) = + let newmsg = filter (/= alerthead) $ + filter (/= alertfoot) $ + lines old ++ lines new + in Just $ StringAlert $ + unlines $ alerthead : newmsg ++ [alertfoot] + combinemessage _ _ = Nothing + +addFileAlert :: FilePath -> Alert +addFileAlert file = (activityAlert (Just "Added") $ takeFileName file) + { alertName = Just AddFileAlert + , alertCombiner = messageCombiner combinemessage + } + where + combinemessage (StringAlert new) (StringAlert old) = + Just $ StringAlert $ + unlines $ take 10 $ new : lines old + combinemessage _ _ = Nothing + +messageCombiner :: (AlertMessage -> AlertMessage -> Maybe AlertMessage) -> AlertCombiner +messageCombiner combinemessage = Just go + where + go new old + | alertClass new /= alertClass old = Nothing + | alertName new == alertName old = + case combinemessage (alertMessage new) (alertMessage old) of + Nothing -> Nothing + Just m -> Just $ old { alertMessage = m } + | otherwise = Nothing diff --git a/Assistant/Threads/Committer.hs b/Assistant/Threads/Committer.hs index f236159f98..2ca6a15b93 100644 --- a/Assistant/Threads/Committer.hs +++ b/Assistant/Threads/Committer.hs @@ -10,6 +10,7 @@ module Assistant.Threads.Committer where import Assistant.Common import Assistant.Changes import Assistant.Commits +import Assistant.Alert import Assistant.ThreadedMonad import Assistant.Threads.Watcher import Assistant.TransferQueue @@ -143,15 +144,16 @@ handleAdds st changechan transferqueue dstatus cs = returnWhen (null pendingadds add :: Change -> IO (Maybe Change) add change@(PendingAddChange { keySource = ks }) = - liftM maybeMaybe $ catchMaybeIO $ - sanitycheck ks $ runThreadState st $ do - showStart "add" $ keyFilename ks - key <- Command.Add.ingest ks - handle (finishedChange change) (keyFilename ks) key + alertWhile' dstatus (addFileAlert $ keyFilename ks) $ + liftM maybeMaybe $ catchMaybeIO $ + sanitycheck ks $ runThreadState st $ do + showStart "add" $ keyFilename ks + key <- Command.Add.ingest ks + handle (finishedChange change) (keyFilename ks) key add _ = return Nothing - maybeMaybe (Just j@(Just _)) = j - maybeMaybe _ = Nothing + maybeMaybe (Just j@(Just _)) = (True, j) + maybeMaybe _ = (False, Nothing) handle _ _ Nothing = do showEndFail From 7cc5fdbd7b25a32c1e5786abbd419c845711d9d5 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 2 Aug 2012 09:08:58 -0400 Subject: [PATCH 236/331] layout --- templates/sidebar/alert.hamlet | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/templates/sidebar/alert.hamlet b/templates/sidebar/alert.hamlet index 84126c3810..9c204402bc 100644 --- a/templates/sidebar/alert.hamlet +++ b/templates/sidebar/alert.hamlet @@ -7,7 +7,7 @@ # $maybe h <- heading $if block -

#{h}

+

#{h}

# $else - #{h} + #{h} # ^{widget} From 520a0463a7172314298db0ce507fa355dc1238a3 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 2 Aug 2012 09:09:06 -0400 Subject: [PATCH 237/331] start webapp thread earlier so it opens ASAP --- Assistant.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/Assistant.hs b/Assistant.hs index 6af6c6639e..b81806ff9c 100644 --- a/Assistant.hs +++ b/Assistant.hs @@ -154,6 +154,9 @@ startAssistant assistant daemonize webappwaiter = do scanremotes <- newScanRemoteMap mapM_ startthread [ watch $ commitThread st changechan commitchan transferqueue dstatus +#ifdef WITH_WEBAPP + , assist $ webAppThread (Just st) dstatus transferqueue Nothing webappwaiter +#endif , assist $ pushThread st dstatus commitchan pushmap , assist $ pushRetryThread st dstatus pushmap , assist $ mergeThread st @@ -163,9 +166,6 @@ startAssistant assistant daemonize webappwaiter = do , assist $ sanityCheckerThread st dstatus transferqueue changechan , assist $ mountWatcherThread st dstatus scanremotes , assist $ transferScannerThread st dstatus scanremotes transferqueue -#ifdef WITH_WEBAPP - , assist $ webAppThread (Just st) dstatus transferqueue Nothing webappwaiter -#endif , watch $ watchThread st dstatus transferqueue changechan ] waitForTermination From 1f2127c520b48e35a5fb335c9e711559733dfd23 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 2 Aug 2012 09:15:08 -0400 Subject: [PATCH 238/331] trim long filenames (have to fit on the sidebar) 30 characters would mostly work, but 20 is safer due to some wider letters like 'w'. Of course this is very heuristic based on filesize anyway. (Bootstrap does a surprisingly bad job at dealing with overlong words in the sidebar.) --- Assistant/Alert.hs | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs index 5877ba069c..6b32fde1d9 100644 --- a/Assistant/Alert.hs +++ b/Assistant/Alert.hs @@ -247,11 +247,18 @@ sanityCheckFixAlert msg = Alert combinemessage _ _ = Nothing addFileAlert :: FilePath -> Alert -addFileAlert file = (activityAlert (Just "Added") $ takeFileName file) +addFileAlert file = (activityAlert (Just "Added") $ trim $ takeFileName file) { alertName = Just AddFileAlert , alertCombiner = messageCombiner combinemessage } where + trim f + | len < maxlen = f + | otherwise = take half f ++ ".." ++ drop (len - half) f + where + len = length f + maxlen = 20 + half = (maxlen - 2) `div` 2 combinemessage (StringAlert new) (StringAlert old) = Just $ StringAlert $ unlines $ take 10 $ new : lines old From d2b48cacdbb192e7501985e93e60b64fa57fa72d Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 2 Aug 2012 09:20:21 -0400 Subject: [PATCH 239/331] add some strictness annotations on general principles --- Assistant/Alert.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs index 6b32fde1d9..b234d2a5a5 100644 --- a/Assistant/Alert.hs +++ b/Assistant/Alert.hs @@ -5,7 +5,7 @@ - Licensed under the GNU GPL version 3 or higher. -} -{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE RankNTypes, BangPatterns #-} module Assistant.Alert where @@ -272,5 +272,5 @@ messageCombiner combinemessage = Just go | alertName new == alertName old = case combinemessage (alertMessage new) (alertMessage old) of Nothing -> Nothing - Just m -> Just $ old { alertMessage = m } + Just !m -> Just $! old { alertMessage = m } | otherwise = Nothing From 6b38227bad8c303470a5b29f50360cea0206d9a1 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 2 Aug 2012 13:12:36 -0400 Subject: [PATCH 240/331] only write data file when installing as normal user --- Build/InstallDesktopFile.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/Build/InstallDesktopFile.hs b/Build/InstallDesktopFile.hs index 3bc796315a..ab2773bf11 100644 --- a/Build/InstallDesktopFile.hs +++ b/Build/InstallDesktopFile.hs @@ -46,9 +46,10 @@ writeDesktop command = do writeDesktopMenuFile (autostart command) $ autoStartPath "git-annex" configdir - programfile <- programFile - createDirectoryIfMissing True (parentDir programFile) - writeFile programfile command + when (uid /= 0) $ do + programfile <- programFile + createDirectoryIfMissing True (parentDir programFile) + writeFile programfile command main = getArgs >>= go where From d2f975944380aab57047a9e84af620e15464fa15 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 2 Aug 2012 13:47:26 -0400 Subject: [PATCH 241/331] refactor --- Assistant/Alert.hs | 19 +++++++++++-------- 1 file changed, 11 insertions(+), 8 deletions(-) diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs index b234d2a5a5..16ce222ad5 100644 --- a/Assistant/Alert.hs +++ b/Assistant/Alert.hs @@ -247,18 +247,11 @@ sanityCheckFixAlert msg = Alert combinemessage _ _ = Nothing addFileAlert :: FilePath -> Alert -addFileAlert file = (activityAlert (Just "Added") $ trim $ takeFileName file) +addFileAlert file = (activityAlert (Just "Added") $ shortFile $ takeFileName file) { alertName = Just AddFileAlert , alertCombiner = messageCombiner combinemessage } where - trim f - | len < maxlen = f - | otherwise = take half f ++ ".." ++ drop (len - half) f - where - len = length f - maxlen = 20 - half = (maxlen - 2) `div` 2 combinemessage (StringAlert new) (StringAlert old) = Just $ StringAlert $ unlines $ take 10 $ new : lines old @@ -274,3 +267,13 @@ messageCombiner combinemessage = Just go Nothing -> Nothing Just !m -> Just $! old { alertMessage = m } | otherwise = Nothing + +shortFile :: FilePath -> String +shortFile f + | len < maxlen = f + | otherwise = take half f ++ ".." ++ drop (len - half) f + where + len = length f + maxlen = 20 + half = (maxlen - 2) `div` 2 + From a6e4283fed739207e3fd5a239ec71f7a71789259 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 2 Aug 2012 13:55:38 -0400 Subject: [PATCH 242/331] add slight delay in between sidebar updates, to avoid excessive churn Tested and 0.01 seconds is not perceivable as a delay when interacting with the UI. --- Assistant/WebApp/SideBar.hs | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/Assistant/WebApp/SideBar.hs b/Assistant/WebApp/SideBar.hs index a4b8378979..4373b5a5b0 100644 --- a/Assistant/WebApp/SideBar.hs +++ b/Assistant/WebApp/SideBar.hs @@ -20,6 +20,7 @@ import Utility.Yesod import Yesod import Data.Text (Text) import qualified Data.Map as M +import Control.Concurrent sideBarDisplay :: Widget sideBarDisplay = do @@ -75,6 +76,13 @@ getSideBarR :: NotificationId -> Handler RepHtml getSideBarR nid = do waitNotifier alertNotifier nid + {- This 0.1 second delay avoids very transient notifications from + - being displayed and churning the sidebar unnecesarily. + - + - This needs to be below the level perceptable by the user, + - to avoid slowing down user actions like closing alerts. -} + liftIO $ threadDelay 100000 + page <- widgetToPageContent sideBarDisplay hamletToRepHtml $ [hamlet|^{pageBody page}|] From e21a32627fc600e6f7fa72929c95cfb49390dae3 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 2 Aug 2012 13:57:34 -0400 Subject: [PATCH 243/331] avoid bogus alert errors --- Assistant/Threads/Committer.hs | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/Assistant/Threads/Committer.hs b/Assistant/Threads/Committer.hs index 2ca6a15b93..cce8d5e2b6 100644 --- a/Assistant/Threads/Committer.hs +++ b/Assistant/Threads/Committer.hs @@ -145,16 +145,19 @@ handleAdds st changechan transferqueue dstatus cs = returnWhen (null pendingadds add :: Change -> IO (Maybe Change) add change@(PendingAddChange { keySource = ks }) = alertWhile' dstatus (addFileAlert $ keyFilename ks) $ - liftM maybeMaybe $ catchMaybeIO $ + liftM ret $ catchMaybeIO $ sanitycheck ks $ runThreadState st $ do showStart "add" $ keyFilename ks key <- Command.Add.ingest ks handle (finishedChange change) (keyFilename ks) key + where + {- Add errors tend to be transient and will + - be automatically dealt with, so don't + - pass to the alert code. -} + ret (Just j@(Just _)) = (True, j) + ret _ = (True, Nothing) add _ = return Nothing - maybeMaybe (Just j@(Just _)) = (True, j) - maybeMaybe _ = (False, Nothing) - handle _ _ Nothing = do showEndFail return Nothing From 74fc9fcbe68ce7802d44499e8b5dc5c5d186ee66 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 2 Aug 2012 14:02:35 -0400 Subject: [PATCH 244/331] add alert when committing --- Assistant/Alert.hs | 3 +++ Assistant/Threads/Committer.hs | 4 +++- 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs index 16ce222ad5..b152c48dca 100644 --- a/Assistant/Alert.hs +++ b/Assistant/Alert.hs @@ -189,6 +189,9 @@ activityAlert header message = baseActivityAlert startupScanAlert :: Alert startupScanAlert = activityAlert Nothing "Performing startup scan" +commitAlert :: Alert +commitAlert = activityAlert Nothing "Committing changes to git" + pushAlert :: [Remote] -> Alert pushAlert rs = activityAlert Nothing $ "Syncing with " ++ unwords (map Remote.name rs) diff --git a/Assistant/Threads/Committer.hs b/Assistant/Threads/Committer.hs index cce8d5e2b6..095c8feac0 100644 --- a/Assistant/Threads/Committer.hs +++ b/Assistant/Threads/Committer.hs @@ -54,7 +54,9 @@ commitThread st changechan commitchan transferqueue dstatus = runEvery (Seconds , show (length readychanges) , "changes" ] - void $ tryIO $ runThreadState st commitStaged + void $ alertWhile dstatus commitAlert $ + tryIO (runThreadState st commitStaged) + >> return True recordCommit commitchan (Commit time) else refill readychanges else refill changes From e11946796d05a733290a47e9cead0b2a2e58d272 Mon Sep 17 00:00:00 2001 From: Nicolas Pouillard Date: Thu, 2 Aug 2012 20:11:41 +0200 Subject: [PATCH 245/331] Fix imports and casing in Build.InstallDesktopFile --- Build/InstallDesktopFile.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/Build/InstallDesktopFile.hs b/Build/InstallDesktopFile.hs index ab2773bf11..891431ebe2 100644 --- a/Build/InstallDesktopFile.hs +++ b/Build/InstallDesktopFile.hs @@ -10,8 +10,12 @@ module Build.InstallDesktopFile where import Utility.Exception import Utility.FreeDesktop +import Utility.Path +import Locations.UserConfig import Control.Applicative +import Control.Monad +import System.Directory import System.Environment import System.Posix.User @@ -48,7 +52,7 @@ writeDesktop command = do when (uid /= 0) $ do programfile <- programFile - createDirectoryIfMissing True (parentDir programFile) + createDirectoryIfMissing True (parentDir programfile) writeFile programfile command main = getArgs >>= go From 13a7362a1a6264689519a8aa685c908ec5660129 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Thu, 2 Aug 2012 23:51:38 -0400 Subject: [PATCH 246/331] fix xdg desktop dir lookup code had to use xdg-user-dir to query it, since it's in a shell format file. Fall back to --- Utility/FreeDesktop.hs | 17 +++++++++++++++-- 1 file changed, 15 insertions(+), 2 deletions(-) diff --git a/Utility/FreeDesktop.hs b/Utility/FreeDesktop.hs index f2168077a9..434537a6d2 100644 --- a/Utility/FreeDesktop.hs +++ b/Utility/FreeDesktop.hs @@ -25,12 +25,16 @@ module Utility.FreeDesktop ( import Utility.Exception import Utility.Path +import Utility.Process +import Utility.PartialPrelude import System.Environment import System.Directory import System.FilePath import Data.List import Data.String.Utils +import Control.Applicative +import Control.Monad (liftM) type DesktopEntry = [(Key, Value)] @@ -104,9 +108,18 @@ userDataDir = xdgEnvHome "DATA_HOME" ".local/share" userConfigDir :: IO FilePath userConfigDir = xdgEnvHome "CONFIG_HOME" ".config" -{- Directory for the user's Desktop, may be localized. -} +{- Directory for the user's Desktop, may be localized. + - + - This is not looked up very fast; the config file is in a shell format + - that is best parsed by shell, so xdg-user-dir is used, with a fallback + - to ~/Desktop. -} userDesktopDir :: IO FilePath -userDesktopDir = xdgEnvHome "DESKTOP_DIR" "Desktop" +userDesktopDir = maybe fallback return =<< (parse <$> xdg_user_dir) + where + parse = maybe Nothing (headMaybe . lines) + xdg_user_dir = catchMaybeIO $ + readProcess "xdg-user-dir" ["DESKTOP"] + fallback = xdgEnvHome "DESKTOP_DIR" "Desktop" xdgEnvHome :: String -> String -> IO String xdgEnvHome envbase homedef = do From 1f89712e6b0a601f3a4685cfbcd4cb5d3180c0e5 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 3 Aug 2012 09:44:43 -0400 Subject: [PATCH 247/331] add a navbar button that opens the repo in the desktop's native file browser This should work on linux (xdg-open) and OSX (open). If the program is not in $PATH, it falls back to opening a browser window/tab with file:/// The only tricky bit is the javascript code, that handles clicking on the link. This is to avoid unnecessary page refreshes. Until I added the return false at the end, the
's normal click event also fired, so two file browsers opened. I have not checked portability extensively. --- Assistant/WebApp.hs | 2 +- Assistant/WebApp/DashBoard.hs | 37 ++++++++++++++++++++++++++++++++++- Assistant/WebApp/routes | 1 + templates/page.hamlet | 3 +++ 4 files changed, 41 insertions(+), 2 deletions(-) diff --git a/Assistant/WebApp.hs b/Assistant/WebApp.hs index 1b767c642d..4042d410e0 100644 --- a/Assistant/WebApp.hs +++ b/Assistant/WebApp.hs @@ -63,7 +63,7 @@ selectNavBar :: Handler [NavBarItem] selectNavBar = ifM (inFirstRun) (return firstRunNavBar, return defaultNavBar) inFirstRun :: Handler Bool -inFirstRun = isNothing . threadState <$> getYesod +inFirstRun = isNothing . relDir <$> getYesod {- Used instead of defaultContent; highlights the current page if it's - on the navbar. -} diff --git a/Assistant/WebApp/DashBoard.hs b/Assistant/WebApp/DashBoard.hs index f4f56a4763..a1e499d702 100644 --- a/Assistant/WebApp/DashBoard.hs +++ b/Assistant/WebApp/DashBoard.hs @@ -5,7 +5,7 @@ - Licensed under the GNU GPL version 3 or higher. -} -{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-} +{-# LANGUAGE CPP, TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-} module Assistant.WebApp.DashBoard where @@ -23,6 +23,7 @@ import Utility.Percentage import Utility.DataUnits import Types.Key import qualified Remote +import qualified Git import Yesod import Text.Hamlet @@ -88,3 +89,37 @@ getNoScriptAutoR = bootstrap (Just DashBoard) $ do let this = NoScriptAutoR toWidgetHead $(hamletFile $ hamletTemplate "dashboard/metarefresh") dashboard False + +{- The javascript code does a post. -} +postFileBrowserR :: Handler () +postFileBrowserR = void openFileBrowser + +{- Used by non-javascript browsers, where clicking on the link actually + - opens this page, so we redirect back to the referrer. -} +getFileBrowserR :: Handler () +getFileBrowserR = whenM openFileBrowser $ do + clearUltDest + setUltDestReferer + redirectUltDest HomeR + +{- Opens the system file browser on the repo, or, as a fallback, + - goes to a file:// url. Returns True if it's ok to redirect away + - from the page (ie, the system file browser was opened). -} +openFileBrowser :: Handler Bool +openFileBrowser = do + path <- runAnnex (error "no configured repository") $ + fromRepo Git.repoPath + ifM (liftIO $ inPath cmd <&&> boolSystem cmd [File path]) + ( return True + , do + clearUltDest + setUltDest $ "file://" ++ path + void $ redirectUltDest HomeR + return False + ) + where +#if OSX + cmd = "open" +#else + cmd = "xdg-open" +#endif diff --git a/Assistant/WebApp/routes b/Assistant/WebApp/routes index 95813edb6f..192e1cd6ba 100644 --- a/Assistant/WebApp/routes +++ b/Assistant/WebApp/routes @@ -11,5 +11,6 @@ /notifier/transfers NotifierTransfersR GET /notifier/sidebar NotifierSideBarR GET /closealert/#AlertId CloseAlert GET +/filebrowser FileBrowserR GET POST /static StaticR Static getStatic diff --git a/templates/page.hamlet b/templates/page.hamlet index 29a091110a..6321f7a181 100644 --- a/templates/page.hamlet +++ b/templates/page.hamlet @@ -9,6 +9,9 @@ #{name} $maybe reldir <- relDir webapp