yesod-bin-1.2.4.1/ 0000755 0000000 0000000 00000000000 12241220146 011726 5 ustar 00 0000000 0000000 yesod-bin-1.2.4.1/refreshing.html 0000644 0000000 0000000 00000003255 12241220146 014755 0 ustar 00 0000000 0000000
Refreshing - Yesod devel
The application isn’t built
We’ll keep trying to refresh every second
Meanwhile, here are some motivational messages:
- You are a beautiful person making a beautiful web site.
- Keep going, you’ve nearly fixed the bug!
- Check your posture, don’t lean over too much.
- Get a glass of water, keep hydrated.
yesod-bin-1.2.4.1/Keter.hs 0000644 0000000 0000000 00000004121 12241220146 013332 0 ustar 00 0000000 0000000 {-# LANGUAGE OverloadedStrings #-}
module Keter
( keter
) where
import Data.Yaml
import qualified Data.HashMap.Strict as Map
import qualified Data.Text as T
import System.Exit
import System.Cmd
import Control.Monad
import System.Directory
import Data.Maybe (mapMaybe)
import qualified Filesystem.Path.CurrentOS as F
import qualified Filesystem as F
import qualified Codec.Archive.Tar as Tar
import Control.Exception
import qualified Data.ByteString.Lazy as L
import Codec.Compression.GZip (compress)
run :: String -> [String] -> IO ()
run a b = do
ec <- rawSystem a b
unless (ec == ExitSuccess) $ exitWith ec
keter :: String -- ^ cabal command
-> Bool -- ^ no build?
-> IO ()
keter cabal noBuild = do
mvalue <- decodeFile "config/keter.yaml"
value <-
case mvalue of
Nothing -> error "No config/keter.yaml found"
Just (Object value) ->
case Map.lookup "host" value of
Just (String s) | "<<" `T.isPrefixOf` s ->
error "Please set your hostname in config/keter.yaml"
_ -> return value
Just _ -> error "config/keter.yaml is not an object"
files <- getDirectoryContents "."
project <-
case mapMaybe (T.stripSuffix ".cabal" . T.pack) files of
[x] -> return x
[] -> error "No cabal file found"
_ -> error "Too many cabal files found"
exec <-
case Map.lookup "exec" value of
Just (String s) -> return $ F.collapse $ "config" F.> F.fromText s
_ -> error "exec not found in config/keter.yaml"
unless noBuild $ do
run cabal ["clean"]
run cabal ["configure"]
run cabal ["build"]
_ <- try' $ F.removeTree "static/tmp"
archive <- Tar.pack "" [F.encodeString exec, "config", "static"]
let fp = T.unpack project ++ ".keter"
L.writeFile fp $ compress $ Tar.write archive
case Map.lookup "copy-to" value of
Just (String s) -> run "scp" [fp, T.unpack s]
_ -> return ()
try' :: IO a -> IO (Either SomeException a)
try' = try
yesod-bin-1.2.4.1/yesod-bin.cabal 0000644 0000000 0000000 00000010035 12241220146 014602 0 ustar 00 0000000 0000000 name: yesod-bin
version: 1.2.4.1
license: MIT
license-file: LICENSE
author: Michael Snoyman
maintainer: Michael Snoyman
synopsis: The yesod helper executable.
description: Provides scaffolding, devel server, and some simple code generation helpers.
category: Web, Yesod
stability: Stable
cabal-version: >= 1.6
build-type: Simple
homepage: http://www.yesodweb.com/
data-files: refreshing.html
extra-source-files:
input/*.cg
hsfiles/mongo.hsfiles
hsfiles/mysql.hsfiles
hsfiles/postgres.hsfiles
hsfiles/postgres-fay.hsfiles
hsfiles/simple.hsfiles
hsfiles/sqlite.hsfiles
executable yesod-ghc-wrapper
main-is: ghcwrapper.hs
build-depends:
base >= 4 && < 5
, Cabal
executable yesod-ld-wrapper
main-is: ghcwrapper.hs
cpp-options: -DLDCMD
build-depends:
base >= 4 && < 5
, Cabal
executable yesod-ar-wrapper
main-is: ghcwrapper.hs
cpp-options: -DARCMD
build-depends:
base >= 4 && < 5
, Cabal
executable yesod
if os(windows)
cpp-options: -DWINDOWS
build-depends: base >= 4.3 && < 5
, ghc >= 7.0.3 && < 7.8
, ghc-paths >= 0.1
, parsec >= 2.1 && < 4
, text >= 0.11
, shakespeare-text >= 1.0 && < 1.1
, shakespeare >= 1.0.2 && < 1.3
, shakespeare-js >= 1.0.2 && < 1.3
, shakespeare-css >= 1.0.2 && < 1.1
, bytestring >= 0.9.1.4
, time >= 1.1.4
, template-haskell
, directory >= 1.0
, Cabal
, unix-compat >= 0.2 && < 0.5
, containers >= 0.2
, attoparsec >= 0.10
, http-types >= 0.7
, blaze-builder >= 0.2.1.4 && < 0.4
, filepath >= 1.1
, process
, zlib >= 0.5 && < 0.6
, tar >= 0.4 && < 0.5
, system-filepath >= 0.4 && < 0.5
, system-fileio >= 0.3 && < 0.4
, unordered-containers
, yaml >= 0.8 && < 0.9
, optparse-applicative >= 0.5
, fsnotify >= 0.0 && < 0.1
, split >= 0.2 && < 0.3
, file-embed
, conduit >= 0.5 && < 1.1
, resourcet >= 0.3 && < 0.5
, base64-bytestring
, lifted-base
, http-reverse-proxy >= 0.1.1
, network
, http-conduit
, network-conduit
, project-template >= 0.1.1
, transformers
, warp >= 1.3.7.5
, wai >= 1.4
ghc-options: -Wall -threaded
main-is: main.hs
other-modules: Scaffolding.Scaffolder
Devel
Build
GhcBuild
Keter
AddHandler
Paths_yesod_bin
Options
source-repository head
type: git
location: https://github.com/yesodweb/yesod
yesod-bin-1.2.4.1/AddHandler.hs 0000644 0000000 0000000 00000006001 12241220146 014245 0 ustar 00 0000000 0000000 module AddHandler (addHandler) where
import Prelude hiding (readFile)
import System.IO (hFlush, stdout)
import Data.Char (isLower, toLower, isSpace)
import Data.List (isPrefixOf, isSuffixOf)
import qualified Data.Text as T
import qualified Data.Text.IO as TIO
import System.Directory (getDirectoryContents)
-- strict readFile
readFile :: FilePath -> IO String
readFile = fmap T.unpack . TIO.readFile
addHandler :: IO ()
addHandler = do
allFiles <- getDirectoryContents "."
cabal <-
case filter (".cabal" `isSuffixOf`) allFiles of
[x] -> return x
[] -> error "No cabal file found"
_ -> error "Too many cabal files found"
putStr "Name of route (without trailing R): "
hFlush stdout
name <- getLine
case name of
[] -> error "Please provide a name"
c:_
| isLower c -> error "Name must start with an upper case letter"
| otherwise -> return ()
putStr "Enter route pattern (ex: /entry/#EntryId): "
hFlush stdout
pattern <- getLine
putStr "Enter space-separated list of methods (ex: GET POST): "
hFlush stdout
methods <- getLine
let modify fp f = readFile fp >>= writeFile fp . f
modify "Application.hs" $ fixApp name
modify cabal $ fixCabal name
modify "config/routes" $ fixRoutes name pattern methods
writeFile ("Handler/" ++ name ++ ".hs") $ mkHandler name pattern methods
fixApp :: String -> String -> String
fixApp name =
unlines . reverse . go . reverse . lines
where
l = "import Handler." ++ name
go [] = [l]
go (x:xs)
| "import Handler." `isPrefixOf` x = l : x : xs
| otherwise = x : go xs
fixCabal :: String -> String -> String
fixCabal name =
unlines . reverse . go . reverse . lines
where
l = "import Handler." ++ name
go [] = [l]
go (x:xs)
| "Handler." `isPrefixOf` x' = (spaces ++ "Handler." ++ name) : x : xs
| otherwise = x : go xs
where
(spaces, x') = span isSpace x
fixRoutes :: String -> String -> String -> String -> String
fixRoutes name pattern methods =
(++ l)
where
l = concat
[ pattern
, " "
, name
, "R "
, methods
, "\n"
]
mkHandler :: String -> String -> String -> String
mkHandler name pattern methods = unlines
$ ("module Handler." ++ name ++ " where")
: ""
: "import Import"
: concatMap go (words methods)
where
go method =
[ ""
, concat $ func : " :: " : map toArrow types ++ ["Handler Html"]
, concat
[ func
, " = error \"Not yet implemented: "
, func
, "\""
]
]
where
func = concat [map toLower method, name, "R"]
types = getTypes pattern
toArrow t = concat [t, " -> "]
getTypes "" = []
getTypes ('/':rest) = getTypes rest
getTypes ('#':rest) =
typ : getTypes rest'
where
(typ, rest') = break (== '/') rest
getTypes rest = getTypes $ dropWhile (/= '/') rest
yesod-bin-1.2.4.1/LICENSE 0000644 0000000 0000000 00000002075 12241220146 012737 0 ustar 00 0000000 0000000 Copyright (c) 2012 Michael Snoyman, http://www.yesodweb.com/
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.
yesod-bin-1.2.4.1/Options.hs 0000644 0000000 0000000 00000010770 12241220146 013722 0 ustar 00 0000000 0000000 {-# LANGUAGE PatternGuards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE CPP #-}
module Options (injectDefaults) where
import Control.Applicative
import qualified Control.Exception as E
import Control.Monad
import Data.Char (isAlphaNum, isSpace, toLower)
import Data.List (foldl')
import Data.List.Split (splitOn)
import qualified Data.Map as M
import Data.Maybe (catMaybes)
import Data.Monoid
import Options.Applicative
import Options.Applicative.Types
import System.Directory
import System.Environment
import System.FilePath ((>))
-- | inject defaults from either files or environments
-- in order of priority:
-- 1. command line arguments: --long-option=value
-- 2. environment variables: PREFIX_COMMAND_LONGOPTION=value
-- 3. $HOME/.prefix/config: prefix.command.longoption=value
--
-- note: this automatically injects values for standard options and flags
-- (also inside subcommands), but not for more complex parsers that use BindP
-- (like `many'). As a workaround a single special case is supported,
-- for `many' arguments that generate a list of strings.
injectDefaults :: String -- ^ prefix, program name
-> [(String, a -> [String] -> a)] -- ^ append extra options for arguments that are lists of strings
-> ParserInfo a -- ^ original parsers
-> IO (ParserInfo a)
injectDefaults prefix lenses parser = do
e <- getEnvironment
config <- (readFile . (> "config") =<< getAppUserDataDirectory prefix)
`E.catch` \(_::E.SomeException) -> return ""
let env = M.fromList . filter ((==[prefix]) . take 1 . fst) $
configLines config <> -- config first
map (\(k,v) -> (splitOn "_" $ map toLower k, v)) e -- env vars override config
p' = parser { infoParser = injectDefaultP env [prefix] (infoParser parser) }
return $ foldl' (\p (key,l) -> fmap (updateA env key l) p) p' lenses
updateA :: M.Map [String] String -> String -> (a -> [String] -> a) -> a -> a
updateA env key upd a =
case M.lookup (splitOn "." key) env of
Nothing -> a
Just v -> upd a (splitOn ":" v)
-- | really simple key/value file reader: x.y = z -> (["x","y"],"z")
configLines :: String -> [([String], String)]
configLines = catMaybes . map (mkLine . takeWhile (/='#')) . lines
where
trim = let f = reverse . dropWhile isSpace in f . f
mkLine l | (k, ('=':v)) <- break (=='=') l = Just (splitOn "." (trim k), trim v)
| otherwise = Nothing
-- | inject the environment into the parser
-- the map contains the paths with the value that's passed into the reader if the
-- command line parser gives no result
injectDefaultP :: M.Map [String] String -> [String] -> Parser a -> Parser a
injectDefaultP _env _path n@(NilP{}) = n
injectDefaultP env path p@(OptP o)
| (Option (CmdReader cmds f) props) <- o =
let cmdMap = M.fromList (map (\c -> (c, mkCmd c)) cmds)
mkCmd cmd =
let (Just parseri) = f cmd
in parseri { infoParser = injectDefaultP env (path ++ [normalizeName cmd]) (infoParser parseri) }
in OptP (Option (CmdReader cmds (`M.lookup` cmdMap)) props)
| (Option (OptReader names (CReader _ rdr) _) _) <- o =
p <|> either' (const empty) pure (msum $ map (rdr <=< (maybe (left $ ErrorMsg "Missing environment variable") right . getEnvValue env path)) names)
| (Option (FlagReader names a) _) <- o =
p <|> if any ((==Just "1") . getEnvValue env path) names then pure a else empty
| otherwise = p
injectDefaultP env path (MultP p1 p2) =
MultP (injectDefaultP env path p1) (injectDefaultP env path p2)
injectDefaultP env path (AltP p1 p2) =
AltP (injectDefaultP env path p1) (injectDefaultP env path p2)
injectDefaultP _env _path b@(BindP {}) = b
#if MIN_VERSION_optparse_applicative(0,6,0)
right = ReadM . Right
left = ReadM . Left
either' f g (ReadM x) = either f g x
#else
right = Right
left = Left
either' = either
#endif
getEnvValue :: M.Map [String] String -> [String] -> OptName -> Maybe String
getEnvValue env path (OptLong l) = M.lookup (path ++ [normalizeName l]) env
getEnvValue _ _ _ = Nothing
normalizeName :: String -> String
normalizeName = map toLower . filter isAlphaNum
yesod-bin-1.2.4.1/ghcwrapper.hs 0000644 0000000 0000000 00000004107 12241220146 014426 0 ustar 00 0000000 0000000 {-
wrapper executable that captures arguments to ghc, ar or ld
-}
{-# LANGUAGE CPP #-}
module Main where
import Control.Monad (when)
import Data.Maybe (fromMaybe)
import Distribution.Compiler (CompilerFlavor (..))
import Distribution.Simple.Configure (configCompiler)
import Distribution.Simple.Program (arProgram,
defaultProgramConfiguration,
ghcProgram, ldProgram,
programPath)
import Distribution.Simple.Program.Db (configureAllKnownPrograms,
lookupProgram)
import Distribution.Simple.Program.Types (Program (..))
import Distribution.Verbosity (silent)
import System.Directory (doesDirectoryExist)
import System.Environment (getArgs)
import System.Exit (ExitCode (..), exitWith)
import System.IO (hPutStrLn, stderr)
import System.Process (rawSystem, readProcess)
#ifdef LDCMD
cmd :: Program
cmd = ldProgram
outFile = "yesod-devel/ldargs.txt"
#else
#ifdef ARCMD
cmd :: Program
cmd = arProgram
outFile ="yesod-devel/arargs.txt"
#else
cmd :: Program
cmd = ghcProgram
outFile = "yesod-devel/ghcargs.txt"
#endif
#endif
runProgram :: Program -> [String] -> IO ExitCode
runProgram pgm args = do
(comp, pgmc) <- configCompiler (Just GHC) Nothing Nothing defaultProgramConfiguration silent
pgmc' <- configureAllKnownPrograms silent pgmc
case lookupProgram pgm pgmc' of
Nothing -> do
hPutStrLn stderr ("cannot find program '" ++ programName pgm ++ "'")
return (ExitFailure 1)
Just p -> rawSystem (programPath p) args
main = do
args <- getArgs
e <- doesDirectoryExist "yesod-devel"
when e $ writeFile outFile (show args ++ "\n")
ex <- runProgram cmd args
exitWith ex
yesod-bin-1.2.4.1/Devel.hs 0000644 0000000 0000000 00000046042 12241220146 013327 0 ustar 00 0000000 0000000 {-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Devel
( devel
, DevelOpts(..)
, defaultDevelOpts
) where
import Paths_yesod_bin
import qualified Distribution.Compiler as D
import qualified Distribution.ModuleName as D
import qualified Distribution.PackageDescription as D
import qualified Distribution.PackageDescription.Parse as D
import qualified Distribution.Simple.Configure as D
import qualified Distribution.Simple.Program as D
import qualified Distribution.Simple.Utils as D
import qualified Distribution.Verbosity as D
import Control.Applicative ((<$>), (<*>))
import Control.Concurrent (forkIO, threadDelay)
import Control.Concurrent.MVar (MVar, newEmptyMVar,
takeMVar, tryPutMVar)
import qualified Control.Exception as Ex
import Control.Monad (forever, unless, void,
when)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.State (evalStateT, get)
import qualified Data.IORef as I
import qualified Data.ByteString.Lazy as LB
import Data.Char (isNumber, isUpper)
import qualified Data.List as L
import qualified Data.Map as Map
import Data.Maybe (fromMaybe)
import qualified Data.Set as Set
import System.Directory
import System.Environment (getEnvironment)
import System.Exit (ExitCode (..),
exitFailure,
exitSuccess)
import System.FilePath (dropExtension,
splitDirectories,
takeExtension, (>))
import System.FSNotify
import System.IO (Handle)
import System.IO.Error (isDoesNotExistError)
import System.Posix.Types (EpochTime)
import System.PosixCompat.Files (getFileStatus,
modificationTime)
import System.Process (ProcessHandle,
createProcess, env,
getProcessExitCode,
proc, readProcess,
system,
terminateProcess)
import System.Timeout (timeout)
import Build (getDeps, isNewerThan,
recompDeps)
import GhcBuild (buildPackage,
getBuildFlags, getPackageArgs)
import qualified Config as GHC
import Data.Conduit.Network (HostPreference (HostIPv4),
bindPort)
import Network (withSocketsDo)
import Network.HTTP.Conduit (def, newManager)
import Network.HTTP.ReverseProxy (ProxyDest (ProxyDest),
waiProxyToSettings, wpsTimeout, wpsOnExc)
#if MIN_VERSION_http_reverse_proxy(0, 2, 0)
import qualified Network.HTTP.ReverseProxy as ReverseProxy
#endif
import Network.HTTP.Types (status200)
import Network.Socket (sClose)
import Network.Wai (responseLBS)
import Network.Wai.Handler.Warp (run)
import SrcLoc (Located)
lockFile :: DevelOpts -> FilePath
lockFile _opts = "yesod-devel/devel-terminate"
writeLock :: DevelOpts -> IO ()
writeLock opts = do
createDirectoryIfMissing True "yesod-devel"
writeFile (lockFile opts) ""
createDirectoryIfMissing True "dist" -- for compatibility with old devel.hs
writeFile "dist/devel-terminate" ""
removeLock :: DevelOpts -> IO ()
removeLock opts = do
removeFileIfExists (lockFile opts)
removeFileIfExists "dist/devel-terminate" -- for compatibility with old devel.hs
data DevelOpts = DevelOpts
{ isCabalDev :: Bool
, forceCabal :: Bool
, verbose :: Bool
, eventTimeout :: Int -- negative value for no timeout
, successHook :: Maybe String
, failHook :: Maybe String
, buildDir :: Maybe String
, develPort :: Int
, proxyTimeout :: Int
, useReverseProxy :: Bool
} deriving (Show, Eq)
getBuildDir :: DevelOpts -> String
getBuildDir opts = fromMaybe "dist" (buildDir opts)
defaultDevelOpts :: DevelOpts
defaultDevelOpts = DevelOpts False False False (-1) Nothing Nothing Nothing 3000 10 True
cabalProgram :: DevelOpts -> FilePath
cabalProgram opts | isCabalDev opts = "cabal-dev"
| otherwise = "cabal"
-- | Run a reverse proxy from port 3000 to 3001. If there is no response on
-- 3001, give an appropriate message to the user.
reverseProxy :: DevelOpts -> I.IORef Int -> IO ()
reverseProxy opts iappPort = do
manager <- newManager def
let loop = forever $ do
run (develPort opts) $ waiProxyToSettings
(const $ do
appPort <- liftIO $ I.readIORef iappPort
return $
#if MIN_VERSION_http_reverse_proxy(0, 2, 0)
ReverseProxy.WPRProxyDest
#else
Right
#endif
$ ProxyDest "127.0.0.1" appPort)
def
{ wpsOnExc = onExc
, wpsTimeout =
if proxyTimeout opts == 0
then Nothing
else Just (1000000 * proxyTimeout opts)
}
manager
putStrLn "Reverse proxy stopped, but it shouldn't"
threadDelay 1000000
putStrLn "Restarting reverse proxy"
loop `Ex.onException` exitFailure
where
onExc _ _ = do
refreshing <- liftIO $ getDataFileName "refreshing.html"
html <- liftIO $ LB.readFile refreshing
return $ responseLBS
status200
[ ("content-type", "text/html")
, ("Refresh", "1")
]
html
checkPort :: Int -> IO Bool
checkPort p = do
es <- Ex.try $ bindPort p HostIPv4
case es of
Left (_ :: Ex.IOException) -> return False
Right s -> do
sClose s
return True
getPort :: DevelOpts -> Int -> IO Int
getPort opts _ | not (useReverseProxy opts) = return $ develPort opts
getPort _ p0 =
loop p0
where
loop p = do
avail <- checkPort p
if avail then return p else loop (succ p)
devel :: DevelOpts -> [String] -> IO ()
devel opts passThroughArgs = withSocketsDo $ withManager $ \manager -> do
avail <- checkPort $ develPort opts
unless avail $ error "devel port unavailable"
iappPort <- getPort opts 17834 >>= I.newIORef
when (useReverseProxy opts) $ void $ forkIO $ reverseProxy opts iappPort
checkDevelFile
writeLock opts
putStrLn "Yesod devel server. Press ENTER to quit"
_ <- forkIO $ do
filesModified <- newEmptyMVar
watchTree manager "." (const True) (\_ -> void (tryPutMVar filesModified ()))
evalStateT (mainOuterLoop iappPort filesModified) Map.empty
_ <- getLine
writeLock opts
exitSuccess
where
bd = getBuildDir opts
-- outer loop re-reads the cabal file
mainOuterLoop iappPort filesModified = do
ghcVer <- liftIO ghcVersion
cabal <- liftIO $ D.findPackageDesc "."
gpd <- liftIO $ D.readPackageDescription D.normal cabal
ldar <- liftIO lookupLdAr
(hsSourceDirs, _) <- liftIO $ checkCabalFile gpd
liftIO $ removeFileIfExists (bd > "setup-config")
c <- liftIO $ configure opts passThroughArgs
if c then do
-- these files contain the wrong data after the configure step,
-- remove them to force a cabal build first
liftIO $ mapM_ removeFileIfExists [ "yesod-devel/ghcargs.txt"
, "yesod-devel/arargs.txt"
, "yesod-devel/ldargs.txt"
]
rebuild <- liftIO $ mkRebuild ghcVer cabal opts ldar
mainInnerLoop iappPort hsSourceDirs filesModified cabal rebuild
else do
liftIO (threadDelay 5000000)
mainOuterLoop iappPort filesModified
-- inner loop rebuilds after files change
mainInnerLoop iappPort hsSourceDirs filesModified cabal rebuild = go
where
go = do
_ <- recompDeps hsSourceDirs
list <- liftIO $ getFileList hsSourceDirs [cabal]
success <- liftIO rebuild
pkgArgs <- liftIO (ghcPackageArgs opts)
let devArgs = pkgArgs ++ ["devel.hs"]
let loop list0 = do
(haskellFileChanged, list1) <- liftIO $
watchForChanges filesModified hsSourceDirs [cabal] list0 (eventTimeout opts)
anyTouched <- recompDeps hsSourceDirs
unless (anyTouched || haskellFileChanged) $ loop list1
if not success
then liftIO $ do
putStrLn "Build failure, pausing..."
runBuildHook $ failHook opts
else do
liftIO $ runBuildHook $ successHook opts
liftIO $ removeLock opts
liftIO $ putStrLn
$ if verbose opts then "Starting development server: runghc " ++ L.unwords devArgs
else "Starting development server..."
env0 <- liftIO getEnvironment
-- get a new port for the new process to listen on
appPort <- liftIO $ I.readIORef iappPort >>= getPort opts . (+ 1)
liftIO $ I.writeIORef iappPort appPort
(_,_,_,ph) <- liftIO $ createProcess (proc "runghc" devArgs)
{ env = Just $ ("PORT", show appPort) : ("DISPLAY_PORT", show $ develPort opts) : env0
}
derefMap <- get
watchTid <- liftIO . forkIO . try_ $ flip evalStateT derefMap $ do
loop list
liftIO $ do
putStrLn "Stopping development server..."
writeLock opts
threadDelay 1000000
putStrLn "Terminating development server..."
terminateProcess ph
ec <- liftIO $ waitForProcess' ph
liftIO $ putStrLn $ "Exit code: " ++ show ec
liftIO $ Ex.throwTo watchTid (userError "process finished")
loop list
n <- liftIO $ cabal `isNewerThan` (bd > "setup-config")
if n then mainOuterLoop iappPort filesModified else go
runBuildHook :: Maybe String -> IO ()
runBuildHook (Just s) = do
ret <- system s
case ret of
ExitFailure _ -> putStrLn ("Error executing hook: " ++ s)
_ -> return ()
runBuildHook Nothing = return ()
{-
run `cabal configure' with our wrappers
-}
configure :: DevelOpts -> [String] -> IO Bool
configure opts extraArgs =
checkExit =<< (createProcess $ proc (cabalProgram opts)
([ "configure"
, "-flibrary-only"
, "-fdevel"
, "--disable-library-profiling"
, "--with-ld=yesod-ld-wrapper"
, "--with-ghc=yesod-ghc-wrapper"
, "--with-ar=yesod-ar-wrapper"
, "--with-hc-pkg=ghc-pkg"
] ++ extraArgs)
)
removeFileIfExists :: FilePath -> IO ()
removeFileIfExists file = removeFile file `Ex.catch` handler
where
handler :: IOError -> IO ()
handler e | isDoesNotExistError e = return ()
| otherwise = Ex.throw e
mkRebuild :: String -> FilePath -> DevelOpts -> (FilePath, FilePath) -> IO (IO Bool)
mkRebuild ghcVer cabalFile opts (ldPath, arPath)
| GHC.cProjectVersion /= ghcVer =
failWith "Yesod has been compiled with a different GHC version, please reinstall"
| forceCabal opts = return (rebuildCabal opts)
| otherwise = do
return $ do
ns <- mapM (cabalFile `isNewerThan`)
[ "yesod-devel/ghcargs.txt", "yesod-devel/arargs.txt", "yesod-devel/ldargs.txt" ]
if or ns
then rebuildCabal opts
else do
bf <- getBuildFlags
rebuildGhc bf ldPath arPath
rebuildGhc :: [Located String] -> FilePath -> FilePath -> IO Bool
rebuildGhc bf ld ar = do
putStrLn "Rebuilding application... (using GHC API)"
buildPackage bf ld ar
rebuildCabal :: DevelOpts -> IO Bool
rebuildCabal opts = do
putStrLn $ "Rebuilding application... (using " ++ cabalProgram opts ++ ")"
checkExit =<< createProcess (proc (cabalProgram opts) args)
where
args | verbose opts = [ "build" ]
| otherwise = [ "build", "-v0" ]
try_ :: forall a. IO a -> IO ()
try_ x = (Ex.try x :: IO (Either Ex.SomeException a)) >> return ()
type FileList = Map.Map FilePath EpochTime
getFileList :: [FilePath] -> [FilePath] -> IO FileList
getFileList hsSourceDirs extraFiles = do
(files, deps) <- getDeps hsSourceDirs
let files' = extraFiles ++ files ++ map fst (Map.toList deps)
fmap Map.fromList $ flip mapM files' $ \f -> do
efs <- Ex.try $ getFileStatus f
return $ case efs of
Left (_ :: Ex.SomeException) -> (f, 0)
Right fs -> (f, modificationTime fs)
-- | Returns @True@ if a .hs file changed.
watchForChanges :: MVar () -> [FilePath] -> [FilePath] -> FileList -> Int -> IO (Bool, FileList)
watchForChanges filesModified hsSourceDirs extraFiles list t = do
newList <- getFileList hsSourceDirs extraFiles
if list /= newList
then do
let haskellFileChanged = not $ Map.null $ Map.filterWithKey isHaskell $
Map.differenceWith compareTimes newList list `Map.union`
Map.differenceWith compareTimes list newList
return (haskellFileChanged, newList)
else timeout (1000000*t) (takeMVar filesModified) >>
watchForChanges filesModified hsSourceDirs extraFiles list t
where
compareTimes x y
| x == y = Nothing
| otherwise = Just x
isHaskell filename _ = takeExtension filename `elem` [".hs", ".lhs", ".hsc", ".cabal"]
checkDevelFile :: IO ()
checkDevelFile = do
e <- doesFileExist "devel.hs"
unless e $ failWith "file devel.hs not found"
checkCabalFile :: D.GenericPackageDescription -> IO ([FilePath], D.Library)
checkCabalFile gpd = case D.condLibrary gpd of
Nothing -> failWith "incorrect cabal file, no library"
Just ct ->
case lookupDevelLib gpd ct of
Nothing ->
failWith "no development flag found in your configuration file. Expected a 'library-only' flag or the older 'devel' flag"
Just dLib -> do
let hsSourceDirs = D.hsSourceDirs . D.libBuildInfo $ dLib
fl <- getFileList hsSourceDirs []
let unlisted = checkFileList fl dLib
unless (null unlisted) $ do
putStrLn "WARNING: the following source files are not listed in exposed-modules or other-modules:"
mapM_ putStrLn unlisted
when (D.fromString "Application" `notElem` D.exposedModules dLib) $
putStrLn "WARNING: no exposed module Application"
return (hsSourceDirs, dLib)
failWith :: String -> IO a
failWith msg = do
putStrLn $ "ERROR: " ++ msg
exitFailure
checkFileList :: FileList -> D.Library -> [FilePath]
checkFileList fl lib = filter isUnlisted . filter isSrcFile $ sourceFiles
where
al = allModules lib
-- a file is only a possible 'module file' if all path pieces start with a capital letter
sourceFiles = filter isSrcFile . map fst . Map.toList $ fl
isSrcFile file = let dirs = filter (/=".") $ splitDirectories file
in all (isUpper . head) dirs && (takeExtension file `elem` [".hs", ".lhs"])
isUnlisted file = not (toModuleName file `Set.member` al)
toModuleName = L.intercalate "." . filter (/=".") . splitDirectories . dropExtension
allModules :: D.Library -> Set.Set String
allModules lib = Set.fromList $ map toString $ D.exposedModules lib ++ (D.otherModules . D.libBuildInfo) lib
where
toString = L.intercalate "." . D.components
ghcVersion :: IO String
ghcVersion = fmap getNumber $ readProcess "runghc" ["--numeric-version", "0"] []
where
getNumber = filter (\x -> isNumber x || x == '.')
ghcPackageArgs :: DevelOpts -> IO [String]
ghcPackageArgs opts = getBuildFlags >>= getPackageArgs (buildDir opts)
lookupDevelLib :: D.GenericPackageDescription -> D.CondTree D.ConfVar c a -> Maybe a
lookupDevelLib gpd ct | found = Just (D.condTreeData ct)
| otherwise = Nothing
where
flags = map (unFlagName . D.flagName) $ D.genPackageFlags gpd
unFlagName (D.FlagName x) = x
found = any (`elem` ["library-only", "devel"]) flags
-- location of `ld' and `ar' programs
lookupLdAr :: IO (FilePath, FilePath)
lookupLdAr = do
mla <- lookupLdAr'
case mla of
Nothing -> failWith "Cannot determine location of `ar' or `ld' program"
Just la -> return la
lookupLdAr' :: IO (Maybe (FilePath, FilePath))
lookupLdAr' = do
(_, pgmc) <- D.configCompiler (Just D.GHC) Nothing Nothing D.defaultProgramConfiguration D.silent
pgmc' <- D.configureAllKnownPrograms D.silent pgmc
return $ (,) <$> look D.ldProgram pgmc' <*> look D.arProgram pgmc'
where
look pgm pdb = fmap D.programPath (D.lookupProgram pgm pdb)
-- | nonblocking version of @waitForProcess@
waitForProcess' :: ProcessHandle -> IO ExitCode
waitForProcess' pid = go
where
go = do
mec <- getProcessExitCode pid
case mec of
Just ec -> return ec
Nothing -> threadDelay 100000 >> go
-- | wait for process started by @createProcess@, return True for ExitSuccess
checkExit :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO Bool
checkExit (_,_,_,h) = (==ExitSuccess) <$> waitForProcess' h
yesod-bin-1.2.4.1/main.hs 0000644 0000000 0000000 00000020676 12241220146 013221 0 ustar 00 0000000 0000000 {-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}
import Control.Monad (unless)
import Data.Monoid
import Data.Version (showVersion)
import Options.Applicative
import System.Exit (ExitCode (ExitSuccess), exitWith)
import System.Process (rawSystem)
import AddHandler (addHandler)
import Devel (DevelOpts (..), devel)
import Keter (keter)
import Options (injectDefaults)
import qualified Paths_yesod_bin
import Scaffolding.Scaffolder
import Options.Applicative.Builder.Internal (Mod, OptionFields)
#if MIN_VERSION_optparse_applicative(0,6,0)
import Options.Applicative.Types (ReadM (ReadM))
#endif
#ifndef WINDOWS
import Build (touch)
touch' :: IO ()
touch' = touch
windowsWarning :: String
windowsWarning = ""
#else
touch' :: IO ()
touch' = return ()
windowsWarning :: String
windowsWarning = " (does not work on Windows)"
#endif
data CabalPgm = Cabal | CabalDev deriving (Show, Eq)
data Options = Options
{ optCabalPgm :: CabalPgm
, optVerbose :: Bool
, optCommand :: Command
}
deriving (Show, Eq)
data Command = Init { _initBare :: Bool }
| Configure
| Build { buildExtraArgs :: [String] }
| Touch
| Devel { _develDisableApi :: Bool
, _develSuccessHook :: Maybe String
, _develFailHook :: Maybe String
, _develRescan :: Int
, _develBuildDir :: Maybe String
, develIgnore :: [String]
, develExtraArgs :: [String]
, _develPort :: Int
, _proxyTimeout :: Int
, _noReverseProxy :: Bool
}
| Test
| AddHandler
| Keter { _keterNoRebuild :: Bool }
| Version
deriving (Show, Eq)
cabalCommand :: Options -> String
cabalCommand mopt
| optCabalPgm mopt == CabalDev = "cabal-dev"
| otherwise = "cabal"
main :: IO ()
main = do
o <- execParser =<< injectDefaults "yesod" [ ("yesod.devel.extracabalarg" , \o args -> o { optCommand =
case optCommand o of
d@Devel{} -> d { develExtraArgs = args }
c -> c
})
, ("yesod.devel.ignore" , \o args -> o { optCommand =
case optCommand o of
d@Devel{} -> d { develIgnore = args }
c -> c
})
, ("yesod.build.extracabalarg" , \o args -> o { optCommand =
case optCommand o of
b@Build{} -> b { buildExtraArgs = args }
c -> c
})
] optParser'
let cabal xs = rawSystem' (cabalCommand o) xs
case optCommand o of
Init bare -> scaffold bare
Configure -> cabal ["configure"]
Build es -> touch' >> cabal ("build":es)
Touch -> touch'
Devel da s f r b _ig es p t nrp -> devel (DevelOpts (optCabalPgm o == CabalDev) da (optVerbose o) r s f b p t (not nrp)) es
Keter noRebuild -> keter (cabalCommand o) noRebuild
Version -> do putStrLn ("yesod-bin version: " ++ showVersion Paths_yesod_bin.version)
AddHandler -> addHandler
Test -> do touch'
cabal ["configure", "--enable-tests", "-flibrary-only"]
cabal ["build"]
cabal ["test"]
optParser' :: ParserInfo Options
optParser' = info (helper <*> optParser) ( fullDesc <> header "Yesod Web Framework command line utility" )
optParser :: Parser Options
optParser = Options
<$> flag Cabal CabalDev ( long "dev" <> short 'd' <> help "use cabal-dev" )
<*> switch ( long "verbose" <> short 'v' <> help "More verbose output" )
<*> subparser ( command "init"
(info (Init <$> (switch (long "bare" <> help "Create files in current folder")))
(progDesc "Scaffold a new site"))
<> command "configure" (info (pure Configure)
(progDesc "Configure a project for building"))
<> command "build" (info (Build <$> extraCabalArgs)
(progDesc $ "Build project (performs TH dependency analysis)" ++ windowsWarning))
<> command "touch" (info (pure Touch)
(progDesc $ "Touch any files with altered TH dependencies but do not build" ++ windowsWarning))
<> command "devel" (info develOptions
(progDesc "Run project with the devel server"))
<> command "test" (info (pure Test)
(progDesc "Build and run the integration tests"))
<> command "add-handler" (info (pure AddHandler)
(progDesc "Add a new handler and module to the project"))
<> command "keter" (info keterOptions
(progDesc "Build a keter bundle"))
<> command "version" (info (pure Version)
(progDesc "Print the version of Yesod"))
)
keterOptions :: Parser Command
keterOptions = Keter <$> switch ( long "nobuild" <> short 'n' <> help "Skip rebuilding" )
develOptions :: Parser Command
develOptions = Devel <$> switch ( long "disable-api" <> short 'd'
<> help "Disable fast GHC API rebuilding")
<*> optStr ( long "success-hook" <> short 's' <> metavar "COMMAND"
<> help "Run COMMAND after rebuild succeeds")
<*> optStr ( long "failure-hook" <> short 'f' <> metavar "COMMAND"
<> help "Run COMMAND when rebuild fails")
<*> option ( long "event-timeout" <> short 't' <> value 1 <> metavar "N"
<> help "Force rescan of files every N seconds" )
<*> optStr ( long "builddir" <> short 'b'
<> help "Set custom cabal build directory, default `dist'")
<*> many ( strOption ( long "ignore" <> short 'i' <> metavar "DIR"
<> help "ignore file changes in DIR" )
)
<*> extraCabalArgs
<*> option ( long "port" <> short 'p' <> value 3000 <> metavar "N"
<> help "Devel server listening port" )
<*> option ( long "proxy-timeout" <> short 'x' <> value 0 <> metavar "N"
<> help "Devel server timeout before returning 'not ready' message (in seconds, 0 for none)" )
<*> switch ( long "disable-reverse-proxy" <> short 'n'
<> help "Disable reverse proxy" )
extraCabalArgs :: Parser [String]
extraCabalArgs = many (strOption ( long "extra-cabal-arg" <> short 'e' <> metavar "ARG"
<> help "pass extra argument ARG to cabal")
)
-- | Optional @String@ argument
optStr :: Mod OptionFields (Maybe String) -> Parser (Maybe String)
optStr m =
nullOption $ value Nothing <> reader (success . str) <> m
where
#if MIN_VERSION_optparse_applicative(0,6,0)
success = ReadM . Right
#else
success = Right
#endif
-- | Like @rawSystem@, but exits if it receives a non-success result.
rawSystem' :: String -> [String] -> IO ()
rawSystem' x y = do
res <- rawSystem x y
unless (res == ExitSuccess) $ exitWith res
yesod-bin-1.2.4.1/GhcBuild.hs 0000644 0000000 0000000 00000046411 12241220146 013751 0 ustar 00 0000000 0000000 {-# OPTIONS_GHC -fno-warn-unused-do-bind #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
{-
There is a lot of code copied from GHC here, and some conditional
compilation. Instead of fixing all warnings and making it much more
difficult to compare the code to the original, just ignore unused
binds and imports.
-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-
build package with the GHC API
-}
module GhcBuild (getBuildFlags, buildPackage, getPackageArgs) where
import qualified Control.Exception as Ex
import Control.Monad (when)
import Data.IORef
import System.Process (rawSystem)
import System.Environment (getEnvironment)
import CmdLineParser
import Data.Char (toLower)
import Data.List (isPrefixOf, isSuffixOf, partition)
import Data.Maybe (fromMaybe)
import DriverPhases (Phase (..), anyHsc, isHaskellSrcFilename,
isSourceFilename, startPhase)
import DriverPipeline (compileFile, link, linkBinary, oneShot)
import DynFlags (DynFlags, compilerInfo)
import qualified DynFlags
import qualified DynFlags as DF
import qualified GHC
import GHC.Paths (libdir)
import HscTypes (HscEnv (..), emptyHomePackageTable)
import qualified Module
import MonadUtils (liftIO)
import Panic (throwGhcException, panic)
import SrcLoc (Located, mkGeneralLocated)
import qualified StaticFlags
import StaticFlags (v_Ld_inputs)
import System.FilePath (normalise, (>))
import Util (consIORef, looksLikeModuleName)
{-
This contains a huge hack:
GHC only accepts setting static flags once per process, however it has no way to
get the remaining options from the command line, without setting the static flags.
This code overwrites the IORef to disable the check. This will likely cause
problems if the flags are modified, but fortunately that's relatively uncommon.
-}
getBuildFlags :: IO [Located String]
getBuildFlags = do
argv0 <- fmap read $ readFile "yesod-devel/ghcargs.txt" -- generated by yesod-ghc-wrapper
argv0' <- prependHsenvArgv argv0
let (minusB_args, argv1) = partition ("-B" `isPrefixOf`) argv0'
mbMinusB | null minusB_args = Nothing
| otherwise = Just (drop 2 (last minusB_args))
let argv1' = map (mkGeneralLocated "on the commandline") argv1
writeIORef StaticFlags.v_opt_C_ready False -- the huge hack
(argv2, staticFlagWarnings) <- GHC.parseStaticFlags argv1'
return argv2
prependHsenvArgv :: [String] -> IO [String]
prependHsenvArgv argv = do
env <- getEnvironment
return $ case (lookup "HSENV" env) of
Nothing -> argv
_ -> hsenvArgv ++ argv
where hsenvArgv = words $ fromMaybe "" (lookup "PACKAGE_DB_FOR_GHC" env)
-- construct a command line for loading the right packages
getPackageArgs :: Maybe String -> [Located String] -> IO [String]
getPackageArgs buildDir argv2 = do
(mode, argv3, modeFlagWarnings) <- parseModeFlags argv2
GHC.runGhc (Just libdir) $ do
dflags0 <- GHC.getSessionDynFlags
(dflags1, _, _) <- GHC.parseDynamicFlags dflags0 argv3
let pkgFlags = map convertPkgFlag (GHC.packageFlags dflags1)
hideAll | gopt DF.Opt_HideAllPackages dflags1 = [ "-hide-all-packages"]
| otherwise = []
ownPkg = "-package-id" ++ Module.packageIdString (DF.thisPackage dflags1) ++ "-inplace"
return (extra dflags1 ++ hideAll ++ pkgFlags ++ [ownPkg])
where
convertPkgFlag (DF.ExposePackage p) = "-package" ++ p
convertPkgFlag (DF.ExposePackageId p) = "-package-id" ++ p
convertPkgFlag (DF.HidePackage p) = "-hide-package" ++ p
convertPkgFlag (DF.IgnorePackage p) = "-ignore-package" ++ p
convertPkgFlag (DF.TrustPackage p) = "-trust" ++ p
convertPkgFlag (DF.DistrustPackage p) ="-distrust" ++ p
#if __GLASGOW_HASKELL__ >= 705
extra df = inplaceConf ++ extra'
where
extra' = concatMap convertExtra (extraConfs df)
-- old cabal-install sometimes misses the .inplace db, fix it here
inplaceConf
| any (".inplace" `isSuffixOf`) extra' = []
| otherwise = ["-package-db" ++ fromMaybe "dist" buildDir
++ "/package.conf.inplace"]
extraConfs df = GHC.extraPkgConfs df []
convertExtra DF.GlobalPkgConf = [ ]
convertExtra DF.UserPkgConf = [ ]
convertExtra (DF.PkgConfFile file) = [ "-package-db" ++ file ]
#else
extra df = inplaceConf ++ extra'
where
extra' = map ("-package-conf"++) (GHC.extraPkgConfs df)
-- old cabal-install sometimes misses the .inplace db, fix it here
inplaceConf
| any (".inplace" `isSuffixOf`) extra' = []
| otherwise = ["-package-conf" ++ fromMaybe "dist" buildDir
++ "/package.conf.inplace"]
#endif
#if __GLASGOW_HASKELL__ >= 707
gopt = DF.gopt
#else
gopt = DF.dopt
#endif
buildPackage :: [Located String] -> FilePath -> FilePath -> IO Bool
buildPackage a ld ar = buildPackage' a ld ar `Ex.catch` \e -> do
putStrLn ("exception building package: " ++ show (e :: Ex.SomeException))
return False
buildPackage' :: [Located String] -> FilePath -> FilePath -> IO Bool
buildPackage' argv2 ld ar = do
(mode, argv3, modeFlagWarnings) <- parseModeFlags argv2
GHC.runGhc (Just libdir) $ do
dflags0 <- GHC.getSessionDynFlags
(dflags1, _, _) <- GHC.parseDynamicFlags dflags0 argv3
let dflags2 = dflags1 { GHC.ghcMode = GHC.CompManager
, GHC.hscTarget = GHC.hscTarget dflags1
, GHC.ghcLink = GHC.LinkBinary
, GHC.verbosity = 1
}
(dflags3, fileish_args, _) <- GHC.parseDynamicFlags dflags2 argv3
GHC.setSessionDynFlags dflags3
let normal_fileish_paths = map (normalise . GHC.unLoc) fileish_args
(srcs, objs) = partition_args normal_fileish_paths [] []
(hs_srcs, non_hs_srcs) = partition haskellish srcs
haskellish (f,Nothing) =
looksLikeModuleName f || isHaskellSrcFilename f || '.' `notElem` f
haskellish (_,Just phase) =
#if MIN_VERSION_ghc(7,4,0)
phase `notElem` [As, Cc, Cobjc, Cobjcpp, CmmCpp, Cmm, StopLn]
#else
phase `notElem` [As, Cc, CmmCpp, Cmm, StopLn]
#endif
hsc_env <- GHC.getSession
-- if (null hs_srcs)
-- then liftIO (oneShot hsc_env StopLn srcs)
-- else do
#if MIN_VERSION_ghc(7,2,0)
o_files <- mapM (\x -> liftIO $ compileFile hsc_env StopLn x)
#else
o_files <- mapM (\x -> compileFile hsc_env StopLn x)
#endif
non_hs_srcs
liftIO $ mapM_ (consIORef v_Ld_inputs) (reverse o_files)
targets <- mapM (uncurry GHC.guessTarget) hs_srcs
GHC.setTargets targets
ok_flag <- GHC.load GHC.LoadAllTargets
if GHC.failed ok_flag
then return False
else liftIO (linkPkg ld ar) >> return True
linkPkg :: FilePath -> FilePath -> IO ()
linkPkg ld ar = do
arargs <- fmap read $ readFile "yesod-devel/arargs.txt"
rawSystem ar arargs
ldargs <- fmap read $ readFile "yesod-devel/ldargs.txt"
rawSystem ld ldargs
return ()
--------------------------------------------------------------------------------------------
-- stuff below copied from ghc main.hs
--------------------------------------------------------------------------------------------
partition_args :: [String] -> [(String, Maybe Phase)] -> [String]
-> ([(String, Maybe Phase)], [String])
partition_args [] srcs objs = (reverse srcs, reverse objs)
partition_args ("-x":suff:args) srcs objs
| "none" <- suff = partition_args args srcs objs
| StopLn <- phase = partition_args args srcs (slurp ++ objs)
| otherwise = partition_args rest (these_srcs ++ srcs) objs
where phase = startPhase suff
(slurp,rest) = break (== "-x") args
these_srcs = zip slurp (repeat (Just phase))
partition_args (arg:args) srcs objs
| looks_like_an_input arg = partition_args args ((arg,Nothing):srcs) objs
| otherwise = partition_args args srcs (arg:objs)
{-
We split out the object files (.o, .dll) and add them
to v_Ld_inputs for use by the linker.
The following things should be considered compilation manager inputs:
- haskell source files (strings ending in .hs, .lhs or other
haskellish extension),
- module names (not forgetting hierarchical module names),
- and finally we consider everything not containing a '.' to be
a comp manager input, as shorthand for a .hs or .lhs filename.
Everything else is considered to be a linker object, and passed
straight through to the linker.
-}
looks_like_an_input :: String -> Bool
looks_like_an_input m = isSourceFilename m
|| looksLikeModuleName m
|| '.' `notElem` m
-- Parsing the mode flag
parseModeFlags :: [Located String]
-> IO (Mode,
[Located String],
[Located String])
parseModeFlags args = do
let ((leftover, errs1, warns), (mModeFlag, errs2, flags')) =
runCmdLine (processArgs mode_flags args)
(Nothing, [], [])
mode = case mModeFlag of
Nothing -> doMakeMode
Just (m, _) -> m
errs = errs1 ++ map (mkGeneralLocated "on the commandline") errs2
when (not (null errs)) $ throwGhcException $ errorsToGhcException errs
return (mode, flags' ++ leftover, warns)
type ModeM = CmdLineP (Maybe (Mode, String), [String], [Located String])
-- mode flags sometimes give rise to new DynFlags (eg. -C, see below)
-- so we collect the new ones and return them.
mode_flags :: [Flag ModeM]
mode_flags =
[ ------- help / version ----------------------------------------------
Flag "?" (PassFlag (setMode showGhcUsageMode))
, Flag "-help" (PassFlag (setMode showGhcUsageMode))
, Flag "V" (PassFlag (setMode showVersionMode))
, Flag "-version" (PassFlag (setMode showVersionMode))
, Flag "-numeric-version" (PassFlag (setMode showNumVersionMode))
, Flag "-info" (PassFlag (setMode showInfoMode))
, Flag "-supported-languages" (PassFlag (setMode showSupportedExtensionsMode))
, Flag "-supported-extensions" (PassFlag (setMode showSupportedExtensionsMode))
] ++
[ Flag k' (PassFlag (setMode (printSetting k)))
| k <- ["Project version",
"Booter version",
"Stage",
"Build platform",
"Host platform",
"Target platform",
"Have interpreter",
"Object splitting supported",
"Have native code generator",
"Support SMP",
"Unregisterised",
"Tables next to code",
"RTS ways",
"Leading underscore",
"Debug on",
"LibDir",
"Global Package DB",
"C compiler flags",
"Gcc Linker flags",
"Ld Linker flags"],
let k' = "-print-" ++ map (replaceSpace . toLower) k
replaceSpace ' ' = '-'
replaceSpace c = c
] ++
------- interfaces ----------------------------------------------------
[ Flag "-show-iface" (HasArg (\f -> setMode (showInterfaceMode f)
"--show-iface"))
------- primary modes ------------------------------------------------
, Flag "c" (PassFlag (\f -> do setMode (stopBeforeMode StopLn) f
addFlag "-no-link" f))
, Flag "M" (PassFlag (setMode doMkDependHSMode))
, Flag "E" (PassFlag (setMode (stopBeforeMode anyHsc)))
, Flag "C" (PassFlag (\f -> do setMode (stopBeforeMode HCc) f
addFlag "-fvia-C" f))
, Flag "S" (PassFlag (setMode (stopBeforeMode As)))
, Flag "-make" (PassFlag (setMode doMakeMode))
, Flag "-interactive" (PassFlag (setMode doInteractiveMode))
, Flag "-abi-hash" (PassFlag (setMode doAbiHashMode))
, Flag "e" (SepArg (\s -> setMode (doEvalMode s) "-e"))
]
setMode :: Mode -> String -> EwM ModeM ()
setMode newMode newFlag = liftEwM $ do
(mModeFlag, errs, flags') <- getCmdLineState
let (modeFlag', errs') =
case mModeFlag of
Nothing -> ((newMode, newFlag), errs)
Just (oldMode, oldFlag) ->
case (oldMode, newMode) of
-- -c/--make are allowed together, and mean --make -no-link
_ | isStopLnMode oldMode && isDoMakeMode newMode
|| isStopLnMode newMode && isDoMakeMode oldMode ->
((doMakeMode, "--make"), [])
-- If we have both --help and --interactive then we
-- want showGhciUsage
_ | isShowGhcUsageMode oldMode &&
isDoInteractiveMode newMode ->
((showGhciUsageMode, oldFlag), [])
| isShowGhcUsageMode newMode &&
isDoInteractiveMode oldMode ->
((showGhciUsageMode, newFlag), [])
-- Otherwise, --help/--version/--numeric-version always win
| isDominantFlag oldMode -> ((oldMode, oldFlag), [])
| isDominantFlag newMode -> ((newMode, newFlag), [])
-- We need to accumulate eval flags like "-e foo -e bar"
(Right (Right (DoEval esOld)),
Right (Right (DoEval [eNew]))) ->
((Right (Right (DoEval (eNew : esOld))), oldFlag),
errs)
-- Saying e.g. --interactive --interactive is OK
_ | oldFlag == newFlag -> ((oldMode, oldFlag), errs)
-- Otherwise, complain
_ -> let err = flagMismatchErr oldFlag newFlag
in ((oldMode, oldFlag), err : errs)
putCmdLineState (Just modeFlag', errs', flags')
where isDominantFlag f = isShowGhcUsageMode f ||
isShowGhciUsageMode f ||
isShowVersionMode f ||
isShowNumVersionMode f
flagMismatchErr :: String -> String -> String
flagMismatchErr oldFlag newFlag
= "cannot use `" ++ oldFlag ++ "' with `" ++ newFlag ++ "'"
addFlag :: String -> String -> EwM ModeM ()
addFlag s flag = liftEwM $ do
(m, e, flags') <- getCmdLineState
putCmdLineState (m, e, mkGeneralLocated loc s : flags')
where loc = "addFlag by " ++ flag ++ " on the commandline"
type Mode = Either PreStartupMode PostStartupMode
type PostStartupMode = Either PreLoadMode PostLoadMode
data PreStartupMode
= ShowVersion -- ghc -V/--version
| ShowNumVersion -- ghc --numeric-version
| ShowSupportedExtensions -- ghc --supported-extensions
| Print String -- ghc --print-foo
showVersionMode, showNumVersionMode, showSupportedExtensionsMode :: Mode
showVersionMode = mkPreStartupMode ShowVersion
showNumVersionMode = mkPreStartupMode ShowNumVersion
showSupportedExtensionsMode = mkPreStartupMode ShowSupportedExtensions
mkPreStartupMode :: PreStartupMode -> Mode
mkPreStartupMode = Left
isShowVersionMode :: Mode -> Bool
isShowVersionMode (Left ShowVersion) = True
isShowVersionMode _ = False
isShowNumVersionMode :: Mode -> Bool
isShowNumVersionMode (Left ShowNumVersion) = True
isShowNumVersionMode _ = False
data PreLoadMode
= ShowGhcUsage -- ghc -?
| ShowGhciUsage -- ghci -?
| ShowInfo -- ghc --info
| PrintWithDynFlags (DynFlags -> String) -- ghc --print-foo
showGhcUsageMode, showGhciUsageMode, showInfoMode :: Mode
showGhcUsageMode = mkPreLoadMode ShowGhcUsage
showGhciUsageMode = mkPreLoadMode ShowGhciUsage
showInfoMode = mkPreLoadMode ShowInfo
printSetting :: String -> Mode
printSetting k = mkPreLoadMode (PrintWithDynFlags f)
where f dflags = fromMaybe (panic ("Setting not found: " ++ show k))
#if MIN_VERSION_ghc(7,2,0)
$ lookup k (compilerInfo dflags)
#else
$ fmap convertPrintable (lookup k compilerInfo)
where
convertPrintable (DynFlags.String s) = s
convertPrintable (DynFlags.FromDynFlags f) = f dflags
#endif
mkPreLoadMode :: PreLoadMode -> Mode
mkPreLoadMode = Right . Left
isShowGhcUsageMode :: Mode -> Bool
isShowGhcUsageMode (Right (Left ShowGhcUsage)) = True
isShowGhcUsageMode _ = False
isShowGhciUsageMode :: Mode -> Bool
isShowGhciUsageMode (Right (Left ShowGhciUsage)) = True
isShowGhciUsageMode _ = False
data PostLoadMode
= ShowInterface FilePath -- ghc --show-iface
| DoMkDependHS -- ghc -M
| StopBefore Phase -- ghc -E | -C | -S
-- StopBefore StopLn is the default
| DoMake -- ghc --make
| DoInteractive -- ghc --interactive
| DoEval [String] -- ghc -e foo -e bar => DoEval ["bar", "foo"]
| DoAbiHash -- ghc --abi-hash
doMkDependHSMode, doMakeMode, doInteractiveMode, doAbiHashMode :: Mode
doMkDependHSMode = mkPostLoadMode DoMkDependHS
doMakeMode = mkPostLoadMode DoMake
doInteractiveMode = mkPostLoadMode DoInteractive
doAbiHashMode = mkPostLoadMode DoAbiHash
showInterfaceMode :: FilePath -> Mode
showInterfaceMode fp = mkPostLoadMode (ShowInterface fp)
stopBeforeMode :: Phase -> Mode
stopBeforeMode phase = mkPostLoadMode (StopBefore phase)
doEvalMode :: String -> Mode
doEvalMode str = mkPostLoadMode (DoEval [str])
mkPostLoadMode :: PostLoadMode -> Mode
mkPostLoadMode = Right . Right
isDoInteractiveMode :: Mode -> Bool
isDoInteractiveMode (Right (Right DoInteractive)) = True
isDoInteractiveMode _ = False
isStopLnMode :: Mode -> Bool
isStopLnMode (Right (Right (StopBefore StopLn))) = True
isStopLnMode _ = False
isDoMakeMode :: Mode -> Bool
isDoMakeMode (Right (Right DoMake)) = True
isDoMakeMode _ = False
#ifdef GHCI
isInteractiveMode :: PostLoadMode -> Bool
isInteractiveMode DoInteractive = True
isInteractiveMode _ = False
#endif
-- isInterpretiveMode: byte-code compiler involved
isInterpretiveMode :: PostLoadMode -> Bool
isInterpretiveMode DoInteractive = True
isInterpretiveMode (DoEval _) = True
isInterpretiveMode _ = False
needsInputsMode :: PostLoadMode -> Bool
needsInputsMode DoMkDependHS = True
needsInputsMode (StopBefore _) = True
needsInputsMode DoMake = True
needsInputsMode _ = False
-- True if we are going to attempt to link in this mode.
-- (we might not actually link, depending on the GhcLink flag)
isLinkMode :: PostLoadMode -> Bool
isLinkMode (StopBefore StopLn) = True
isLinkMode DoMake = True
isLinkMode DoInteractive = True
isLinkMode (DoEval _) = True
isLinkMode _ = False
isCompManagerMode :: PostLoadMode -> Bool
isCompManagerMode DoMake = True
isCompManagerMode DoInteractive = True
isCompManagerMode (DoEval _) = True
isCompManagerMode _ = False
yesod-bin-1.2.4.1/Setup.lhs 0000644 0000000 0000000 00000000162 12241220146 013535 0 ustar 00 0000000 0000000 #!/usr/bin/env runhaskell
> module Main where
> import Distribution.Simple
> main :: IO ()
> main = defaultMain
yesod-bin-1.2.4.1/Build.hs 0000644 0000000 0000000 00000024623 12241220146 013330 0 ustar 00 0000000 0000000 {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Build
( getDeps
, touchDeps
, touch
, recompDeps
, isNewerThan
, safeReadFile
) where
import Control.Applicative ((<|>), many, (<$>))
import qualified Data.Attoparsec.Text as A
import Data.Char (isSpace, isUpper)
import qualified Data.Text as T
import Data.Text.Encoding (decodeUtf8With)
import Data.Text.Encoding.Error (lenientDecode)
import Data.ByteString (ByteString)
import qualified Data.ByteString as S
import Control.Exception (SomeException, try, IOException)
import Control.Exception.Lifted (handle)
import Control.Monad (when, filterM, forM, forM_, (>=>))
import Control.Monad.Trans.State (StateT, get, put, execStateT)
import Control.Monad.Trans.Writer (WriterT, tell, execWriterT)
import Control.Monad.IO.Class (MonadIO, liftIO)
import Control.Monad.Trans.Class (lift)
import Data.Monoid (Monoid (mappend, mempty))
import qualified Data.Map as Map
import qualified Data.Set as Set
import qualified System.Posix.Types
import System.Directory
import System.FilePath (takeExtension, replaceExtension, (>), takeDirectory)
import System.PosixCompat.Files (getFileStatus, setFileTimes,
accessTime, modificationTime)
import Text.Shakespeare (Deref)
import Text.Julius (juliusUsedIdentifiers)
import Text.Cassius (cassiusUsedIdentifiers)
import Text.Lucius (luciusUsedIdentifiers)
safeReadFile :: MonadIO m => FilePath -> m (Either IOException ByteString)
safeReadFile = liftIO . try . S.readFile
touch :: IO ()
touch = do
m <- handle (\(_ :: SomeException) -> return Map.empty) $ readFile touchCache >>= readIO
x <- fmap snd (getDeps [])
m' <- execStateT (execWriterT $ touchDeps id updateFileTime x) m
createDirectoryIfMissing True $ takeDirectory touchCache
writeFile touchCache $ show m'
where
touchCache = "dist/touchCache.txt"
-- | Returns True if any files were touched, otherwise False
recompDeps :: [FilePath] -> StateT (Map.Map FilePath (Set.Set Deref)) IO Bool
recompDeps =
fmap toBool . execWriterT . (liftIO . getDeps >=> touchDeps hiFile removeHi . snd)
where
toBool NoFilesTouched = False
toBool SomeFilesTouched = True
type Deps = Map.Map FilePath ([FilePath], ComparisonType)
getDeps :: [FilePath] -> IO ([FilePath], Deps)
getDeps hsSourceDirs = do
let defSrcDirs = case hsSourceDirs of
[] -> ["."]
ds -> ds
hss <- fmap concat $ mapM findHaskellFiles defSrcDirs
deps' <- mapM determineDeps hss
return $ (hss, fixDeps $ zip hss deps')
data AnyFilesTouched = NoFilesTouched | SomeFilesTouched
instance Monoid AnyFilesTouched where
mempty = NoFilesTouched
mappend NoFilesTouched NoFilesTouched = mempty
mappend _ _ = SomeFilesTouched
touchDeps :: (FilePath -> FilePath) ->
(FilePath -> FilePath -> IO ()) ->
Deps -> WriterT AnyFilesTouched (StateT (Map.Map FilePath (Set.Set Deref)) IO) ()
touchDeps f action deps = (mapM_ go . Map.toList) deps
where
go (x, (ys, ct)) = do
isChanged <- handle (\(_ :: SomeException) -> return True) $ lift $
case ct of
AlwaysOutdated -> return True
CompareUsedIdentifiers getDerefs -> do
derefMap <- get
ebs <- safeReadFile x
let newDerefs =
case ebs of
Left _ -> Set.empty
Right bs -> Set.fromList $ getDerefs $ T.unpack $ decodeUtf8With lenientDecode bs
put $ Map.insert x newDerefs derefMap
case Map.lookup x derefMap of
Just oldDerefs | oldDerefs == newDerefs -> return False
_ -> return True
when isChanged $ forM_ ys $ \y -> do
n <- liftIO $ x `isNewerThan` f y
when n $ do
liftIO $ putStrLn ("Forcing recompile for " ++ y ++ " because of " ++ x)
liftIO $ action x y
tell SomeFilesTouched
-- | remove the .hi files for a .hs file, thereby forcing a recompile
removeHi :: FilePath -> FilePath -> IO ()
removeHi _ hs = mapM_ removeFile' hiFiles
where
removeFile' file = try' (removeFile file) >> return ()
hiFiles = map (\e -> "dist/build" > replaceExtension hs e)
["hi", "p_hi"]
-- | change file mtime of .hs file to that of the dependency
updateFileTime :: FilePath -> FilePath -> IO ()
updateFileTime x hs = do
(_ , modx) <- getFileStatus' x
(access, _ ) <- getFileStatus' hs
_ <- try' (setFileTimes hs access modx)
return ()
hiFile :: FilePath -> FilePath
hiFile hs = "dist/build" > replaceExtension hs "hi"
try' :: IO x -> IO (Either SomeException x)
try' = try
isNewerThan :: FilePath -> FilePath -> IO Bool
isNewerThan f1 f2 = do
(_, mod1) <- getFileStatus' f1
(_, mod2) <- getFileStatus' f2
return (mod1 > mod2)
getFileStatus' :: FilePath ->
IO (System.Posix.Types.EpochTime, System.Posix.Types.EpochTime)
getFileStatus' fp = do
efs <- try' $ getFileStatus fp
case efs of
Left _ -> return (0, 0)
Right fs -> return (accessTime fs, modificationTime fs)
fixDeps :: [(FilePath, [(ComparisonType, FilePath)])] -> Deps
fixDeps =
Map.unionsWith combine . map go
where
go :: (FilePath, [(ComparisonType, FilePath)]) -> Deps
go (x, ys) = Map.fromList $ map (\(ct, y) -> (y, ([x], ct))) ys
combine (ys1, ct) (ys2, _) = (ys1 `mappend` ys2, ct)
findHaskellFiles :: FilePath -> IO [FilePath]
findHaskellFiles path = do
contents <- getDirectoryContents path
fmap concat $ mapM go contents
where
go ('.':_) = return []
go filename = do
d <- doesDirectoryExist full
if not d
then if isHaskellFile
then return [full]
else return []
else if isHaskellDir
then findHaskellFiles full
else return []
where
-- this could fail on unicode
isHaskellDir = isUpper (head filename)
isHaskellFile = takeExtension filename `elem` watch_files
full = path > filename
watch_files = [".hs", ".lhs"]
data TempType = StaticFiles FilePath
| Verbatim | Messages FilePath | Hamlet | Widget | Julius | Cassius | Lucius
deriving Show
-- | How to tell if a file is outdated.
data ComparisonType = AlwaysOutdated
| CompareUsedIdentifiers (String -> [Deref])
determineDeps :: FilePath -> IO [(ComparisonType, FilePath)]
determineDeps x = do
y <- safeReadFile x
case y of
Left _ -> return []
Right bs -> do
let z = A.parseOnly (many $ (parser <|> (A.anyChar >> return Nothing)))
$ decodeUtf8With lenientDecode bs
case z of
Left _ -> return []
Right r -> mapM go r >>= filterM (doesFileExist . snd) . concat
where
go (Just (StaticFiles fp, _)) = map ((,) AlwaysOutdated) <$> getFolderContents fp
go (Just (Hamlet, f)) = return [(AlwaysOutdated, f)]
go (Just (Widget, f)) = return
[ (AlwaysOutdated, "templates/" ++ f ++ ".hamlet")
, (CompareUsedIdentifiers $ map fst . juliusUsedIdentifiers, "templates/" ++ f ++ ".julius")
, (CompareUsedIdentifiers $ map fst . luciusUsedIdentifiers, "templates/" ++ f ++ ".lucius")
, (CompareUsedIdentifiers $ map fst . cassiusUsedIdentifiers, "templates/" ++ f ++ ".cassius")
]
go (Just (Julius, f)) = return [(CompareUsedIdentifiers $ map fst . juliusUsedIdentifiers, f)]
go (Just (Cassius, f)) = return [(CompareUsedIdentifiers $ map fst . cassiusUsedIdentifiers, f)]
go (Just (Lucius, f)) = return [(CompareUsedIdentifiers $ map fst . luciusUsedIdentifiers, f)]
go (Just (Verbatim, f)) = return [(AlwaysOutdated, f)]
go (Just (Messages f, _)) = map ((,) AlwaysOutdated) <$> getFolderContents f
go Nothing = return []
parser = do
ty <- (do _ <- A.string "\nstaticFiles \""
x' <- A.many1 $ A.satisfy (/= '"')
return $ StaticFiles x')
<|> (A.string "$(parseRoutesFile " >> return Verbatim)
<|> (A.string "$(hamletFile " >> return Hamlet)
<|> (A.string "$(ihamletFile " >> return Hamlet)
<|> (A.string "$(whamletFile " >> return Hamlet)
<|> (A.string "$(html " >> return Hamlet)
<|> (A.string "$(widgetFile " >> return Widget)
<|> (A.string "$(Settings.hamletFile " >> return Hamlet)
<|> (A.string "$(Settings.widgetFile " >> return Widget)
<|> (A.string "$(juliusFile " >> return Julius)
<|> (A.string "$(cassiusFile " >> return Cassius)
<|> (A.string "$(luciusFile " >> return Lucius)
<|> (A.string "$(persistFile " >> return Verbatim)
<|> (
A.string "$(persistFileWith " >>
A.many1 (A.satisfy (/= '"')) >>
return Verbatim)
<|> (do
_ <- A.string "\nmkMessage \""
A.skipWhile (/= '"')
_ <- A.string "\" \""
x' <- A.many1 $ A.satisfy (/= '"')
_ <- A.string "\" \""
_y <- A.many1 $ A.satisfy (/= '"')
_ <- A.string "\""
return $ Messages x')
case ty of
Messages{} -> return $ Just (ty, "")
StaticFiles{} -> return $ Just (ty, "")
_ -> do
A.skipWhile isSpace
_ <- A.char '"'
y <- A.many1 $ A.satisfy (/= '"')
_ <- A.char '"'
A.skipWhile isSpace
_ <- A.char ')'
return $ Just (ty, y)
getFolderContents :: FilePath -> IO [FilePath]
getFolderContents fp = do
cs <- getDirectoryContents fp
let notHidden ('.':_) = False
notHidden ('t':"mp") = False
notHidden ('f':"ay") = False
notHidden _ = True
fmap concat $ forM (filter notHidden cs) $ \c -> do
let f = fp ++ '/' : c
isFile <- doesFileExist f
if isFile then return [f] else getFolderContents f
yesod-bin-1.2.4.1/input/ 0000755 0000000 0000000 00000000000 12241220146 013065 5 ustar 00 0000000 0000000 yesod-bin-1.2.4.1/input/done.cg 0000644 0000000 0000000 00000001313 12241220146 014323 0 ustar 00 0000000 0000000
---------------------------------------
___
{-) |\
[m,].-"-. /
[][__][__] \(/\__/\)/
[__][__][__][__]~~~~ | |
[][__][__][__][__][] / |
[__][__][__][__][__]| /| |
[][__][__][__][__][]| || | ~~~~
ejm [__][__][__][__][__]__,__, \__/
---------------------------------------
The foundation for your web application has been built.
There are a lot of resources to help you use Yesod.
Start with the book: http://www.yesodweb.com/book
Take part in the community: http://yesodweb.com/page/community
Start your project:
cd PROJECTNAME && cabal sandbox init && cabal install && yesod devel
yesod-bin-1.2.4.1/input/welcome.cg 0000644 0000000 0000000 00000000267 12241220146 015040 0 ustar 00 0000000 0000000 Welcome to the Yesod scaffolder.
I'm going to be creating a skeleton Yesod project for you.
What do you want to call your project? We'll use this for the cabal name.
Project name:
yesod-bin-1.2.4.1/input/database.cg 0000644 0000000 0000000 00000000703 12241220146 015144 0 ustar 00 0000000 0000000 Yesod uses Persistent for its (you guessed it) persistence layer.
This tool will build in either SQLite or PostgreSQL or MongoDB support for you.
We recommend starting with SQLite: it has no dependencies.
s = sqlite
p = postgresql
pf = postgresql + Fay (experimental)
mongo = mongodb
mysql = MySQL
simple = no database, no auth
url = Let me specify URL containing a site (advanced)
So, what'll it be?
yesod-bin-1.2.4.1/hsfiles/ 0000755 0000000 0000000 00000000000 12241220146 013363 5 ustar 00 0000000 0000000 yesod-bin-1.2.4.1/hsfiles/sqlite.hsfiles 0000644 0000000 0000000 00000603567 12241220146 016264 0 ustar 00 0000000 0000000 {-# START_FILE .ghci #-}
:set -i.:config:dist/build/autogen
:set -XCPP -XTemplateHaskell -XQuasiQuotes -XTypeFamilies -XFlexibleContexts -XGADTs -XOverloadedStrings -XMultiParamTypeClasses -XGeneralizedNewtypeDeriving -XEmptyDataDecls -XDeriveDataTypeable
{-# START_FILE .gitignore #-}
dist*
static/tmp/
config/client_session_key.aes
*.hi
*.o
*.sqlite3
.hsenv*
cabal-dev/
yesod-devel/
.cabal-sandbox
cabal.sandbox.config
{-# START_FILE Application.hs #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Application
( makeApplication
, getApplicationDev
, makeFoundation
) where
import Import
import Settings
import Yesod.Auth
import Yesod.Default.Config
import Yesod.Default.Main
import Yesod.Default.Handlers
import Network.Wai.Middleware.RequestLogger
import qualified Database.Persist
import Database.Persist.Sql (runMigration)
import Network.HTTP.Conduit (newManager, def)
import Control.Monad.Logger (runLoggingT)
import System.IO (stdout)
import System.Log.FastLogger (mkLogger)
-- Import all relevant handler modules here.
-- Don't forget to add new modules to your cabal file!
import Handler.Home
-- This line actually creates our YesodDispatch instance. It is the second half
-- of the call to mkYesodData which occurs in Foundation.hs. Please see the
-- comments there for more details.
mkYesodDispatch "App" resourcesApp
-- This function allocates resources (such as a database connection pool),
-- performs initialization and creates a WAI application. This is also the
-- place to put your migrate statements to have automatic database
-- migrations handled by Yesod.
makeApplication :: AppConfig DefaultEnv Extra -> IO Application
makeApplication conf = do
foundation <- makeFoundation conf
-- Initialize the logging middleware
logWare <- mkRequestLogger def
{ outputFormat =
if development
then Detailed True
else Apache FromSocket
, destination = Logger $ appLogger foundation
}
-- Create the WAI application and apply middlewares
app <- toWaiAppPlain foundation
return $ logWare app
-- | Loads up any necessary settings, creates your foundation datatype, and
-- performs some initialization.
makeFoundation :: AppConfig DefaultEnv Extra -> IO App
makeFoundation conf = do
manager <- newManager def
s <- staticSite
dbconf <- withYamlEnvironment "config/sqlite.yml" (appEnv conf)
Database.Persist.loadConfig >>=
Database.Persist.applyEnv
p <- Database.Persist.createPoolConfig (dbconf :: Settings.PersistConf)
logger <- mkLogger True stdout
let foundation = App conf s p manager dbconf logger
-- Perform database migration using our application's logging settings.
runLoggingT
(Database.Persist.runPool dbconf (runMigration migrateAll) p)
(messageLoggerSource foundation logger)
return foundation
-- for yesod devel
getApplicationDev :: IO (Int, Application)
getApplicationDev =
defaultDevelApp loader makeApplication
where
loader = Yesod.Default.Config.loadConfig (configSettings Development)
{ csParseExtra = parseExtra
}
{-# START_FILE Foundation.hs #-}
module Foundation where
import Prelude
import Yesod
import Yesod.Static
import Yesod.Auth
import Yesod.Auth.BrowserId
import Yesod.Auth.GoogleEmail
import Yesod.Default.Config
import Yesod.Default.Util (addStaticContentExternal)
import Network.HTTP.Conduit (Manager)
import qualified Settings
import Settings.Development (development)
import qualified Database.Persist
import Database.Persist.Sql (SqlPersistT)
import Settings.StaticFiles
import Settings (widgetFile, Extra (..))
import Model
import Text.Jasmine (minifym)
import Text.Hamlet (hamletFile)
import System.Log.FastLogger (Logger)
-- | The site argument for your application. This can be a good place to
-- keep settings and values requiring initialization before your application
-- starts running, such as database connections. Every handler will have
-- access to the data present here.
data App = App
{ settings :: AppConfig DefaultEnv Extra
, getStatic :: Static -- ^ Settings for static file serving.
, connPool :: Database.Persist.PersistConfigPool Settings.PersistConf -- ^ Database connection pool.
, httpManager :: Manager
, persistConfig :: Settings.PersistConf
, appLogger :: Logger
}
-- Set up i18n messages. See the message folder.
mkMessage "App" "messages" "en"
-- This is where we define all of the routes in our application. For a full
-- explanation of the syntax, please see:
-- http://www.yesodweb.com/book/routing-and-handlers
--
-- Note that this is really half the story; in Application.hs, mkYesodDispatch
-- generates the rest of the code. Please see the linked documentation for an
-- explanation for this split.
mkYesodData "App" $(parseRoutesFile "config/routes")
type Form x = Html -> MForm (HandlerT App IO) (FormResult x, Widget)
-- Please see the documentation for the Yesod typeclass. There are a number
-- of settings which can be configured by overriding methods here.
instance Yesod App where
approot = ApprootMaster $ appRoot . settings
-- Store session data on the client in encrypted cookies,
-- default session idle timeout is 120 minutes
makeSessionBackend _ = fmap Just $ defaultClientSessionBackend
(120 * 60) -- 120 minutes
"config/client_session_key.aes"
defaultLayout widget = do
master <- getYesod
mmsg <- getMessage
-- We break up the default layout into two components:
-- default-layout is the contents of the body tag, and
-- default-layout-wrapper is the entire page. Since the final
-- value passed to hamletToRepHtml cannot be a widget, this allows
-- you to use normal widget features in default-layout.
pc <- widgetToPageContent $ do
$(combineStylesheets 'StaticR
[ css_normalize_css
, css_bootstrap_css
])
$(widgetFile "default-layout")
giveUrlRenderer $(hamletFile "templates/default-layout-wrapper.hamlet")
-- This is done to provide an optimization for serving static files from
-- a separate domain. Please see the staticRoot setting in Settings.hs
urlRenderOverride y (StaticR s) =
Just $ uncurry (joinPath y (Settings.staticRoot $ settings y)) $ renderRoute s
urlRenderOverride _ _ = Nothing
-- The page to be redirected to when authentication is required.
authRoute _ = Just $ AuthR LoginR
-- This function creates static content files in the static folder
-- and names them based on a hash of their content. This allows
-- expiration dates to be set far in the future without worry of
-- users receiving stale content.
addStaticContent =
addStaticContentExternal minifym genFileName Settings.staticDir (StaticR . flip StaticRoute [])
where
-- Generate a unique filename based on the content itself
genFileName lbs
| development = "autogen-" ++ base64md5 lbs
| otherwise = base64md5 lbs
-- Place Javascript at bottom of the body tag so the rest of the page loads first
jsLoader _ = BottomOfBody
-- What messages should be logged. The following includes all messages when
-- in development, and warnings and errors in production.
shouldLog _ _source level =
development || level == LevelWarn || level == LevelError
makeLogger = return . appLogger
-- How to run database actions.
instance YesodPersist App where
type YesodPersistBackend App = SqlPersistT
runDB = defaultRunDB persistConfig connPool
instance YesodPersistRunner App where
getDBRunner = defaultGetDBRunner connPool
instance YesodAuth App where
type AuthId App = UserId
-- Where to send a user after successful login
loginDest _ = HomeR
-- Where to send a user after logout
logoutDest _ = HomeR
getAuthId creds = runDB $ do
x <- getBy $ UniqueUser $ credsIdent creds
case x of
Just (Entity uid _) -> return $ Just uid
Nothing -> do
fmap Just $ insert $ User (credsIdent creds) Nothing
-- You can add other plugins like BrowserID, email or OAuth here
authPlugins _ = [authBrowserId def, authGoogleEmail]
authHttpManager = httpManager
-- This instance is required to use forms. You can modify renderMessage to
-- achieve customized and internationalized form validation messages.
instance RenderMessage App FormMessage where
renderMessage _ _ = defaultFormMessage
-- | Get the 'Extra' value, used to hold data from the settings.yml file.
getExtra :: Handler Extra
getExtra = fmap (appExtra . settings) getYesod
-- Note: previous versions of the scaffolding included a deliver function to
-- send emails. Unfortunately, there are too many different options for us to
-- give a reasonable default. Instead, the information is available on the
-- wiki:
--
-- https://github.com/yesodweb/yesod/wiki/Sending-email
{-# START_FILE Handler/Home.hs #-}
{-# LANGUAGE TupleSections, OverloadedStrings #-}
module Handler.Home where
import Import
-- This is a handler function for the GET request method on the HomeR
-- resource pattern. All of your resource patterns are defined in
-- config/routes
--
-- The majority of the code you will write in Yesod lives in these handler
-- functions. You can spread them across multiple files if you are so
-- inclined, or create a single monolithic file.
getHomeR :: Handler Html
getHomeR = do
(formWidget, formEnctype) <- generateFormPost sampleForm
let submission = Nothing :: Maybe (FileInfo, Text)
handlerName = "getHomeR" :: Text
defaultLayout $ do
aDomId <- newIdent
setTitle "Welcome To Yesod!"
$(widgetFile "homepage")
postHomeR :: Handler Html
postHomeR = do
((result, formWidget), formEnctype) <- runFormPost sampleForm
let handlerName = "postHomeR" :: Text
submission = case result of
FormSuccess res -> Just res
_ -> Nothing
defaultLayout $ do
aDomId <- newIdent
setTitle "Welcome To Yesod!"
$(widgetFile "homepage")
sampleForm :: Form (FileInfo, Text)
sampleForm = renderDivs $ (,)
<$> fileAFormReq "Choose a file"
<*> areq textField "What's on the file?" Nothing
{-# START_FILE Import.hs #-}
module Import
( module Import
) where
import Prelude as Import hiding (head, init, last,
readFile, tail, writeFile)
import Yesod as Import hiding (Route (..))
import Control.Applicative as Import (pure, (<$>), (<*>))
import Data.Text as Import (Text)
import Foundation as Import
import Model as Import
import Settings as Import
import Settings.Development as Import
import Settings.StaticFiles as Import
#if __GLASGOW_HASKELL__ >= 704
import Data.Monoid as Import
(Monoid (mappend, mempty, mconcat),
(<>))
#else
import Data.Monoid as Import
(Monoid (mappend, mempty, mconcat))
infixr 5 <>
(<>) :: Monoid m => m -> m -> m
(<>) = mappend
#endif
{-# START_FILE Model.hs #-}
module Model where
import Prelude
import Yesod
import Data.Text (Text)
import Database.Persist.Quasi
import Data.Typeable (Typeable)
-- You can define all of your database entities in the entities file.
-- You can find more information on persistent and how to declare entities
-- at:
-- http://www.yesodweb.com/book/persistent/
share [mkPersist sqlOnlySettings, mkMigrate "migrateAll"]
$(persistFileWith lowerCaseSettings "config/models")
{-# START_FILE PROJECTNAME.cabal #-}
name: PROJECTNAME
version: 0.0.0
cabal-version: >= 1.8
build-type: Simple
Flag dev
Description: Turn on development settings, like auto-reload templates.
Default: False
Flag library-only
Description: Build for use with "yesod devel"
Default: False
library
exposed-modules: Application
Foundation
Import
Model
Settings
Settings.StaticFiles
Settings.Development
Handler.Home
if flag(dev) || flag(library-only)
cpp-options: -DDEVELOPMENT
ghc-options: -Wall -O0
else
ghc-options: -Wall -O2
extensions: TemplateHaskell
QuasiQuotes
OverloadedStrings
NoImplicitPrelude
CPP
MultiParamTypeClasses
TypeFamilies
GADTs
GeneralizedNewtypeDeriving
FlexibleContexts
EmptyDataDecls
NoMonomorphismRestriction
DeriveDataTypeable
build-depends: base >= 4 && < 5
, yesod >= 1.2 && < 1.3
, yesod-core >= 1.2 && < 1.3
, yesod-auth >= 1.2 && < 1.3
, yesod-static >= 1.2 && < 1.3
, yesod-form >= 1.3 && < 1.4
, bytestring >= 0.9 && < 0.11
, text >= 0.11 && < 0.12
, persistent >= 1.2 && < 1.3
, persistent-sqlite >= 1.2 && < 1.3
, persistent-template >= 1.2 && < 1.3
, template-haskell
, hamlet >= 1.1 && < 1.2
, shakespeare-css >= 1.0 && < 1.1
, shakespeare-js >= 1.2 && < 1.3
, shakespeare-text >= 1.0 && < 1.1
, hjsmin >= 0.1 && < 0.2
, monad-control >= 0.3 && < 0.4
, wai-extra >= 1.3 && < 1.4
, yaml >= 0.8 && < 0.9
, http-conduit >= 1.9 && < 1.10
, directory >= 1.1 && < 1.3
, warp >= 1.3 && < 1.4
, data-default
, aeson
, conduit >= 1.0
, monad-logger >= 0.3
, fast-logger >= 0.3
executable PROJECTNAME
if flag(library-only)
Buildable: False
main-is: main.hs
hs-source-dirs: app
build-depends: base
, PROJECTNAME
, yesod
ghc-options: -threaded -O2
test-suite test
type: exitcode-stdio-1.0
main-is: main.hs
hs-source-dirs: tests
ghc-options: -Wall
build-depends: base
, PROJECTNAME
, yesod-test >= 1.2 && < 1.3
, yesod-core
, yesod
, persistent
, persistent-sqlite
, resourcet
, monad-logger
, transformers
, hspec
{-# START_FILE Settings.hs #-}
-- | Settings are centralized, as much as possible, into this file. This
-- includes database connection settings, static file locations, etc.
-- In addition, you can configure a number of different aspects of Yesod
-- by overriding methods in the Yesod typeclass. That instance is
-- declared in the Foundation.hs file.
module Settings where
import Prelude
import Text.Shakespeare.Text (st)
import Language.Haskell.TH.Syntax
import Database.Persist.Sqlite (SqliteConf)
import Yesod.Default.Config
import Yesod.Default.Util
import Data.Text (Text)
import Data.Yaml
import Control.Applicative
import Settings.Development
import Data.Default (def)
import Text.Hamlet
-- | Which Persistent backend this site is using.
type PersistConf = SqliteConf
-- Static setting below. Changing these requires a recompile
-- | The location of static files on your system. This is a file system
-- path. The default value works properly with your scaffolded site.
staticDir :: FilePath
staticDir = "static"
-- | The base URL for your static files. As you can see by the default
-- value, this can simply be "static" appended to your application root.
-- A powerful optimization can be serving static files from a separate
-- domain name. This allows you to use a web server optimized for static
-- files, more easily set expires and cache values, and avoid possibly
-- costly transference of cookies on static files. For more information,
-- please see:
-- http://code.google.com/speed/page-speed/docs/request.html#ServeFromCookielessDomain
--
-- If you change the resource pattern for StaticR in Foundation.hs, you will
-- have to make a corresponding change here.
--
-- To see how this value is used, see urlRenderOverride in Foundation.hs
staticRoot :: AppConfig DefaultEnv x -> Text
staticRoot conf = [st|#{appRoot conf}/static|]
-- | Settings for 'widgetFile', such as which template languages to support and
-- default Hamlet settings.
--
-- For more information on modifying behavior, see:
--
-- https://github.com/yesodweb/yesod/wiki/Overriding-widgetFile
widgetFileSettings :: WidgetFileSettings
widgetFileSettings = def
{ wfsHamletSettings = defaultHamletSettings
{ hamletNewlines = AlwaysNewlines
}
}
-- The rest of this file contains settings which rarely need changing by a
-- user.
widgetFile :: String -> Q Exp
widgetFile = (if development then widgetFileReload
else widgetFileNoReload)
widgetFileSettings
data Extra = Extra
{ extraCopyright :: Text
, extraAnalytics :: Maybe Text -- ^ Google Analytics
} deriving Show
parseExtra :: DefaultEnv -> Object -> Parser Extra
parseExtra _ o = Extra
<$> o .: "copyright"
<*> o .:? "analytics"
{-# START_FILE Settings/Development.hs #-}
module Settings.Development where
import Prelude
development :: Bool
development =
#if DEVELOPMENT
True
#else
False
#endif
production :: Bool
production = not development
{-# START_FILE Settings/StaticFiles.hs #-}
module Settings.StaticFiles where
import Prelude (IO)
import Yesod.Static
import qualified Yesod.Static as Static
import Settings (staticDir)
import Settings.Development
import Language.Haskell.TH (Q, Exp, Name)
import Data.Default (def)
-- | use this to create your static file serving site
staticSite :: IO Static.Static
staticSite = if development then Static.staticDevel staticDir
else Static.static staticDir
-- | This generates easy references to files in the static directory at compile time,
-- giving you compile-time verification that referenced files exist.
-- Warning: any files added to your static directory during run-time can't be
-- accessed this way. You'll have to use their FilePath or URL to access them.
$(staticFiles Settings.staticDir)
combineSettings :: CombineSettings
combineSettings = def
-- The following two functions can be used to combine multiple CSS or JS files
-- at compile time to decrease the number of http requests.
-- Sample usage (inside a Widget):
--
-- > $(combineStylesheets 'StaticR [style1_css, style2_css])
combineStylesheets :: Name -> [Route Static] -> Q Exp
combineStylesheets = combineStylesheets' development combineSettings
combineScripts :: Name -> [Route Static] -> Q Exp
combineScripts = combineScripts' development combineSettings
{-# START_FILE app/main.hs #-}
import Prelude (IO)
import Yesod.Default.Config (fromArgs)
import Yesod.Default.Main (defaultMain)
import Settings (parseExtra)
import Application (makeApplication)
main :: IO ()
main = defaultMain (fromArgs parseExtra) makeApplication
{-# START_FILE BASE64 config/favicon.ico #-}
AAABAAIAEBAAAAEAIABoBAAAJgAAABAQAgABAAEAsAAAAI4EAAAoAAAAEAAAACAAAAABACAAAAAA
AAAAAAAAAAAAAAAAAAAAAAAAAAAApl4sAAAAAAAAAAAAAAAAAUEpGyNpSjaIg2NO2ZBvWfqTc13/
jW1X9YNhTMZrSTNkUTMfDwAAAAAAAAAAAAAAAAAAAAAAAAAANR0NClk6JmF+W0Txj2xV/41qVP+M
aVP/jGlS/4xpUv+MaVL/i2dQ/3pVPdNeOiEzQRsBAgAAAAAAAAAAMBgHAlIxG1h5UDb/h15D9n5W
PPZ4TzXmeVE303hQNtV4UDbVeFA11XdQNdV5UTfbbUUpx1UsEBgAAAAAAAAFADIVAwlULxY/f1M1
4dOffryecFHMXTIVhAAAAAURAAAOEwAADxQAAA8TAAAPEAAADigEABFNJAkZTSQJCRAHAQdKIARt
OxUAC1kvE3qQYEDfzJt5wXtOL9pQJAa0UScKjVInCo1SJwqNUSYJjVElCY1RJQmLUSUHslEjBGcu
EgAuVSQC/00eAGAYAAAPXzAQuLGAXs6ygV/PYTESwkMXAFRGHgI3Rx4BPEceATxHHQE7RBsBMkwf
AqlUIQHgQhoAaVUhAP9TIQDhSBwAI0EXAD5xQSHbzJp4wJRiQtBRIgKuRxsAb0kdAGpJHQBqSR0A
e04fAJNJHQClVCEA/0YcAIRVIgD/VSIA7E0fADQyDQAyaToa1MqXdMLJl3bBc0Ii6UscAJFFGgBE
RRoAQUIZAFlRIADpVSIA/1UiAP9JHwN9WicG/1QhAIMAAAAMVywPoaBtTNi6imnEsIBfya9+Xc1m
OBm2UycIilgqDYVVKQ2DVigJ4FwqCf5cKgr/Qx8GUGAwEc08EwAPTSgQY4dXN+LPnXy9g1c54XtM
LevJl3a/k2RE3WY5Gv9mNxn/Zjga/2c5G/9oOhz/Zzka/DQYBRFZLRA1JhAAJHhML9XJlnTCqXxe
zXFHLPtxRyv/n3BR2MuZd7uFWjzmc0gt/nRKLv90Sy//dUww/21CJcIAAAAATCsURXRONdR+Vjr5
j2ZL5oJbQfN+Vz3/flg//4NcQfePZkrogVk/8n5YP/6BW0H/gVtD/oBaQf9qQCRIJAgAAFAxHRt4
VDzVjWpS/4lmT/6LZ1D/jGlS/4xpU/6MaVL/i2hS/otpUv6Na1T+jmtV/o9tV/98Vj2cYzoeBgAA
AAAGAgAAZ0cyMIVkTtqae2f/mXpm/5l5Zf6Zemb+mXpm/5p6Zv+ae2f+mnxp/5p7Z/+HZE2qdE84
FAAAAAAAAAAAAAAAAAAAAABrTDgfhWVQnp2Abf+njHv/pot6/6aMev+njHv/qI18/5t+avOHZU9y
fFc/DgAAAAAAAAAAJhABAAAAAAAAAAAAyqmXADYdCQNoSDQjh2hUbpd6aJ+Zfmurl3pnlYZkTlpw
TDYTX0IxAbNeMwAAAAAAsoFfAPgfAADwBwAA4AMAAOH/AADwAQAAsPwAAJh4AAAYOAAAkAAAALAA
AADgAAAAwAEAAMABAADgAwAA8A8AAP4/AAAoAAAAEAAAACAAAAABAAEAAAAAAAAAAAAAAAAAAAAA
AAAAAAAAAAAA////AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA
AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA
AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA==
{-# START_FILE config/keter.yaml #-}
exec: ../dist/build/PROJECTNAME/PROJECTNAME
args:
- production
host: <>
# Use the following to automatically copy your bundle upon creation via `yesod
# keter`. Uses `scp` internally, so you can set it to a remote destination
# copy-to: user@host:/opt/keter/incoming
{-# START_FILE config/models #-}
User
ident Text
password Text Maybe
UniqueUser ident
deriving Typeable
Email
email Text
user UserId Maybe
verkey Text Maybe
UniqueEmail email
-- By default this file is used in Model.hs (which is imported by Foundation.hs)
{-# START_FILE config/robots.txt #-}
User-agent: *
{-# START_FILE config/routes #-}
/static StaticR Static getStatic
/auth AuthR Auth getAuth
/favicon.ico FaviconR GET
/robots.txt RobotsR GET
/ HomeR GET POST
{-# START_FILE config/settings.yml #-}
Default: &defaults
host: "*4" # any IPv4 host
port: 3000
approot: "http://localhost:3000"
copyright: Insert copyright statement here
#analytics: UA-YOURCODE
Development:
<<: *defaults
Testing:
<<: *defaults
Staging:
<<: *defaults
Production:
#approot: "http://www.example.com"
<<: *defaults
{-# START_FILE config/sqlite.yml #-}
Default: &defaults
database: PROJECTNAME.sqlite3
poolsize: 10
Development:
<<: *defaults
Testing:
database: PROJECTNAME_test.sqlite3
<<: *defaults
Staging:
database: PROJECTNAME_staging.sqlite3
poolsize: 100
<<: *defaults
Production:
database: PROJECTNAME_production.sqlite3
poolsize: 100
<<: *defaults
{-# START_FILE deploy/Procfile #-}
# Free deployment to Heroku.
#
# !! Warning: You must use a 64 bit machine to compile !!
#
# This could mean using a virtual machine. Give your VM as much memory as you can to speed up linking.
#
# Basic Yesod setup:
#
# * Move this file out of the deploy directory and into your root directory
#
# mv deploy/Procfile ./
#
# * Create an empty package.json
# echo '{ "name": "PROJECTNAME", "version": "0.0.1", "dependencies": {} }' >> package.json
#
# Postgresql Yesod setup:
#
# * add dependencies on the "heroku", "aeson" and "unordered-containers" packages in your cabal file
#
# * add code in Application.hs to use the heroku package and load the connection parameters.
# The below works for Postgresql.
#
# import Data.HashMap.Strict as H
# import Data.Aeson.Types as AT
# #ifndef DEVELOPMENT
# import qualified Web.Heroku
# #endif
#
#
#
# makeFoundation :: AppConfig DefaultEnv Extra -> Logger -> IO App
# makeFoundation conf setLogger = do
# manager <- newManager def
# s <- staticSite
# hconfig <- loadHerokuConfig
# dbconf <- withYamlEnvironment "config/postgresql.yml" (appEnv conf)
# (Database.Persist.Store.loadConfig . combineMappings hconfig) >>=
# Database.Persist.Store.applyEnv
# p <- Database.Persist.Store.createPoolConfig (dbconf :: Settings.PersistConfig)
# Database.Persist.Store.runPool dbconf (runMigration migrateAll) p
# return $ App conf setLogger s p manager dbconf
#
# #ifndef DEVELOPMENT
# canonicalizeKey :: (Text, val) -> (Text, val)
# canonicalizeKey ("dbname", val) = ("database", val)
# canonicalizeKey pair = pair
#
# toMapping :: [(Text, Text)] -> AT.Value
# toMapping xs = AT.Object $ M.fromList $ map (\(key, val) -> (key, AT.String val)) xs
# #endif
#
# combineMappings :: AT.Value -> AT.Value -> AT.Value
# combineMappings (AT.Object m1) (AT.Object m2) = AT.Object $ m1 `M.union` m2
# combineMappings _ _ = error "Data.Object is not a Mapping."
#
# loadHerokuConfig :: IO AT.Value
# loadHerokuConfig = do
# #ifdef DEVELOPMENT
# return $ AT.Object M.empty
# #else
# Web.Heroku.dbConnParams >>= return . toMapping . map canonicalizeKey
# #endif
# Heroku setup:
# Find the Heroku guide. Roughly:
#
# * sign up for a heroku account and register your ssh key
# * create a new application on the *cedar* stack
#
# * make your Yesod project the git repository for that application
# * create a deploy branch
#
# git checkout -b deploy
#
# Repeat these steps to deploy:
# * add your web executable binary (referenced below) to the git repository
#
# git checkout deploy
# git add ./dist/build/PROJECTNAME/PROJECTNAME
# git commit -m deploy
#
# * push to Heroku
#
# git push heroku deploy:master
# Heroku configuration that runs your app
web: ./dist/build/PROJECTNAME/PROJECTNAME production -p $PORT
{-# START_FILE devel.hs #-}
{-# LANGUAGE PackageImports #-}
import "PROJECTNAME" Application (getApplicationDev)
import Network.Wai.Handler.Warp
(runSettings, defaultSettings, settingsPort)
import Control.Concurrent (forkIO)
import System.Directory (doesFileExist, removeFile)
import System.Exit (exitSuccess)
import Control.Concurrent (threadDelay)
main :: IO ()
main = do
putStrLn "Starting devel application"
(port, app) <- getApplicationDev
forkIO $ runSettings defaultSettings
{ settingsPort = port
} app
loop
loop :: IO ()
loop = do
threadDelay 100000
e <- doesFileExist "yesod-devel/devel-terminate"
if e then terminateDevel else loop
terminateDevel :: IO ()
terminateDevel = exitSuccess
{-# START_FILE messages/en.msg #-}
Hello: Hello
{-# START_FILE static/css/bootstrap.css #-}
/*!
* Bootstrap v2.3.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;
line-height: 0;
content: "";
}
.clearfix:after {
clear: both;
}
.hide-text {
font: 0/0 a;
color: transparent;
text-shadow: none;
background-color: transparent;
border: 0;
}
.input-block-level {
display: block;
width: 100%;
min-height: 30px;
-webkit-box-sizing: border-box;
-moz-box-sizing: border-box;
box-sizing: border-box;
}
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 {
width: auto\9;
height: auto;
max-width: 100%;
vertical-align: middle;
border: 0;
-ms-interpolation-mode: bicubic;
}
#map_canvas img,
.google-maps img {
max-width: none;
}
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,
html input[type="button"],
input[type="reset"],
input[type="submit"] {
cursor: pointer;
-webkit-appearance: button;
}
label,
select,
button,
input[type="button"],
input[type="reset"],
input[type="submit"],
input[type="radio"],
input[type="checkbox"] {
cursor: pointer;
}
input[type="search"] {
-webkit-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;
}
@media print {
* {
color: #000 !important;
text-shadow: none !important;
background: transparent !important;
box-shadow: none !important;
}
a,
a:visited {
text-decoration: underline;
}
a[href]:after {
content: " (" attr(href) ")";
}
abbr[title]:after {
content: " (" attr(title) ")";
}
.ir a:after,
a[href^="javascript:"]:after,
a[href^="#"]:after {
content: "";
}
pre,
blockquote {
border: 1px solid #999;
page-break-inside: avoid;
}
thead {
display: table-header-group;
}
tr,
img {
page-break-inside: avoid;
}
img {
max-width: 100% !important;
}
@page {
margin: 0.5cm;
}
p,
h2,
h3 {
orphans: 3;
widows: 3;
}
h2,
h3 {
page-break-after: avoid;
}
}
body {
margin: 0;
font-family: "Helvetica Neue", Helvetica, Arial, sans-serif;
font-size: 14px;
line-height: 20px;
color: #333333;
background-color: #ffffff;
}
a {
color: #0088cc;
text-decoration: none;
}
a:hover,
a:focus {
color: #005580;
text-decoration: underline;
}
.img-rounded {
-webkit-border-radius: 6px;
-moz-border-radius: 6px;
border-radius: 6px;
}
.img-polaroid {
padding: 4px;
background-color: #fff;
border: 1px solid #ccc;
border: 1px solid rgba(0, 0, 0, 0.2);
-webkit-box-shadow: 0 1px 3px rgba(0, 0, 0, 0.1);
-moz-box-shadow: 0 1px 3px rgba(0, 0, 0, 0.1);
box-shadow: 0 1px 3px rgba(0, 0, 0, 0.1);
}
.img-circle {
-webkit-border-radius: 500px;
-moz-border-radius: 500px;
border-radius: 500px;
}
.row {
margin-left: -20px;
*zoom: 1;
}
.row:before,
.row:after {
display: table;
line-height: 0;
content: "";
}
.row:after {
clear: both;
}
[class*="span"] {
float: left;
min-height: 1px;
margin-left: 20px;
}
.container,
.navbar-static-top .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;
line-height: 0;
content: "";
}
.row-fluid:after {
clear: both;
}
.row-fluid [class*="span"] {
display: block;
float: left;
width: 100%;
min-height: 30px;
margin-left: 2.127659574468085%;
*margin-left: 2.074468085106383%;
-webkit-box-sizing: border-box;
-moz-box-sizing: border-box;
box-sizing: border-box;
}
.row-fluid [class*="span"]:first-child {
margin-left: 0;
}
.row-fluid .controls-row [class*="span"] + [class*="span"] {
margin-left: 2.127659574468085%;
}
.row-fluid .span12 {
width: 100%;
*width: 99.94680851063829%;
}
.row-fluid .span11 {
width: 91.48936170212765%;
*width: 91.43617021276594%;
}
.row-fluid .span10 {
width: 82.97872340425532%;
*width: 82.92553191489361%;
}
.row-fluid .span9 {
width: 74.46808510638297%;
*width: 74.41489361702126%;
}
.row-fluid .span8 {
width: 65.95744680851064%;
*width: 65.90425531914893%;
}
.row-fluid .span7 {
width: 57.44680851063829%;
*width: 57.39361702127659%;
}
.row-fluid .span6 {
width: 48.93617021276595%;
*width: 48.88297872340425%;
}
.row-fluid .span5 {
width: 40.42553191489362%;
*width: 40.37234042553192%;
}
.row-fluid .span4 {
width: 31.914893617021278%;
*width: 31.861702127659576%;
}
.row-fluid .span3 {
width: 23.404255319148934%;
*width: 23.351063829787233%;
}
.row-fluid .span2 {
width: 14.893617021276595%;
*width: 14.840425531914894%;
}
.row-fluid .span1 {
width: 6.382978723404255%;
*width: 6.329787234042553%;
}
.row-fluid .offset12 {
margin-left: 104.25531914893617%;
*margin-left: 104.14893617021275%;
}
.row-fluid .offset12:first-child {
margin-left: 102.12765957446808%;
*margin-left: 102.02127659574467%;
}
.row-fluid .offset11 {
margin-left: 95.74468085106382%;
*margin-left: 95.6382978723404%;
}
.row-fluid .offset11:first-child {
margin-left: 93.61702127659574%;
*margin-left: 93.51063829787232%;
}
.row-fluid .offset10 {
margin-left: 87.23404255319149%;
*margin-left: 87.12765957446807%;
}
.row-fluid .offset10:first-child {
margin-left: 85.1063829787234%;
*margin-left: 84.99999999999999%;
}
.row-fluid .offset9 {
margin-left: 78.72340425531914%;
*margin-left: 78.61702127659572%;
}
.row-fluid .offset9:first-child {
margin-left: 76.59574468085106%;
*margin-left: 76.48936170212764%;
}
.row-fluid .offset8 {
margin-left: 70.2127659574468%;
*margin-left: 70.10638297872339%;
}
.row-fluid .offset8:first-child {
margin-left: 68.08510638297872%;
*margin-left: 67.9787234042553%;
}
.row-fluid .offset7 {
margin-left: 61.70212765957446%;
*margin-left: 61.59574468085106%;
}
.row-fluid .offset7:first-child {
margin-left: 59.574468085106375%;
*margin-left: 59.46808510638297%;
}
.row-fluid .offset6 {
margin-left: 53.191489361702125%;
*margin-left: 53.085106382978715%;
}
.row-fluid .offset6:first-child {
margin-left: 51.063829787234035%;
*margin-left: 50.95744680851063%;
}
.row-fluid .offset5 {
margin-left: 44.68085106382979%;
*margin-left: 44.57446808510638%;
}
.row-fluid .offset5:first-child {
margin-left: 42.5531914893617%;
*margin-left: 42.4468085106383%;
}
.row-fluid .offset4 {
margin-left: 36.170212765957444%;
*margin-left: 36.06382978723405%;
}
.row-fluid .offset4:first-child {
margin-left: 34.04255319148936%;
*margin-left: 33.93617021276596%;
}
.row-fluid .offset3 {
margin-left: 27.659574468085104%;
*margin-left: 27.5531914893617%;
}
.row-fluid .offset3:first-child {
margin-left: 25.53191489361702%;
*margin-left: 25.425531914893618%;
}
.row-fluid .offset2 {
margin-left: 19.148936170212764%;
*margin-left: 19.04255319148936%;
}
.row-fluid .offset2:first-child {
margin-left: 17.02127659574468%;
*margin-left: 16.914893617021278%;
}
.row-fluid .offset1 {
margin-left: 10.638297872340425%;
*margin-left: 10.53191489361702%;
}
.row-fluid .offset1:first-child {
margin-left: 8.51063829787234%;
*margin-left: 8.404255319148938%;
}
[class*="span"].hide,
.row-fluid [class*="span"].hide {
display: none;
}
[class*="span"].pull-right,
.row-fluid [class*="span"].pull-right {
float: right;
}
.container {
margin-right: auto;
margin-left: auto;
*zoom: 1;
}
.container:before,
.container:after {
display: table;
line-height: 0;
content: "";
}
.container:after {
clear: both;
}
.container-fluid {
padding-right: 20px;
padding-left: 20px;
*zoom: 1;
}
.container-fluid:before,
.container-fluid:after {
display: table;
line-height: 0;
content: "";
}
.container-fluid:after {
clear: both;
}
p {
margin: 0 0 10px;
}
.lead {
margin-bottom: 20px;
font-size: 21px;
font-weight: 200;
line-height: 30px;
}
small {
font-size: 85%;
}
strong {
font-weight: bold;
}
em {
font-style: italic;
}
cite {
font-style: normal;
}
.muted {
color: #999999;
}
a.muted:hover,
a.muted:focus {
color: #808080;
}
.text-warning {
color: #c09853;
}
a.text-warning:hover,
a.text-warning:focus {
color: #a47e3c;
}
.text-error {
color: #b94a48;
}
a.text-error:hover,
a.text-error:focus {
color: #953b39;
}
.text-info {
color: #3a87ad;
}
a.text-info:hover,
a.text-info:focus {
color: #2d6987;
}
.text-success {
color: #468847;
}
a.text-success:hover,
a.text-success:focus {
color: #356635;
}
.text-left {
text-align: left;
}
.text-right {
text-align: right;
}
.text-center {
text-align: center;
}
h1,
h2,
h3,
h4,
h5,
h6 {
margin: 10px 0;
font-family: inherit;
font-weight: bold;
line-height: 20px;
color: inherit;
text-rendering: optimizelegibility;
}
h1 small,
h2 small,
h3 small,
h4 small,
h5 small,
h6 small {
font-weight: normal;
line-height: 1;
color: #999999;
}
h1,
h2,
h3 {
line-height: 40px;
}
h1 {
font-size: 38.5px;
}
h2 {
font-size: 31.5px;
}
h3 {
font-size: 24.5px;
}
h4 {
font-size: 17.5px;
}
h5 {
font-size: 14px;
}
h6 {
font-size: 11.9px;
}
h1 small {
font-size: 24.5px;
}
h2 small {
font-size: 17.5px;
}
h3 small {
font-size: 14px;
}
h4 small {
font-size: 14px;
}
.page-header {
padding-bottom: 9px;
margin: 20px 0 30px;
border-bottom: 1px solid #eeeeee;
}
ul,
ol {
padding: 0;
margin: 0 0 10px 25px;
}
ul ul,
ul ol,
ol ol,
ol ul {
margin-bottom: 0;
}
li {
line-height: 20px;
}
ul.unstyled,
ol.unstyled {
margin-left: 0;
list-style: none;
}
ul.inline,
ol.inline {
margin-left: 0;
list-style: none;
}
ul.inline > li,
ol.inline > li {
display: inline-block;
*display: inline;
padding-right: 5px;
padding-left: 5px;
*zoom: 1;
}
dl {
margin-bottom: 20px;
}
dt,
dd {
line-height: 20px;
}
dt {
font-weight: bold;
}
dd {
margin-left: 10px;
}
.dl-horizontal {
*zoom: 1;
}
.dl-horizontal:before,
.dl-horizontal:after {
display: table;
line-height: 0;
content: "";
}
.dl-horizontal:after {
clear: both;
}
.dl-horizontal dt {
float: left;
width: 160px;
overflow: hidden;
clear: left;
text-align: right;
text-overflow: ellipsis;
white-space: nowrap;
}
.dl-horizontal dd {
margin-left: 180px;
}
hr {
margin: 20px 0;
border: 0;
border-top: 1px solid #eeeeee;
border-bottom: 1px solid #ffffff;
}
abbr[title],
abbr[data-original-title] {
cursor: help;
border-bottom: 1px dotted #999999;
}
abbr.initialism {
font-size: 90%;
text-transform: uppercase;
}
blockquote {
padding: 0 0 0 15px;
margin: 0 0 20px;
border-left: 5px solid #eeeeee;
}
blockquote p {
margin-bottom: 0;
font-size: 17.5px;
font-weight: 300;
line-height: 1.25;
}
blockquote small {
display: block;
line-height: 20px;
color: #999999;
}
blockquote small:before {
content: '\2014 \00A0';
}
blockquote.pull-right {
float: right;
padding-right: 15px;
padding-left: 0;
border-right: 5px solid #eeeeee;
border-left: 0;
}
blockquote.pull-right p,
blockquote.pull-right small {
text-align: right;
}
blockquote.pull-right small:before {
content: '';
}
blockquote.pull-right small:after {
content: '\00A0 \2014';
}
q:before,
q:after,
blockquote:before,
blockquote:after {
content: "";
}
address {
display: block;
margin-bottom: 20px;
font-style: normal;
line-height: 20px;
}
code,
pre {
padding: 0 3px 2px;
font-family: Monaco, Menlo, Consolas, "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;
white-space: nowrap;
background-color: #f7f7f9;
border: 1px solid #e1e1e8;
}
pre {
display: block;
padding: 9.5px;
margin: 0 0 10px;
font-size: 13px;
line-height: 20px;
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;
}
pre.prettyprint {
margin-bottom: 20px;
}
pre code {
padding: 0;
color: inherit;
white-space: pre;
white-space: pre-wrap;
background-color: transparent;
border: 0;
}
.pre-scrollable {
max-height: 340px;
overflow-y: scroll;
}
form {
margin: 0 0 20px;
}
fieldset {
padding: 0;
margin: 0;
border: 0;
}
legend {
display: block;
width: 100%;
padding: 0;
margin-bottom: 20px;
font-size: 21px;
line-height: 40px;
color: #333333;
border: 0;
border-bottom: 1px solid #e5e5e5;
}
legend small {
font-size: 15px;
color: #999999;
}
label,
input,
button,
select,
textarea {
font-size: 14px;
font-weight: normal;
line-height: 20px;
}
input,
button,
select,
textarea {
font-family: "Helvetica Neue", Helvetica, Arial, sans-serif;
}
label {
display: block;
margin-bottom: 5px;
}
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;
height: 20px;
padding: 4px 6px;
margin-bottom: 10px;
font-size: 14px;
line-height: 20px;
color: #555555;
vertical-align: middle;
-webkit-border-radius: 4px;
-moz-border-radius: 4px;
border-radius: 4px;
}
input,
textarea,
.uneditable-input {
width: 206px;
}
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-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;
-o-transition: border linear 0.2s, box-shadow linear 0.2s;
transition: border linear 0.2s, box-shadow linear 0.2s;
}
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);
}
input[type="radio"],
input[type="checkbox"] {
margin: 4px 0 0;
margin-top: 1px \9;
*margin-top: 0;
line-height: normal;
}
input[type="file"],
input[type="image"],
input[type="submit"],
input[type="reset"],
input[type="button"],
input[type="radio"],
input[type="checkbox"] {
width: auto;
}
select,
input[type="file"] {
height: 30px;
/* 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: 30px;
}
select {
width: 220px;
background-color: #ffffff;
border: 1px solid #cccccc;
}
select[multiple],
select[size] {
height: auto;
}
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;
}
.uneditable-input,
.uneditable-textarea {
color: #999999;
cursor: not-allowed;
background-color: #fcfcfc;
border-color: #cccccc;
-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);
}
.uneditable-input {
overflow: hidden;
white-space: nowrap;
}
.uneditable-textarea {
width: auto;
height: auto;
}
input:-moz-placeholder,
textarea:-moz-placeholder {
color: #999999;
}
input:-ms-input-placeholder,
textarea:-ms-input-placeholder {
color: #999999;
}
input::-webkit-input-placeholder,
textarea::-webkit-input-placeholder {
color: #999999;
}
.radio,
.checkbox {
min-height: 20px;
padding-left: 20px;
}
.radio input[type="radio"],
.checkbox input[type="checkbox"] {
float: left;
margin-left: -20px;
}
.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-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[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[class*="span"],
.row-fluid select[class*="span"],
.row-fluid textarea[class*="span"],
.row-fluid .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;
}
.controls-row [class*="span"] + [class*="span"] {
margin-left: 20px;
}
input.span12,
textarea.span12,
.uneditable-input.span12 {
width: 926px;
}
input.span11,
textarea.span11,
.uneditable-input.span11 {
width: 846px;
}
input.span10,
textarea.span10,
.uneditable-input.span10 {
width: 766px;
}
input.span9,
textarea.span9,
.uneditable-input.span9 {
width: 686px;
}
input.span8,
textarea.span8,
.uneditable-input.span8 {
width: 606px;
}
input.span7,
textarea.span7,
.uneditable-input.span7 {
width: 526px;
}
input.span6,
textarea.span6,
.uneditable-input.span6 {
width: 446px;
}
input.span5,
textarea.span5,
.uneditable-input.span5 {
width: 366px;
}
input.span4,
textarea.span4,
.uneditable-input.span4 {
width: 286px;
}
input.span3,
textarea.span3,
.uneditable-input.span3 {
width: 206px;
}
input.span2,
textarea.span2,
.uneditable-input.span2 {
width: 126px;
}
input.span1,
textarea.span1,
.uneditable-input.span1 {
width: 46px;
}
.controls-row {
*zoom: 1;
}
.controls-row:before,
.controls-row:after {
display: table;
line-height: 0;
content: "";
}
.controls-row:after {
clear: both;
}
.controls-row [class*="span"],
.row-fluid .controls-row [class*="span"] {
float: left;
}
.controls-row .checkbox[class*="span"],
.controls-row .radio[class*="span"] {
padding-top: 5px;
}
input[disabled],
select[disabled],
textarea[disabled],
input[readonly],
select[readonly],
textarea[readonly] {
cursor: not-allowed;
background-color: #eeeeee;
}
input[type="radio"][disabled],
input[type="checkbox"][disabled],
input[type="radio"][readonly],
input[type="checkbox"][readonly] {
background-color: transparent;
}
.control-group.warning .control-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;
}
.control-group.warning input,
.control-group.warning select,
.control-group.warning textarea {
border-color: #c09853;
-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);
}
.control-group.warning input:focus,
.control-group.warning select:focus,
.control-group.warning textarea:focus {
border-color: #a47e3c;
-webkit-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 0 0 6px #dbc59e;
-moz-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 0 0 6px #dbc59e;
box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 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 .control-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;
}
.control-group.error input,
.control-group.error select,
.control-group.error textarea {
border-color: #b94a48;
-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);
}
.control-group.error input:focus,
.control-group.error select:focus,
.control-group.error textarea:focus {
border-color: #953b39;
-webkit-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 0 0 6px #d59392;
-moz-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 0 0 6px #d59392;
box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 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 .control-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;
}
.control-group.success input,
.control-group.success select,
.control-group.success textarea {
border-color: #468847;
-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);
}
.control-group.success input:focus,
.control-group.success select:focus,
.control-group.success textarea:focus {
border-color: #356635;
-webkit-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 0 0 6px #7aba7b;
-moz-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 0 0 6px #7aba7b;
box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 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;
}
.control-group.info .control-label,
.control-group.info .help-block,
.control-group.info .help-inline {
color: #3a87ad;
}
.control-group.info .checkbox,
.control-group.info .radio,
.control-group.info input,
.control-group.info select,
.control-group.info textarea {
color: #3a87ad;
}
.control-group.info input,
.control-group.info select,
.control-group.info textarea {
border-color: #3a87ad;
-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);
}
.control-group.info input:focus,
.control-group.info select:focus,
.control-group.info textarea:focus {
border-color: #2d6987;
-webkit-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 0 0 6px #7ab5d3;
-moz-box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 0 0 6px #7ab5d3;
box-shadow: inset 0 1px 1px rgba(0, 0, 0, 0.075), 0 0 6px #7ab5d3;
}
.control-group.info .input-prepend .add-on,
.control-group.info .input-append .add-on {
color: #3a87ad;
background-color: #d9edf7;
border-color: #3a87ad;
}
input:focus:invalid,
textarea:focus:invalid,
select:focus:invalid {
color: #b94a48;
border-color: #ee5f5b;
}
input:focus:invalid:focus,
textarea:focus:invalid:focus,
select:focus: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: 19px 20px 20px;
margin-top: 20px;
margin-bottom: 20px;
background-color: #f5f5f5;
border-top: 1px solid #e5e5e5;
*zoom: 1;
}
.form-actions:before,
.form-actions:after {
display: table;
line-height: 0;
content: "";
}
.form-actions:after {
clear: both;
}
.help-block,
.help-inline {
color: #595959;
}
.help-block {
display: block;
margin-bottom: 10px;
}
.help-inline {
display: inline-block;
*display: inline;
padding-left: 5px;
vertical-align: middle;
*zoom: 1;
}
.input-append,
.input-prepend {
display: inline-block;
margin-bottom: 10px;
font-size: 0;
white-space: nowrap;
vertical-align: middle;
}
.input-append input,
.input-prepend input,
.input-append select,
.input-prepend select,
.input-append .uneditable-input,
.input-prepend .uneditable-input,
.input-append .dropdown-menu,
.input-prepend .dropdown-menu,
.input-append .popover,
.input-prepend .popover {
font-size: 14px;
}
.input-append input,
.input-prepend input,
.input-append select,
.input-prepend select,
.input-append .uneditable-input,
.input-prepend .uneditable-input {
position: relative;
margin-bottom: 0;
*margin-left: 0;
vertical-align: top;
-webkit-border-radius: 0 4px 4px 0;
-moz-border-radius: 0 4px 4px 0;
border-radius: 0 4px 4px 0;
}
.input-append input:focus,
.input-prepend input:focus,
.input-append select:focus,
.input-prepend select:focus,
.input-append .uneditable-input:focus,
.input-prepend .uneditable-input:focus {
z-index: 2;
}
.input-append .add-on,
.input-prepend .add-on {
display: inline-block;
width: auto;
height: 20px;
min-width: 16px;
padding: 4px 5px;
font-size: 14px;
font-weight: normal;
line-height: 20px;
text-align: center;
text-shadow: 0 1px 0 #ffffff;
background-color: #eeeeee;
border: 1px solid #ccc;
}
.input-append .add-on,
.input-prepend .add-on,
.input-append .btn,
.input-prepend .btn,
.input-append .btn-group > .dropdown-toggle,
.input-prepend .btn-group > .dropdown-toggle {
vertical-align: top;
-webkit-border-radius: 0;
-moz-border-radius: 0;
border-radius: 0;
}
.input-append .active,
.input-prepend .active {
background-color: #a9dba9;
border-color: #46a546;
}
.input-prepend .add-on,
.input-prepend .btn {
margin-right: -1px;
}
.input-prepend .add-on:first-child,
.input-prepend .btn:first-child {
-webkit-border-radius: 4px 0 0 4px;
-moz-border-radius: 4px 0 0 4px;
border-radius: 4px 0 0 4px;
}
.input-append input,
.input-append select,
.input-append .uneditable-input {
-webkit-border-radius: 4px 0 0 4px;
-moz-border-radius: 4px 0 0 4px;
border-radius: 4px 0 0 4px;
}
.input-append input + .btn-group .btn:last-child,
.input-append select + .btn-group .btn:last-child,
.input-append .uneditable-input + .btn-group .btn:last-child {
-webkit-border-radius: 0 4px 4px 0;
-moz-border-radius: 0 4px 4px 0;
border-radius: 0 4px 4px 0;
}
.input-append .add-on,
.input-append .btn,
.input-append .btn-group {
margin-left: -1px;
}
.input-append .add-on:last-child,
.input-append .btn:last-child,
.input-append .btn-group:last-child > .dropdown-toggle {
-webkit-border-radius: 0 4px 4px 0;
-moz-border-radius: 0 4px 4px 0;
border-radius: 0 4px 4px 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 input + .btn-group .btn,
.input-prepend.input-append select + .btn-group .btn,
.input-prepend.input-append .uneditable-input + .btn-group .btn {
-webkit-border-radius: 0 4px 4px 0;
-moz-border-radius: 0 4px 4px 0;
border-radius: 0 4px 4px 0;
}
.input-prepend.input-append .add-on:first-child,
.input-prepend.input-append .btn:first-child {
margin-right: -1px;
-webkit-border-radius: 4px 0 0 4px;
-moz-border-radius: 4px 0 0 4px;
border-radius: 4px 0 0 4px;
}
.input-prepend.input-append .add-on:last-child,
.input-prepend.input-append .btn:last-child {
margin-left: -1px;
-webkit-border-radius: 0 4px 4px 0;
-moz-border-radius: 0 4px 4px 0;
border-radius: 0 4px 4px 0;
}
.input-prepend.input-append .btn-group:first-child {
margin-left: 0;
}
input.search-query {
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: 15px;
-moz-border-radius: 15px;
border-radius: 15px;
}
/* Allow for input prepend/append in search forms */
.form-search .input-append .search-query,
.form-search .input-prepend .search-query {
-webkit-border-radius: 0;
-moz-border-radius: 0;
border-radius: 0;
}
.form-search .input-append .search-query {
-webkit-border-radius: 14px 0 0 14px;
-moz-border-radius: 14px 0 0 14px;
border-radius: 14px 0 0 14px;
}
.form-search .input-append .btn {
-webkit-border-radius: 0 14px 14px 0;
-moz-border-radius: 0 14px 14px 0;
border-radius: 0 14px 14px 0;
}
.form-search .input-prepend .search-query {
-webkit-border-radius: 0 14px 14px 0;
-moz-border-radius: 0 14px 14px 0;
border-radius: 0 14px 14px 0;
}
.form-search .input-prepend .btn {
-webkit-border-radius: 14px 0 0 14px;
-moz-border-radius: 14px 0 0 14px;
border-radius: 14px 0 0 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;
*display: inline;
margin-bottom: 0;
vertical-align: middle;
*zoom: 1;
}
.form-search .hide,
.form-inline .hide,
.form-horizontal .hide {
display: none;
}
.form-search label,
.form-inline label,
.form-search .btn-group,
.form-inline .btn-group {
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-right: 3px;
margin-left: 0;
}
.control-group {
margin-bottom: 10px;
}
legend + .control-group {
margin-top: 20px;
-webkit-margin-top-collapse: separate;
}
.form-horizontal .control-group {
margin-bottom: 20px;
*zoom: 1;
}
.form-horizontal .control-group:before,
.form-horizontal .control-group:after {
display: table;
line-height: 0;
content: "";
}
.form-horizontal .control-group:after {
clear: both;
}
.form-horizontal .control-label {
float: left;
width: 160px;
padding-top: 5px;
text-align: right;
}
.form-horizontal .controls {
*display: inline-block;
*padding-left: 20px;
margin-left: 180px;
*margin-left: 0;
}
.form-horizontal .controls:first-child {
*padding-left: 180px;
}
.form-horizontal .help-block {
margin-bottom: 0;
}
.form-horizontal input + .help-block,
.form-horizontal select + .help-block,
.form-horizontal textarea + .help-block,
.form-horizontal .uneditable-input + .help-block,
.form-horizontal .input-prepend + .help-block,
.form-horizontal .input-append + .help-block {
margin-top: 10px;
}
.form-horizontal .form-actions {
padding-left: 180px;
}
table {
max-width: 100%;
background-color: transparent;
border-collapse: collapse;
border-spacing: 0;
}
.table {
width: 100%;
margin-bottom: 20px;
}
.table th,
.table td {
padding: 8px;
line-height: 20px;
text-align: left;
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 .table {
background-color: #ffffff;
}
.table-condensed th,
.table-condensed td {
padding: 4px 5px;
}
.table-bordered {
border: 1px solid #dddddd;
border-collapse: separate;
*border-collapse: collapse;
border-left: 0;
-webkit-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,
.table-bordered tbody:first-child tr:first-child > th:first-child {
-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,
.table-bordered tbody:first-child tr:first-child > th:last-child {
-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,
.table-bordered tbody:last-child tr:last-child > th:first-child,
.table-bordered tfoot:last-child tr:last-child > td:first-child,
.table-bordered tfoot:last-child tr:last-child > th:first-child {
-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,
.table-bordered tbody:last-child tr:last-child > th:last-child,
.table-bordered tfoot:last-child tr:last-child > td:last-child,
.table-bordered tfoot:last-child tr:last-child > th:last-child {
-webkit-border-bottom-right-radius: 4px;
border-bottom-right-radius: 4px;
-moz-border-radius-bottomright: 4px;
}
.table-bordered tfoot + tbody:last-child tr:last-child td:first-child {
-webkit-border-bottom-left-radius: 0;
border-bottom-left-radius: 0;
-moz-border-radius-bottomleft: 0;
}
.table-bordered tfoot + tbody:last-child tr:last-child td:last-child {
-webkit-border-bottom-right-radius: 0;
border-bottom-right-radius: 0;
-moz-border-radius-bottomright: 0;
}
.table-bordered caption + thead tr:first-child th:first-child,
.table-bordered caption + tbody tr:first-child td:first-child,
.table-bordered colgroup + thead tr:first-child th:first-child,
.table-bordered colgroup + tbody tr:first-child td:first-child {
-webkit-border-top-left-radius: 4px;
border-top-left-radius: 4px;
-moz-border-radius-topleft: 4px;
}
.table-bordered caption + thead tr:first-child th:last-child,
.table-bordered caption + tbody tr:first-child td:last-child,
.table-bordered colgroup + thead tr:first-child th:last-child,
.table-bordered colgroup + tbody tr:first-child td:last-child {
-webkit-border-top-right-radius: 4px;
border-top-right-radius: 4px;
-moz-border-radius-topright: 4px;
}
.table-striped tbody > tr:nth-child(odd) > td,
.table-striped tbody > tr:nth-child(odd) > th {
background-color: #f9f9f9;
}
.table-hover tbody tr:hover > td,
.table-hover tbody tr:hover > th {
background-color: #f5f5f5;
}
table td[class*="span"],
table th[class*="span"],
.row-fluid table td[class*="span"],
.row-fluid table th[class*="span"] {
display: table-cell;
float: none;
margin-left: 0;
}
.table td.span1,
.table th.span1 {
float: none;
width: 44px;
margin-left: 0;
}
.table td.span2,
.table th.span2 {
float: none;
width: 124px;
margin-left: 0;
}
.table td.span3,
.table th.span3 {
float: none;
width: 204px;
margin-left: 0;
}
.table td.span4,
.table th.span4 {
float: none;
width: 284px;
margin-left: 0;
}
.table td.span5,
.table th.span5 {
float: none;
width: 364px;
margin-left: 0;
}
.table td.span6,
.table th.span6 {
float: none;
width: 444px;
margin-left: 0;
}
.table td.span7,
.table th.span7 {
float: none;
width: 524px;
margin-left: 0;
}
.table td.span8,
.table th.span8 {
float: none;
width: 604px;
margin-left: 0;
}
.table td.span9,
.table th.span9 {
float: none;
width: 684px;
margin-left: 0;
}
.table td.span10,
.table th.span10 {
float: none;
width: 764px;
margin-left: 0;
}
.table td.span11,
.table th.span11 {
float: none;
width: 844px;
margin-left: 0;
}
.table td.span12,
.table th.span12 {
float: none;
width: 924px;
margin-left: 0;
}
.table tbody tr.success > td {
background-color: #dff0d8;
}
.table tbody tr.error > td {
background-color: #f2dede;
}
.table tbody tr.warning > td {
background-color: #fcf8e3;
}
.table tbody tr.info > td {
background-color: #d9edf7;
}
.table-hover tbody tr.success:hover > td {
background-color: #d0e9c6;
}
.table-hover tbody tr.error:hover > td {
background-color: #ebcccc;
}
.table-hover tbody tr.warning:hover > td {
background-color: #faf2cc;
}
.table-hover tbody tr.info:hover > td {
background-color: #c4e3f3;
}
[class^="icon-"],
[class*=" icon-"] {
display: inline-block;
width: 14px;
height: 14px;
margin-top: 1px;
*margin-right: .3em;
line-height: 14px;
vertical-align: text-top;
background-image: url("../img/glyphicons-halflings.png");
background-position: 14px 14px;
background-repeat: no-repeat;
}
/* White icons with optional class, or on hover/focus/active states of certain elements */
.icon-white,
.nav-pills > .active > a > [class^="icon-"],
.nav-pills > .active > a > [class*=" icon-"],
.nav-list > .active > a > [class^="icon-"],
.nav-list > .active > a > [class*=" icon-"],
.navbar-inverse .nav > .active > a > [class^="icon-"],
.navbar-inverse .nav > .active > a > [class*=" icon-"],
.dropdown-menu > li > a:hover > [class^="icon-"],
.dropdown-menu > li > a:focus > [class^="icon-"],
.dropdown-menu > li > a:hover > [class*=" icon-"],
.dropdown-menu > li > a:focus > [class*=" icon-"],
.dropdown-menu > .active > a > [class^="icon-"],
.dropdown-menu > .active > a > [class*=" icon-"],
.dropdown-submenu:hover > a > [class^="icon-"],
.dropdown-submenu:focus > a > [class^="icon-"],
.dropdown-submenu:hover > a > [class*=" icon-"],
.dropdown-submenu:focus > a > [class*=" icon-"] {
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 {
width: 16px;
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 {
width: 16px;
background-position: -384px -120px;
}
.icon-folder-open {
width: 16px;
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-top: 4px solid #000000;
border-right: 4px solid transparent;
border-left: 4px solid transparent;
content: "";
}
.dropdown .caret {
margin-top: 8px;
margin-left: 2px;
}
.dropdown-menu {
position: absolute;
top: 100%;
left: 0;
z-index: 1000;
display: none;
float: left;
min-width: 160px;
padding: 5px 0;
margin: 2px 0 0;
list-style: none;
background-color: #ffffff;
border: 1px solid #ccc;
border: 1px solid rgba(0, 0, 0, 0.2);
*border-right-width: 2px;
*border-bottom-width: 2px;
-webkit-border-radius: 6px;
-moz-border-radius: 6px;
border-radius: 6px;
-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: 9px 1px;
*margin: -5px 0 5px;
overflow: hidden;
background-color: #e5e5e5;
border-bottom: 1px solid #ffffff;
}
.dropdown-menu > li > a {
display: block;
padding: 3px 20px;
clear: both;
font-weight: normal;
line-height: 20px;
color: #333333;
white-space: nowrap;
}
.dropdown-menu > li > a:hover,
.dropdown-menu > li > a:focus,
.dropdown-submenu:hover > a,
.dropdown-submenu:focus > a {
color: #ffffff;
text-decoration: none;
background-color: #0081c2;
background-image: -moz-linear-gradient(top, #0088cc, #0077b3);
background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#0088cc), to(#0077b3));
background-image: -webkit-linear-gradient(top, #0088cc, #0077b3);
background-image: -o-linear-gradient(top, #0088cc, #0077b3);
background-image: linear-gradient(to bottom, #0088cc, #0077b3);
background-repeat: repeat-x;
filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#ff0088cc', endColorstr='#ff0077b3', GradientType=0);
}
.dropdown-menu > .active > a,
.dropdown-menu > .active > a:hover,
.dropdown-menu > .active > a:focus {
color: #ffffff;
text-decoration: none;
background-color: #0081c2;
background-image: -moz-linear-gradient(top, #0088cc, #0077b3);
background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#0088cc), to(#0077b3));
background-image: -webkit-linear-gradient(top, #0088cc, #0077b3);
background-image: -o-linear-gradient(top, #0088cc, #0077b3);
background-image: linear-gradient(to bottom, #0088cc, #0077b3);
background-repeat: repeat-x;
outline: 0;
filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#ff0088cc', endColorstr='#ff0077b3', GradientType=0);
}
.dropdown-menu > .disabled > a,
.dropdown-menu > .disabled > a:hover,
.dropdown-menu > .disabled > a:focus {
color: #999999;
}
.dropdown-menu > .disabled > a:hover,
.dropdown-menu > .disabled > a:focus {
text-decoration: none;
cursor: default;
background-color: transparent;
background-image: none;
filter: progid:DXImageTransform.Microsoft.gradient(enabled=false);
}
.open {
*z-index: 1000;
}
.open > .dropdown-menu {
display: block;
}
.dropdown-backdrop {
position: fixed;
top: 0;
right: 0;
bottom: 0;
left: 0;
z-index: 990;
}
.pull-right > .dropdown-menu {
right: 0;
left: auto;
}
.dropup .caret,
.navbar-fixed-bottom .dropdown .caret {
border-top: 0;
border-bottom: 4px solid #000000;
content: "";
}
.dropup .dropdown-menu,
.navbar-fixed-bottom .dropdown .dropdown-menu {
top: auto;
bottom: 100%;
margin-bottom: 1px;
}
.dropdown-submenu {
position: relative;
}
.dropdown-submenu > .dropdown-menu {
top: 0;
left: 100%;
margin-top: -6px;
margin-left: -1px;
-webkit-border-radius: 0 6px 6px 6px;
-moz-border-radius: 0 6px 6px 6px;
border-radius: 0 6px 6px 6px;
}
.dropdown-submenu:hover > .dropdown-menu {
display: block;
}
.dropup .dropdown-submenu > .dropdown-menu {
top: auto;
bottom: 0;
margin-top: 0;
margin-bottom: -2px;
-webkit-border-radius: 5px 5px 5px 0;
-moz-border-radius: 5px 5px 5px 0;
border-radius: 5px 5px 5px 0;
}
.dropdown-submenu > a:after {
display: block;
float: right;
width: 0;
height: 0;
margin-top: 5px;
margin-right: -10px;
border-color: transparent;
border-left-color: #cccccc;
border-style: solid;
border-width: 5px 0 5px 5px;
content: " ";
}
.dropdown-submenu:hover > a:after {
border-left-color: #ffffff;
}
.dropdown-submenu.pull-left {
float: none;
}
.dropdown-submenu.pull-left > .dropdown-menu {
left: -100%;
margin-left: 10px;
-webkit-border-radius: 6px 0 6px 6px;
-moz-border-radius: 6px 0 6px 6px;
border-radius: 6px 0 6px 6px;
}
.dropdown .dropdown-menu .nav-header {
padding-right: 20px;
padding-left: 20px;
}
.typeahead {
z-index: 1051;
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 #e3e3e3;
-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 {
opacity: 0;
-webkit-transition: opacity 0.15s linear;
-moz-transition: opacity 0.15s linear;
-o-transition: opacity 0.15s linear;
transition: opacity 0.15s linear;
}
.fade.in {
opacity: 1;
}
.collapse {
position: relative;
height: 0;
overflow: hidden;
-webkit-transition: height 0.35s ease;
-moz-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;
font-weight: bold;
line-height: 20px;
color: #000000;
text-shadow: 0 1px 0 #ffffff;
opacity: 0.2;
filter: alpha(opacity=20);
}
.close:hover,
.close:focus {
color: #000000;
text-decoration: none;
cursor: pointer;
opacity: 0.4;
filter: alpha(opacity=40);
}
button.close {
padding: 0;
cursor: pointer;
background: transparent;
border: 0;
-webkit-appearance: none;
}
.btn {
display: inline-block;
*display: inline;
padding: 4px 12px;
margin-bottom: 0;
*margin-left: .3em;
font-size: 14px;
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-color: #e6e6e6;
background-image: -moz-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(to bottom, #ffffff, #e6e6e6);
background-repeat: repeat-x;
border: 1px solid #cccccc;
*border: 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);
border-bottom-color: #b3b3b3;
-webkit-border-radius: 4px;
-moz-border-radius: 4px;
border-radius: 4px;
filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#ffffffff', endColorstr='#ffe6e6e6', 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);
}
.btn:hover,
.btn:focus,
.btn:active,
.btn.active,
.btn.disabled,
.btn[disabled] {
color: #333333;
background-color: #e6e6e6;
*background-color: #d9d9d9;
}
.btn:active,
.btn.active {
background-color: #cccccc \9;
}
.btn:first-child {
*margin-left: 0;
}
.btn:hover,
.btn:focus {
color: #333333;
text-decoration: none;
background-position: 0 -15px;
-webkit-transition: background-position 0.1s linear;
-moz-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;
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;
opacity: 0.65;
filter: alpha(opacity=65);
-webkit-box-shadow: none;
-moz-box-shadow: none;
box-shadow: none;
}
.btn-large {
padding: 11px 19px;
font-size: 17.5px;
-webkit-border-radius: 6px;
-moz-border-radius: 6px;
border-radius: 6px;
}
.btn-large [class^="icon-"],
.btn-large [class*=" icon-"] {
margin-top: 4px;
}
.btn-small {
padding: 2px 10px;
font-size: 11.9px;
-webkit-border-radius: 3px;
-moz-border-radius: 3px;
border-radius: 3px;
}
.btn-small [class^="icon-"],
.btn-small [class*=" icon-"] {
margin-top: 0;
}
.btn-mini [class^="icon-"],
.btn-mini [class*=" icon-"] {
margin-top: -1px;
}
.btn-mini {
padding: 0 6px;
font-size: 10.5px;
-webkit-border-radius: 3px;
-moz-border-radius: 3px;
border-radius: 3px;
}
.btn-block {
display: block;
width: 100%;
padding-right: 0;
padding-left: 0;
-webkit-box-sizing: border-box;
-moz-box-sizing: border-box;
box-sizing: border-box;
}
.btn-block + .btn-block {
margin-top: 5px;
}
input[type="submit"].btn-block,
input[type="reset"].btn-block,
input[type="button"].btn-block {
width: 100%;
}
.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 {
color: #ffffff;
text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.25);
background-color: #006dcc;
*background-color: #0044cc;
background-image: -moz-linear-gradient(top, #0088cc, #0044cc);
background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#0088cc), to(#0044cc));
background-image: -webkit-linear-gradient(top, #0088cc, #0044cc);
background-image: -o-linear-gradient(top, #0088cc, #0044cc);
background-image: linear-gradient(to bottom, #0088cc, #0044cc);
background-repeat: repeat-x;
border-color: #0044cc #0044cc #002a80;
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='#ff0088cc', endColorstr='#ff0044cc', GradientType=0);
filter: progid:DXImageTransform.Microsoft.gradient(enabled=false);
}
.btn-primary:hover,
.btn-primary:focus,
.btn-primary:active,
.btn-primary.active,
.btn-primary.disabled,
.btn-primary[disabled] {
color: #ffffff;
background-color: #0044cc;
*background-color: #003bb3;
}
.btn-primary:active,
.btn-primary.active {
background-color: #003399 \9;
}
.btn-warning {
color: #ffffff;
text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.25);
background-color: #faa732;
*background-color: #f89406;
background-image: -moz-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(to bottom, #fbb450, #f89406);
background-repeat: repeat-x;
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='#fffbb450', endColorstr='#fff89406', GradientType=0);
filter: progid:DXImageTransform.Microsoft.gradient(enabled=false);
}
.btn-warning:hover,
.btn-warning:focus,
.btn-warning:active,
.btn-warning.active,
.btn-warning.disabled,
.btn-warning[disabled] {
color: #ffffff;
background-color: #f89406;
*background-color: #df8505;
}
.btn-warning:active,
.btn-warning.active {
background-color: #c67605 \9;
}
.btn-danger {
color: #ffffff;
text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.25);
background-color: #da4f49;
*background-color: #bd362f;
background-image: -moz-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(to bottom, #ee5f5b, #bd362f);
background-repeat: repeat-x;
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='#ffee5f5b', endColorstr='#ffbd362f', GradientType=0);
filter: progid:DXImageTransform.Microsoft.gradient(enabled=false);
}
.btn-danger:hover,
.btn-danger:focus,
.btn-danger:active,
.btn-danger.active,
.btn-danger.disabled,
.btn-danger[disabled] {
color: #ffffff;
background-color: #bd362f;
*background-color: #a9302a;
}
.btn-danger:active,
.btn-danger.active {
background-color: #942a25 \9;
}
.btn-success {
color: #ffffff;
text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.25);
background-color: #5bb75b;
*background-color: #51a351;
background-image: -moz-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(to bottom, #62c462, #51a351);
background-repeat: repeat-x;
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='#ff62c462', endColorstr='#ff51a351', GradientType=0);
filter: progid:DXImageTransform.Microsoft.gradient(enabled=false);
}
.btn-success:hover,
.btn-success:focus,
.btn-success:active,
.btn-success.active,
.btn-success.disabled,
.btn-success[disabled] {
color: #ffffff;
background-color: #51a351;
*background-color: #499249;
}
.btn-success:active,
.btn-success.active {
background-color: #408140 \9;
}
.btn-info {
color: #ffffff;
text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.25);
background-color: #49afcd;
*background-color: #2f96b4;
background-image: -moz-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(to bottom, #5bc0de, #2f96b4);
background-repeat: repeat-x;
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='#ff5bc0de', endColorstr='#ff2f96b4', GradientType=0);
filter: progid:DXImageTransform.Microsoft.gradient(enabled=false);
}
.btn-info:hover,
.btn-info:focus,
.btn-info:active,
.btn-info.active,
.btn-info.disabled,
.btn-info[disabled] {
color: #ffffff;
background-color: #2f96b4;
*background-color: #2a85a0;
}
.btn-info:active,
.btn-info.active {
background-color: #24748c \9;
}
.btn-inverse {
color: #ffffff;
text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.25);
background-color: #363636;
*background-color: #222222;
background-image: -moz-linear-gradient(top, #444444, #222222);
background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#444444), to(#222222));
background-image: -webkit-linear-gradient(top, #444444, #222222);
background-image: -o-linear-gradient(top, #444444, #222222);
background-image: linear-gradient(to bottom, #444444, #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='#ff444444', endColorstr='#ff222222', GradientType=0);
filter: progid:DXImageTransform.Microsoft.gradient(enabled=false);
}
.btn-inverse:hover,
.btn-inverse:focus,
.btn-inverse:active,
.btn-inverse.active,
.btn-inverse.disabled,
.btn-inverse[disabled] {
color: #ffffff;
background-color: #222222;
*background-color: #151515;
}
.btn-inverse:active,
.btn-inverse.active {
background-color: #080808 \9;
}
button.btn,
input[type="submit"].btn {
*padding-top: 3px;
*padding-bottom: 3px;
}
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-link,
.btn-link:active,
.btn-link[disabled] {
background-color: transparent;
background-image: none;
-webkit-box-shadow: none;
-moz-box-shadow: none;
box-shadow: none;
}
.btn-link {
color: #0088cc;
cursor: pointer;
border-color: transparent;
-webkit-border-radius: 0;
-moz-border-radius: 0;
border-radius: 0;
}
.btn-link:hover,
.btn-link:focus {
color: #005580;
text-decoration: underline;
background-color: transparent;
}
.btn-link[disabled]:hover,
.btn-link[disabled]:focus {
color: #333333;
text-decoration: none;
}
.btn-group {
position: relative;
display: inline-block;
*display: inline;
*margin-left: .3em;
font-size: 0;
white-space: nowrap;
vertical-align: middle;
*zoom: 1;
}
.btn-group:first-child {
*margin-left: 0;
}
.btn-group + .btn-group {
margin-left: 5px;
}
.btn-toolbar {
margin-top: 10px;
margin-bottom: 10px;
font-size: 0;
}
.btn-toolbar > .btn + .btn,
.btn-toolbar > .btn-group + .btn,
.btn-toolbar > .btn + .btn-group {
margin-left: 5px;
}
.btn-group > .btn {
position: relative;
-webkit-border-radius: 0;
-moz-border-radius: 0;
border-radius: 0;
}
.btn-group > .btn + .btn {
margin-left: -1px;
}
.btn-group > .btn,
.btn-group > .dropdown-menu,
.btn-group > .popover {
font-size: 14px;
}
.btn-group > .btn-mini {
font-size: 10.5px;
}
.btn-group > .btn-small {
font-size: 11.9px;
}
.btn-group > .btn-large {
font-size: 17.5px;
}
.btn-group > .btn:first-child {
margin-left: 0;
-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;
-moz-border-radius-topleft: 4px;
}
.btn-group > .btn:last-child,
.btn-group > .dropdown-toggle {
-webkit-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;
}
.btn-group > .btn.large:first-child {
margin-left: 0;
-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;
-moz-border-radius-topleft: 6px;
}
.btn-group > .btn.large:last-child,
.btn-group > .large.dropdown-toggle {
-webkit-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;
}
.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 > .btn + .dropdown-toggle {
*padding-top: 5px;
padding-right: 8px;
*padding-bottom: 5px;
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);
}
.btn-group > .btn-mini + .dropdown-toggle {
*padding-top: 2px;
padding-right: 5px;
*padding-bottom: 2px;
padding-left: 5px;
}
.btn-group > .btn-small + .dropdown-toggle {
*padding-top: 5px;
*padding-bottom: 4px;
}
.btn-group > .btn-large + .dropdown-toggle {
*padding-top: 7px;
padding-right: 12px;
*padding-bottom: 7px;
padding-left: 12px;
}
.btn-group.open .dropdown-toggle {
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);
}
.btn-group.open .btn.dropdown-toggle {
background-color: #e6e6e6;
}
.btn-group.open .btn-primary.dropdown-toggle {
background-color: #0044cc;
}
.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: 8px;
margin-left: 0;
}
.btn-large .caret {
margin-top: 6px;
}
.btn-large .caret {
border-top-width: 5px;
border-right-width: 5px;
border-left-width: 5px;
}
.btn-mini .caret,
.btn-small .caret {
margin-top: 8px;
}
.dropup .btn-large .caret {
border-bottom-width: 5px;
}
.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;
}
.btn-group-vertical {
display: inline-block;
*display: inline;
/* IE7 inline-block hack */
*zoom: 1;
}
.btn-group-vertical > .btn {
display: block;
float: none;
max-width: 100%;
-webkit-border-radius: 0;
-moz-border-radius: 0;
border-radius: 0;
}
.btn-group-vertical > .btn + .btn {
margin-top: -1px;
margin-left: 0;
}
.btn-group-vertical > .btn:first-child {
-webkit-border-radius: 4px 4px 0 0;
-moz-border-radius: 4px 4px 0 0;
border-radius: 4px 4px 0 0;
}
.btn-group-vertical > .btn:last-child {
-webkit-border-radius: 0 0 4px 4px;
-moz-border-radius: 0 0 4px 4px;
border-radius: 0 0 4px 4px;
}
.btn-group-vertical > .btn-large:first-child {
-webkit-border-radius: 6px 6px 0 0;
-moz-border-radius: 6px 6px 0 0;
border-radius: 6px 6px 0 0;
}
.btn-group-vertical > .btn-large:last-child {
-webkit-border-radius: 0 0 6px 6px;
-moz-border-radius: 0 0 6px 6px;
border-radius: 0 0 6px 6px;
}
.alert {
padding: 8px 35px 8px 14px;
margin-bottom: 20px;
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;
}
.alert,
.alert h4 {
color: #c09853;
}
.alert h4 {
margin: 0;
}
.alert .close {
position: relative;
top: -2px;
right: -21px;
line-height: 20px;
}
.alert-success {
color: #468847;
background-color: #dff0d8;
border-color: #d6e9c6;
}
.alert-success h4 {
color: #468847;
}
.alert-danger,
.alert-error {
color: #b94a48;
background-color: #f2dede;
border-color: #eed3d7;
}
.alert-danger h4,
.alert-error h4 {
color: #b94a48;
}
.alert-info {
color: #3a87ad;
background-color: #d9edf7;
border-color: #bce8f1;
}
.alert-info h4 {
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-bottom: 20px;
margin-left: 0;
list-style: none;
}
.nav > li > a {
display: block;
}
.nav > li > a:hover,
.nav > li > a:focus {
text-decoration: none;
background-color: #eeeeee;
}
.nav > li > a > img {
max-width: none;
}
.nav > .pull-right {
float: right;
}
.nav-header {
display: block;
padding: 3px 15px;
font-size: 11px;
font-weight: bold;
line-height: 20px;
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-right: 15px;
padding-left: 15px;
margin-bottom: 0;
}
.nav-list > li > a,
.nav-list .nav-header {
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,
.nav-list > .active > a:focus {
color: #ffffff;
text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.2);
background-color: #0088cc;
}
.nav-list [class^="icon-"],
.nav-list [class*=" icon-"] {
margin-right: 2px;
}
.nav-list .divider {
*width: 100%;
height: 1px;
margin: 9px 1px;
*margin: -5px 0 5px;
overflow: hidden;
background-color: #e5e5e5;
border-bottom: 1px solid #ffffff;
}
.nav-tabs,
.nav-pills {
*zoom: 1;
}
.nav-tabs:before,
.nav-pills:before,
.nav-tabs:after,
.nav-pills:after {
display: table;
line-height: 0;
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: 20px;
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,
.nav-tabs > li > a:focus {
border-color: #eeeeee #eeeeee #dddddd;
}
.nav-tabs > .active > a,
.nav-tabs > .active > a:hover,
.nav-tabs > .active > a:focus {
color: #555555;
cursor: default;
background-color: #ffffff;
border: 1px solid #ddd;
border-bottom-color: transparent;
}
.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,
.nav-pills > .active > a:focus {
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-top-right-radius: 4px;
border-top-right-radius: 4px;
-webkit-border-top-left-radius: 4px;
border-top-left-radius: 4px;
-moz-border-radius-topright: 4px;
-moz-border-radius-topleft: 4px;
}
.nav-tabs.nav-stacked > li:last-child > a {
-webkit-border-bottom-right-radius: 4px;
border-bottom-right-radius: 4px;
-webkit-border-bottom-left-radius: 4px;
border-bottom-left-radius: 4px;
-moz-border-radius-bottomright: 4px;
-moz-border-radius-bottomleft: 4px;
}
.nav-tabs.nav-stacked > li > a:hover,
.nav-tabs.nav-stacked > li > a:focus {
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 {
-webkit-border-radius: 0 0 6px 6px;
-moz-border-radius: 0 0 6px 6px;
border-radius: 0 0 6px 6px;
}
.nav-pills .dropdown-menu {
-webkit-border-radius: 6px;
-moz-border-radius: 6px;
border-radius: 6px;
}
.nav .dropdown-toggle .caret {
margin-top: 6px;
border-top-color: #0088cc;
border-bottom-color: #0088cc;
}
.nav .dropdown-toggle:hover .caret,
.nav .dropdown-toggle:focus .caret {
border-top-color: #005580;
border-bottom-color: #005580;
}
/* move down carets for tabs */
.nav-tabs .dropdown-toggle .caret {
margin-top: 8px;
}
.nav .active .dropdown-toggle .caret {
border-top-color: #fff;
border-bottom-color: #fff;
}
.nav-tabs .active .dropdown-toggle .caret {
border-top-color: #555555;
border-bottom-color: #555555;
}
.nav > .dropdown.active > a:hover,
.nav > .dropdown.active > a:focus {
cursor: pointer;
}
.nav-tabs .open .dropdown-toggle,
.nav-pills .open .dropdown-toggle,
.nav > li.dropdown.open.active > a:hover,
.nav > li.dropdown.open.active > a:focus {
color: #ffffff;
background-color: #999999;
border-color: #999999;
}
.nav li.dropdown.open .caret,
.nav li.dropdown.open.active .caret,
.nav li.dropdown.open a:hover .caret,
.nav li.dropdown.open a:focus .caret {
border-top-color: #ffffff;
border-bottom-color: #ffffff;
opacity: 1;
filter: alpha(opacity=100);
}
.tabs-stacked .open > a:hover,
.tabs-stacked .open > a:focus {
border-color: #999999;
}
.tabbable {
*zoom: 1;
}
.tabbable:before,
.tabbable:after {
display: table;
line-height: 0;
content: "";
}
.tabbable:after {
clear: both;
}
.tab-content {
overflow: auto;
}
.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,
.tabs-below > .nav-tabs > li > a:focus {
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:focus {
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,
.tabs-left > .nav-tabs > li > a:focus {
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:focus {
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,
.tabs-right > .nav-tabs > li > a:focus {
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:focus {
border-color: #ddd #ddd #ddd transparent;
*border-left-color: #ffffff;
}
.nav > .disabled > a {
color: #999999;
}
.nav > .disabled > a:hover,
.nav > .disabled > a:focus {
text-decoration: none;
cursor: default;
background-color: transparent;
}
.navbar {
*position: relative;
*z-index: 2;
margin-bottom: 20px;
overflow: visible;
}
.navbar-inner {
min-height: 40px;
padding-right: 20px;
padding-left: 20px;
background-color: #fafafa;
background-image: -moz-linear-gradient(top, #ffffff, #f2f2f2);
background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#ffffff), to(#f2f2f2));
background-image: -webkit-linear-gradient(top, #ffffff, #f2f2f2);
background-image: -o-linear-gradient(top, #ffffff, #f2f2f2);
background-image: linear-gradient(to bottom, #ffffff, #f2f2f2);
background-repeat: repeat-x;
border: 1px solid #d4d4d4;
-webkit-border-radius: 4px;
-moz-border-radius: 4px;
border-radius: 4px;
filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#ffffffff', endColorstr='#fff2f2f2', GradientType=0);
*zoom: 1;
-webkit-box-shadow: 0 1px 4px rgba(0, 0, 0, 0.065);
-moz-box-shadow: 0 1px 4px rgba(0, 0, 0, 0.065);
box-shadow: 0 1px 4px rgba(0, 0, 0, 0.065);
}
.navbar-inner:before,
.navbar-inner:after {
display: table;
line-height: 0;
content: "";
}
.navbar-inner:after {
clear: both;
}
.navbar .container {
width: auto;
}
.nav-collapse.collapse {
height: auto;
overflow: visible;
}
.navbar .brand {
display: block;
float: left;
padding: 10px 20px 10px;
margin-left: -20px;
font-size: 20px;
font-weight: 200;
color: #777777;
text-shadow: 0 1px 0 #ffffff;
}
.navbar .brand:hover,
.navbar .brand:focus {
text-decoration: none;
}
.navbar-text {
margin-bottom: 0;
line-height: 40px;
color: #777777;
}
.navbar-link {
color: #777777;
}
.navbar-link:hover,
.navbar-link:focus {
color: #333333;
}
.navbar .divider-vertical {
height: 40px;
margin: 0 9px;
border-right: 1px solid #ffffff;
border-left: 1px solid #f2f2f2;
}
.navbar .btn,
.navbar .btn-group {
margin-top: 5px;
}
.navbar .btn-group .btn,
.navbar .input-prepend .btn,
.navbar .input-append .btn,
.navbar .input-prepend .btn-group,
.navbar .input-append .btn-group {
margin-top: 0;
}
.navbar-form {
margin-bottom: 0;
*zoom: 1;
}
.navbar-form:before,
.navbar-form:after {
display: table;
line-height: 0;
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,
.navbar-form .btn {
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: 5px;
white-space: nowrap;
}
.navbar-form .input-append input,
.navbar-form .input-prepend input {
margin-top: 0;
}
.navbar-search {
position: relative;
float: left;
margin-top: 5px;
margin-bottom: 0;
}
.navbar-search .search-query {
padding: 4px 14px;
margin-bottom: 0;
font-family: "Helvetica Neue", Helvetica, Arial, sans-serif;
font-size: 13px;
font-weight: normal;
line-height: 1;
-webkit-border-radius: 15px;
-moz-border-radius: 15px;
border-radius: 15px;
}
.navbar-static-top {
position: static;
margin-bottom: 0;
}
.navbar-static-top .navbar-inner {
-webkit-border-radius: 0;
-moz-border-radius: 0;
border-radius: 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-static-top .navbar-inner {
border-width: 0 0 1px;
}
.navbar-fixed-bottom .navbar-inner {
border-width: 1px 0 0;
}
.navbar-fixed-top .navbar-inner,
.navbar-fixed-bottom .navbar-inner {
padding-right: 0;
padding-left: 0;
-webkit-border-radius: 0;
-moz-border-radius: 0;
border-radius: 0;
}
.navbar-static-top .container,
.navbar-fixed-top .container,
.navbar-fixed-bottom .container {
width: 940px;
}
.navbar-fixed-top {
top: 0;
}
.navbar-fixed-top .navbar-inner,
.navbar-static-top .navbar-inner {
-webkit-box-shadow: 0 1px 10px rgba(0, 0, 0, 0.1);
-moz-box-shadow: 0 1px 10px rgba(0, 0, 0, 0.1);
box-shadow: 0 1px 10px rgba(0, 0, 0, 0.1);
}
.navbar-fixed-bottom {
bottom: 0;
}
.navbar-fixed-bottom .navbar-inner {
-webkit-box-shadow: 0 -1px 10px rgba(0, 0, 0, 0.1);
-moz-box-shadow: 0 -1px 10px rgba(0, 0, 0, 0.1);
box-shadow: 0 -1px 10px rgba(0, 0, 0, 0.1);
}
.navbar .nav {
position: relative;
left: 0;
display: block;
float: left;
margin: 0 10px 0 0;
}
.navbar .nav.pull-right {
float: right;
margin-right: 0;
}
.navbar .nav > li {
float: left;
}
.navbar .nav > li > a {
float: none;
padding: 10px 15px 10px;
color: #777777;
text-decoration: none;
text-shadow: 0 1px 0 #ffffff;
}
.navbar .nav .dropdown-toggle .caret {
margin-top: 8px;
}
.navbar .nav > li > a:focus,
.navbar .nav > li > a:hover {
color: #333333;
text-decoration: none;
background-color: transparent;
}
.navbar .nav > .active > a,
.navbar .nav > .active > a:hover,
.navbar .nav > .active > a:focus {
color: #555555;
text-decoration: none;
background-color: #e5e5e5;
-webkit-box-shadow: inset 0 3px 8px rgba(0, 0, 0, 0.125);
-moz-box-shadow: inset 0 3px 8px rgba(0, 0, 0, 0.125);
box-shadow: inset 0 3px 8px rgba(0, 0, 0, 0.125);
}
.navbar .btn-navbar {
display: none;
float: right;
padding: 7px 10px;
margin-right: 5px;
margin-left: 5px;
color: #ffffff;
text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.25);
background-color: #ededed;
*background-color: #e5e5e5;
background-image: -moz-linear-gradient(top, #f2f2f2, #e5e5e5);
background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#f2f2f2), to(#e5e5e5));
background-image: -webkit-linear-gradient(top, #f2f2f2, #e5e5e5);
background-image: -o-linear-gradient(top, #f2f2f2, #e5e5e5);
background-image: linear-gradient(to bottom, #f2f2f2, #e5e5e5);
background-repeat: repeat-x;
border-color: #e5e5e5 #e5e5e5 #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(startColorstr='#fff2f2f2', endColorstr='#ffe5e5e5', 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:focus,
.navbar .btn-navbar:active,
.navbar .btn-navbar.active,
.navbar .btn-navbar.disabled,
.navbar .btn-navbar[disabled] {
color: #ffffff;
background-color: #e5e5e5;
*background-color: #d9d9d9;
}
.navbar .btn-navbar:active,
.navbar .btn-navbar.active {
background-color: #cccccc \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 .nav > li > .dropdown-menu:before {
position: absolute;
top: -7px;
left: 9px;
display: inline-block;
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 .nav > li > .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 .nav > li > .dropdown-menu:before {
top: auto;
bottom: -7px;
border-top: 7px solid #ccc;
border-bottom: 0;
border-top-color: rgba(0, 0, 0, 0.2);
}
.navbar-fixed-bottom .nav > li > .dropdown-menu:after {
top: auto;
bottom: -6px;
border-top: 6px solid #ffffff;
border-bottom: 0;
}
.navbar .nav li.dropdown > a:hover .caret,
.navbar .nav li.dropdown > a:focus .caret {
border-top-color: #333333;
border-bottom-color: #333333;
}
.navbar .nav li.dropdown.open > .dropdown-toggle,
.navbar .nav li.dropdown.active > .dropdown-toggle,
.navbar .nav li.dropdown.open.active > .dropdown-toggle {
color: #555555;
background-color: #e5e5e5;
}
.navbar .nav li.dropdown > .dropdown-toggle .caret {
border-top-color: #777777;
border-bottom-color: #777777;
}
.navbar .nav li.dropdown.open > .dropdown-toggle .caret,
.navbar .nav li.dropdown.active > .dropdown-toggle .caret,
.navbar .nav li.dropdown.open.active > .dropdown-toggle .caret {
border-top-color: #555555;
border-bottom-color: #555555;
}
.navbar .pull-right > li > .dropdown-menu,
.navbar .nav > li > .dropdown-menu.pull-right {
right: 0;
left: auto;
}
.navbar .pull-right > li > .dropdown-menu:before,
.navbar .nav > li > .dropdown-menu.pull-right:before {
right: 12px;
left: auto;
}
.navbar .pull-right > li > .dropdown-menu:after,
.navbar .nav > li > .dropdown-menu.pull-right:after {
right: 13px;
left: auto;
}
.navbar .pull-right > li > .dropdown-menu .dropdown-menu,
.navbar .nav > li > .dropdown-menu.pull-right .dropdown-menu {
right: 100%;
left: auto;
margin-right: -1px;
margin-left: 0;
-webkit-border-radius: 6px 0 6px 6px;
-moz-border-radius: 6px 0 6px 6px;
border-radius: 6px 0 6px 6px;
}
.navbar-inverse .navbar-inner {
background-color: #1b1b1b;
background-image: -moz-linear-gradient(top, #222222, #111111);
background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#222222), to(#111111));
background-image: -webkit-linear-gradient(top, #222222, #111111);
background-image: -o-linear-gradient(top, #222222, #111111);
background-image: linear-gradient(to bottom, #222222, #111111);
background-repeat: repeat-x;
border-color: #252525;
filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#ff222222', endColorstr='#ff111111', GradientType=0);
}
.navbar-inverse .brand,
.navbar-inverse .nav > li > a {
color: #999999;
text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.25);
}
.navbar-inverse .brand:hover,
.navbar-inverse .nav > li > a:hover,
.navbar-inverse .brand:focus,
.navbar-inverse .nav > li > a:focus {
color: #ffffff;
}
.navbar-inverse .brand {
color: #999999;
}
.navbar-inverse .navbar-text {
color: #999999;
}
.navbar-inverse .nav > li > a:focus,
.navbar-inverse .nav > li > a:hover {
color: #ffffff;
background-color: transparent;
}
.navbar-inverse .nav .active > a,
.navbar-inverse .nav .active > a:hover,
.navbar-inverse .nav .active > a:focus {
color: #ffffff;
background-color: #111111;
}
.navbar-inverse .navbar-link {
color: #999999;
}
.navbar-inverse .navbar-link:hover,
.navbar-inverse .navbar-link:focus {
color: #ffffff;
}
.navbar-inverse .divider-vertical {
border-right-color: #222222;
border-left-color: #111111;
}
.navbar-inverse .nav li.dropdown.open > .dropdown-toggle,
.navbar-inverse .nav li.dropdown.active > .dropdown-toggle,
.navbar-inverse .nav li.dropdown.open.active > .dropdown-toggle {
color: #ffffff;
background-color: #111111;
}
.navbar-inverse .nav li.dropdown > a:hover .caret,
.navbar-inverse .nav li.dropdown > a:focus .caret {
border-top-color: #ffffff;
border-bottom-color: #ffffff;
}
.navbar-inverse .nav li.dropdown > .dropdown-toggle .caret {
border-top-color: #999999;
border-bottom-color: #999999;
}
.navbar-inverse .nav li.dropdown.open > .dropdown-toggle .caret,
.navbar-inverse .nav li.dropdown.active > .dropdown-toggle .caret,
.navbar-inverse .nav li.dropdown.open.active > .dropdown-toggle .caret {
border-top-color: #ffffff;
border-bottom-color: #ffffff;
}
.navbar-inverse .navbar-search .search-query {
color: #ffffff;
background-color: #515151;
border-color: #111111;
-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;
-o-transition: none;
transition: none;
}
.navbar-inverse .navbar-search .search-query:-moz-placeholder {
color: #cccccc;
}
.navbar-inverse .navbar-search .search-query:-ms-input-placeholder {
color: #cccccc;
}
.navbar-inverse .navbar-search .search-query::-webkit-input-placeholder {
color: #cccccc;
}
.navbar-inverse .navbar-search .search-query:focus,
.navbar-inverse .navbar-search .search-query.focused {
padding: 5px 15px;
color: #333333;
text-shadow: 0 1px 0 #ffffff;
background-color: #ffffff;
border: 0;
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-inverse .btn-navbar {
color: #ffffff;
text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.25);
background-color: #0e0e0e;
*background-color: #040404;
background-image: -moz-linear-gradient(top, #151515, #040404);
background-image: -webkit-gradient(linear, 0 0, 0 100%, from(#151515), to(#040404));
background-image: -webkit-linear-gradient(top, #151515, #040404);
background-image: -o-linear-gradient(top, #151515, #040404);
background-image: linear-gradient(to bottom, #151515, #040404);
background-repeat: repeat-x;
border-color: #040404 #040404 #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='#ff151515', endColorstr='#ff040404', GradientType=0);
filter: progid:DXImageTransform.Microsoft.gradient(enabled=false);
}
.navbar-inverse .btn-navbar:hover,
.navbar-inverse .btn-navbar:focus,
.navbar-inverse .btn-navbar:active,
.navbar-inverse .btn-navbar.active,
.navbar-inverse .btn-navbar.disabled,
.navbar-inverse .btn-navbar[disabled] {
color: #ffffff;
background-color: #040404;
*background-color: #000000;
}
.navbar-inverse .btn-navbar:active,
.navbar-inverse .btn-navbar.active {
background-color: #000000 \9;
}
.breadcrumb {
padding: 8px 15px;
margin: 0 0 20px;
list-style: none;
background-color: #f5f5f5;
-webkit-border-radius: 4px;
-moz-border-radius: 4px;
border-radius: 4px;
}
.breadcrumb > li {
display: inline-block;
*display: inline;
text-shadow: 0 1px 0 #ffffff;
*zoom: 1;
}
.breadcrumb > li > .divider {
padding: 0 5px;
color: #ccc;
}
.breadcrumb > .active {
color: #999999;
}
.pagination {
margin: 20px 0;
}
.pagination ul {
display: inline-block;
*display: inline;
margin-bottom: 0;
margin-left: 0;
-webkit-border-radius: 4px;
-moz-border-radius: 4px;
border-radius: 4px;
*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);
}
.pagination ul > li {
display: inline;
}
.pagination ul > li > a,
.pagination ul > li > span {
float: left;
padding: 4px 12px;
line-height: 20px;
text-decoration: none;
background-color: #ffffff;
border: 1px solid #dddddd;
border-left-width: 0;
}
.pagination ul > li > a:hover,
.pagination ul > li > a:focus,
.pagination ul > .active > a,
.pagination ul > .active > span {
background-color: #f5f5f5;
}
.pagination ul > .active > a,
.pagination ul > .active > span {
color: #999999;
cursor: default;
}
.pagination ul > .disabled > span,
.pagination ul > .disabled > a,
.pagination ul > .disabled > a:hover,
.pagination ul > .disabled > a:focus {
color: #999999;
cursor: default;
background-color: transparent;
}
.pagination ul > li:first-child > a,
.pagination ul > li:first-child > span {
border-left-width: 1px;
-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;
-moz-border-radius-topleft: 4px;
}
.pagination ul > li:last-child > a,
.pagination ul > li:last-child > span {
-webkit-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;
}
.pagination-centered {
text-align: center;
}
.pagination-right {
text-align: right;
}
.pagination-large ul > li > a,
.pagination-large ul > li > span {
padding: 11px 19px;
font-size: 17.5px;
}
.pagination-large ul > li:first-child > a,
.pagination-large ul > li:first-child > span {
-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;
-moz-border-radius-topleft: 6px;
}
.pagination-large ul > li:last-child > a,
.pagination-large ul > li:last-child > span {
-webkit-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;
}
.pagination-mini ul > li:first-child > a,
.pagination-small ul > li:first-child > a,
.pagination-mini ul > li:first-child > span,
.pagination-small ul > li:first-child > span {
-webkit-border-bottom-left-radius: 3px;
border-bottom-left-radius: 3px;
-webkit-border-top-left-radius: 3px;
border-top-left-radius: 3px;
-moz-border-radius-bottomleft: 3px;
-moz-border-radius-topleft: 3px;
}
.pagination-mini ul > li:last-child > a,
.pagination-small ul > li:last-child > a,
.pagination-mini ul > li:last-child > span,
.pagination-small ul > li:last-child > span {
-webkit-border-top-right-radius: 3px;
border-top-right-radius: 3px;
-webkit-border-bottom-right-radius: 3px;
border-bottom-right-radius: 3px;
-moz-border-radius-topright: 3px;
-moz-border-radius-bottomright: 3px;
}
.pagination-small ul > li > a,
.pagination-small ul > li > span {
padding: 2px 10px;
font-size: 11.9px;
}
.pagination-mini ul > li > a,
.pagination-mini ul > li > span {
padding: 0 6px;
font-size: 10.5px;
}
.pager {
margin: 20px 0;
text-align: center;
list-style: none;
*zoom: 1;
}
.pager:before,
.pager:after {
display: table;
line-height: 0;
content: "";
}
.pager:after {
clear: both;
}
.pager li {
display: inline;
}
.pager li > a,
.pager li > span {
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 li > a:hover,
.pager li > a:focus {
text-decoration: none;
background-color: #f5f5f5;
}
.pager .next > a,
.pager .next > span {
float: right;
}
.pager .previous > a,
.pager .previous > span {
float: left;
}
.pager .disabled > a,
.pager .disabled > a:hover,
.pager .disabled > a:focus,
.pager .disabled > span {
color: #999999;
cursor: default;
background-color: #fff;
}
.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: 10%;
left: 50%;
z-index: 1050;
width: 560px;
margin-left: -280px;
background-color: #ffffff;
border: 1px solid #999;
border: 1px solid rgba(0, 0, 0, 0.3);
*border: 1px solid #999;
-webkit-border-radius: 6px;
-moz-border-radius: 6px;
border-radius: 6px;
outline: none;
-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 {
top: -25%;
-webkit-transition: opacity 0.3s linear, top 0.3s ease-out;
-moz-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: 10%;
}
.modal-header {
padding: 9px 15px;
border-bottom: 1px solid #eee;
}
.modal-header .close {
margin-top: 2px;
}
.modal-header h3 {
margin: 0;
line-height: 30px;
}
.modal-body {
position: relative;
max-height: 400px;
padding: 15px;
overflow-y: auto;
}
.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;
*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;
line-height: 0;
content: "";
}
.modal-footer:after {
clear: both;
}
.modal-footer .btn + .btn {
margin-bottom: 0;
margin-left: 5px;
}
.modal-footer .btn-group .btn + .btn {
margin-left: -1px;
}
.modal-footer .btn-block + .btn-block {
margin-left: 0;
}
.tooltip {
position: absolute;
z-index: 1030;
display: block;
font-size: 11px;
line-height: 1.4;
opacity: 0;
filter: alpha(opacity=0);
visibility: visible;
}
.tooltip.in {
opacity: 0.8;
filter: alpha(opacity=80);
}
.tooltip.top {
padding: 5px 0;
margin-top: -3px;
}
.tooltip.right {
padding: 0 5px;
margin-left: 3px;
}
.tooltip.bottom {
padding: 5px 0;
margin-top: 3px;
}
.tooltip.left {
padding: 0 5px;
margin-left: -3px;
}
.tooltip-inner {
max-width: 200px;
padding: 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;
border-color: transparent;
border-style: solid;
}
.tooltip.top .tooltip-arrow {
bottom: 0;
left: 50%;
margin-left: -5px;
border-top-color: #000000;
border-width: 5px 5px 0;
}
.tooltip.right .tooltip-arrow {
top: 50%;
left: 0;
margin-top: -5px;
border-right-color: #000000;
border-width: 5px 5px 5px 0;
}
.tooltip.left .tooltip-arrow {
top: 50%;
right: 0;
margin-top: -5px;
border-left-color: #000000;
border-width: 5px 0 5px 5px;
}
.tooltip.bottom .tooltip-arrow {
top: 0;
left: 50%;
margin-left: -5px;
border-bottom-color: #000000;
border-width: 0 5px 5px;
}
.popover {
position: absolute;
top: 0;
left: 0;
z-index: 1010;
display: none;
max-width: 276px;
padding: 1px;
text-align: left;
white-space: normal;
background-color: #ffffff;
border: 1px solid #ccc;
border: 1px solid rgba(0, 0, 0, 0.2);
-webkit-border-radius: 6px;
-moz-border-radius: 6px;
border-radius: 6px;
-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;
}
.popover.top {
margin-top: -10px;
}
.popover.right {
margin-left: 10px;
}
.popover.bottom {
margin-top: 10px;
}
.popover.left {
margin-left: -10px;
}
.popover-title {
padding: 8px 14px;
margin: 0;
font-size: 14px;
font-weight: normal;
line-height: 18px;
background-color: #f7f7f7;
border-bottom: 1px solid #ebebeb;
-webkit-border-radius: 5px 5px 0 0;
-moz-border-radius: 5px 5px 0 0;
border-radius: 5px 5px 0 0;
}
.popover-title:empty {
display: none;
}
.popover-content {
padding: 9px 14px;
}
.popover .arrow,
.popover .arrow:after {
position: absolute;
display: block;
width: 0;
height: 0;
border-color: transparent;
border-style: solid;
}
.popover .arrow {
border-width: 11px;
}
.popover .arrow:after {
border-width: 10px;
content: "";
}
.popover.top .arrow {
bottom: -11px;
left: 50%;
margin-left: -11px;
border-top-color: #999;
border-top-color: rgba(0, 0, 0, 0.25);
border-bottom-width: 0;
}
.popover.top .arrow:after {
bottom: 1px;
margin-left: -10px;
border-top-color: #ffffff;
border-bottom-width: 0;
}
.popover.right .arrow {
top: 50%;
left: -11px;
margin-top: -11px;
border-right-color: #999;
border-right-color: rgba(0, 0, 0, 0.25);
border-left-width: 0;
}
.popover.right .arrow:after {
bottom: -10px;
left: 1px;
border-right-color: #ffffff;
border-left-width: 0;
}
.popover.bottom .arrow {
top: -11px;
left: 50%;
margin-left: -11px;
border-bottom-color: #999;
border-bottom-color: rgba(0, 0, 0, 0.25);
border-top-width: 0;
}
.popover.bottom .arrow:after {
top: 1px;
margin-left: -10px;
border-bottom-color: #ffffff;
border-top-width: 0;
}
.popover.left .arrow {
top: 50%;
right: -11px;
margin-top: -11px;
border-left-color: #999;
border-left-color: rgba(0, 0, 0, 0.25);
border-right-width: 0;
}
.popover.left .arrow:after {
right: 1px;
bottom: -10px;
border-left-color: #ffffff;
border-right-width: 0;
}
.thumbnails {
margin-left: -20px;
list-style: none;
*zoom: 1;
}
.thumbnails:before,
.thumbnails:after {
display: table;
line-height: 0;
content: "";
}
.thumbnails:after {
clear: both;
}
.row-fluid .thumbnails {
margin-left: 0;
}
.thumbnails > li {
float: left;
margin-bottom: 20px;
margin-left: 20px;
}
.thumbnail {
display: block;
padding: 4px;
line-height: 20px;
border: 1px solid #ddd;
-webkit-border-radius: 4px;
-moz-border-radius: 4px;
border-radius: 4px;
-webkit-box-shadow: 0 1px 3px rgba(0, 0, 0, 0.055);
-moz-box-shadow: 0 1px 3px rgba(0, 0, 0, 0.055);
box-shadow: 0 1px 3px rgba(0, 0, 0, 0.055);
-webkit-transition: all 0.2s ease-in-out;
-moz-transition: all 0.2s ease-in-out;
-o-transition: all 0.2s ease-in-out;
transition: all 0.2s ease-in-out;
}
a.thumbnail:hover,
a.thumbnail:focus {
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-right: auto;
margin-left: auto;
}
.thumbnail .caption {
padding: 9px;
color: #555555;
}
.media,
.media-body {
overflow: hidden;
*overflow: visible;
zoom: 1;
}
.media,
.media .media {
margin-top: 15px;
}
.media:first-child {
margin-top: 0;
}
.media-object {
display: block;
}
.media-heading {
margin: 0 0 5px;
}
.media > .pull-left {
margin-right: 10px;
}
.media > .pull-right {
margin-left: 10px;
}
.media-list {
margin-left: 0;
list-style: none;
}
.label,
.badge {
display: inline-block;
padding: 2px 4px;
font-size: 11.844px;
font-weight: bold;
line-height: 14px;
color: #ffffff;
text-shadow: 0 -1px 0 rgba(0, 0, 0, 0.25);
white-space: nowrap;
vertical-align: baseline;
background-color: #999999;
}
.label {
-webkit-border-radius: 3px;
-moz-border-radius: 3px;
border-radius: 3px;
}
.badge {
padding-right: 9px;
padding-left: 9px;
-webkit-border-radius: 9px;
-moz-border-radius: 9px;
border-radius: 9px;
}
.label:empty,
.badge:empty {
display: none;
}
a.label:hover,
a.label:focus,
a.badge:hover,
a.badge:focus {
color: #ffffff;
text-decoration: none;
cursor: pointer;
}
.label-important,
.badge-important {
background-color: #b94a48;
}
.label-important[href],
.badge-important[href] {
background-color: #953b39;
}
.label-warning,
.badge-warning {
background-color: #f89406;
}
.label-warning[href],
.badge-warning[href] {
background-color: #c67605;
}
.label-success,
.badge-success {
background-color: #468847;
}
.label-success[href],
.badge-success[href] {
background-color: #356635;
}
.label-info,
.badge-info {
background-color: #3a87ad;
}
.label-info[href],
.badge-info[href] {
background-color: #2d6987;
}
.label-inverse,
.badge-inverse {
background-color: #333333;
}
.label-inverse[href],
.badge-inverse[href] {
background-color: #1a1a1a;
}
.btn .label,
.btn .badge {
position: relative;
top: -1px;
}
.btn-mini .label,
.btn-mini .badge {
top: 0;
}
@-webkit-keyframes progress-bar-stripes {
from {
background-position: 40px 0;
}
to {
background-position: 0 0;
}
}
@-moz-keyframes progress-bar-stripes {
from {
background-position: 40px 0;
}
to {
background-position: 0 0;
}
}
@-ms-keyframes progress-bar-stripes {
from {
background-position: 40px 0;
}
to {
background-position: 0 0;
}
}
@-o-keyframes progress-bar-stripes {
from {
background-position: 0 0;
}
to {
background-position: 40px 0;
}
}
@keyframes progress-bar-stripes {
from {
background-position: 40px 0;
}
to {
background-position: 0 0;
}
}
.progress {
height: 20px;
margin-bottom: 20px;
overflow: hidden;
background-color: #f7f7f7;
background-image: -moz-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(to bottom, #f5f5f5, #f9f9f9);
background-repeat: repeat-x;
-webkit-border-radius: 4px;
-moz-border-radius: 4px;
border-radius: 4px;
filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#fff5f5f5', endColorstr='#fff9f9f9', 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 {
float: left;
width: 0;
height: 100%;
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: -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(to bottom, #149bdf, #0480be);
background-repeat: repeat-x;
filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#ff149bdf', endColorstr='#ff0480be', 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;
box-sizing: border-box;
-webkit-transition: width 0.6s ease;
-moz-transition: width 0.6s ease;
-o-transition: width 0.6s ease;
transition: width 0.6s ease;
}
.progress .bar + .bar {
-webkit-box-shadow: inset 1px 0 0 rgba(0, 0, 0, 0.15), inset 0 -1px 0 rgba(0, 0, 0, 0.15);
-moz-box-shadow: inset 1px 0 0 rgba(0, 0, 0, 0.15), inset 0 -1px 0 rgba(0, 0, 0, 0.15);
box-shadow: inset 1px 0 0 rgba(0, 0, 0, 0.15), inset 0 -1px 0 rgba(0, 0, 0, 0.15);
}
.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: -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;
-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,
.progress .bar-danger {
background-color: #dd514c;
background-image: -moz-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(to bottom, #ee5f5b, #c43c35);
background-repeat: repeat-x;
filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#ffee5f5b', endColorstr='#ffc43c35', GradientType=0);
}
.progress-danger.progress-striped .bar,
.progress-striped .bar-danger {
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: -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,
.progress .bar-success {
background-color: #5eb95e;
background-image: -moz-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(to bottom, #62c462, #57a957);
background-repeat: repeat-x;
filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#ff62c462', endColorstr='#ff57a957', GradientType=0);
}
.progress-success.progress-striped .bar,
.progress-striped .bar-success {
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: -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,
.progress .bar-info {
background-color: #4bb1cf;
background-image: -moz-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(to bottom, #5bc0de, #339bb9);
background-repeat: repeat-x;
filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#ff5bc0de', endColorstr='#ff339bb9', GradientType=0);
}
.progress-info.progress-striped .bar,
.progress-striped .bar-info {
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: -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,
.progress .bar-warning {
background-color: #faa732;
background-image: -moz-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(to bottom, #fbb450, #f89406);
background-repeat: repeat-x;
filter: progid:DXImageTransform.Microsoft.gradient(startColorstr='#fffbb450', endColorstr='#fff89406', GradientType=0);
}
.progress-warning.progress-striped .bar,
.progress-striped .bar-warning {
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: -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: 20px;
}
.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-toggle {
cursor: pointer;
}
.accordion-inner {
padding: 9px 15px;
border-top: 1px solid #e5e5e5;
}
.carousel {
position: relative;
margin-bottom: 20px;
line-height: 1;
}
.carousel-inner {
position: relative;
width: 100%;
overflow: hidden;
}
.carousel-inner > .item {
position: relative;
display: none;
-webkit-transition: 0.6s ease-in-out left;
-moz-transition: 0.6s ease-in-out left;
-o-transition: 0.6s ease-in-out left;
transition: 0.6s ease-in-out left;
}
.carousel-inner > .item > img,
.carousel-inner > .item > a > img {
display: block;
line-height: 1;
}
.carousel-inner > .active,
.carousel-inner > .next,
.carousel-inner > .prev {
display: block;
}
.carousel-inner > .active {
left: 0;
}
.carousel-inner > .next,
.carousel-inner > .prev {
position: absolute;
top: 0;
width: 100%;
}
.carousel-inner > .next {
left: 100%;
}
.carousel-inner > .prev {
left: -100%;
}
.carousel-inner > .next.left,
.carousel-inner > .prev.right {
left: 0;
}
.carousel-inner > .active.left {
left: -100%;
}
.carousel-inner > .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 {
right: 15px;
left: auto;
}
.carousel-control:hover,
.carousel-control:focus {
color: #ffffff;
text-decoration: none;
opacity: 0.9;
filter: alpha(opacity=90);
}
.carousel-indicators {
position: absolute;
top: 15px;
right: 15px;
z-index: 5;
margin: 0;
list-style: none;
}
.carousel-indicators li {
display: block;
float: left;
width: 10px;
height: 10px;
margin-left: 5px;
text-indent: -999px;
background-color: #ccc;
background-color: rgba(255, 255, 255, 0.25);
border-radius: 5px;
}
.carousel-indicators .active {
background-color: #fff;
}
.carousel-caption {
position: absolute;
right: 0;
bottom: 0;
left: 0;
padding: 15px;
background: #333333;
background: rgba(0, 0, 0, 0.75);
}
.carousel-caption h4,
.carousel-caption p {
line-height: 20px;
color: #ffffff;
}
.carousel-caption h4 {
margin: 0 0 5px;
}
.carousel-caption p {
margin-bottom: 0;
}
.hero-unit {
padding: 60px;
margin-bottom: 30px;
font-size: 18px;
font-weight: 200;
line-height: 30px;
color: inherit;
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;
letter-spacing: -1px;
color: inherit;
}
.hero-unit li {
line-height: 30px;
}
.pull-right {
float: right;
}
.pull-left {
float: left;
}
.hide {
display: none;
}
.show {
display: block;
}
.invisible {
visibility: hidden;
}
.affix {
position: fixed;
}
{-# START_FILE static/css/normalize.css #-}
/*! normalize.css v2.1.2 | MIT License | git.io/normalize */
/* ==========================================================================
HTML5 display definitions
========================================================================== */
/**
* Correct `block` display not defined in IE 8/9.
*/
article,
aside,
details,
figcaption,
figure,
footer,
header,
hgroup,
main,
nav,
section,
summary {
display: block;
}
/**
* Correct `inline-block` display not defined in IE 8/9.
*/
audio,
canvas,
video {
display: inline-block;
}
/**
* Prevent modern browsers from displaying `audio` without controls.
* Remove excess height in iOS 5 devices.
*/
audio:not([controls]) {
display: none;
height: 0;
}
/**
* Address styling not present in IE 8/9.
*/
[hidden] {
display: none;
}
/* ==========================================================================
Base
========================================================================== */
/**
* 1. Set default font family to sans-serif.
* 2. Prevent iOS text size adjust after orientation change, without disabling
* user zoom.
*/
html {
font-family: sans-serif; /* 1 */
-ms-text-size-adjust: 100%; /* 2 */
-webkit-text-size-adjust: 100%; /* 2 */
}
/**
* Remove default margin.
*/
body {
margin: 0;
}
/* ==========================================================================
Links
========================================================================== */
/**
* Address `outline` inconsistency between Chrome and other browsers.
*/
a:focus {
outline: thin dotted;
}
/**
* Improve readability when focused and also mouse hovered in all browsers.
*/
a:active,
a:hover {
outline: 0;
}
/* ==========================================================================
Typography
========================================================================== */
/**
* Address variable `h1` font-size and margin within `section` and `article`
* contexts in Firefox 4+, Safari 5, and Chrome.
*/
h1 {
font-size: 2em;
margin: 0.67em 0;
}
/**
* Address styling not present in IE 8/9, Safari 5, and Chrome.
*/
abbr[title] {
border-bottom: 1px dotted;
}
/**
* Address style set to `bolder` in Firefox 4+, Safari 5, and Chrome.
*/
b,
strong {
font-weight: bold;
}
/**
* Address styling not present in Safari 5 and Chrome.
*/
dfn {
font-style: italic;
}
/**
* Address differences between Firefox and other browsers.
*/
hr {
-moz-box-sizing: content-box;
box-sizing: content-box;
height: 0;
}
/**
* Address styling not present in IE 8/9.
*/
mark {
background: #ff0;
color: #000;
}
/**
* Correct font family set oddly in Safari 5 and Chrome.
*/
code,
kbd,
pre,
samp {
font-family: monospace, serif;
font-size: 1em;
}
/**
* Improve readability of pre-formatted text in all browsers.
*/
pre {
white-space: pre-wrap;
}
/**
* Set consistent quote types.
*/
q {
quotes: "\201C" "\201D" "\2018" "\2019";
}
/**
* Address inconsistent and variable font size in all browsers.
*/
small {
font-size: 80%;
}
/**
* Prevent `sub` and `sup` affecting `line-height` in all browsers.
*/
sub,
sup {
font-size: 75%;
line-height: 0;
position: relative;
vertical-align: baseline;
}
sup {
top: -0.5em;
}
sub {
bottom: -0.25em;
}
/* ==========================================================================
Embedded content
========================================================================== */
/**
* Remove border when inside `a` element in IE 8/9.
*/
img {
border: 0;
}
/**
* Correct overflow displayed oddly in IE 9.
*/
svg:not(:root) {
overflow: hidden;
}
/* ==========================================================================
Figures
========================================================================== */
/**
* Address margin not present in IE 8/9 and Safari 5.
*/
figure {
margin: 0;
}
/* ==========================================================================
Forms
========================================================================== */
/**
* Define consistent border, margin, and padding.
*/
fieldset {
border: 1px solid #c0c0c0;
margin: 0 2px;
padding: 0.35em 0.625em 0.75em;
}
/**
* 1. Correct `color` not being inherited in IE 8/9.
* 2. Remove padding so people aren't caught out if they zero out fieldsets.
*/
legend {
border: 0; /* 1 */
padding: 0; /* 2 */
}
/**
* 1. Correct font family not being inherited in all browsers.
* 2. Correct font size not being inherited in all browsers.
* 3. Address margins set differently in Firefox 4+, Safari 5, and Chrome.
*/
button,
input,
select,
textarea {
font-family: inherit; /* 1 */
font-size: 100%; /* 2 */
margin: 0; /* 3 */
}
/**
* Address Firefox 4+ setting `line-height` on `input` using `!important` in
* the UA stylesheet.
*/
button,
input {
line-height: normal;
}
/**
* Address inconsistent `text-transform` inheritance for `button` and `select`.
* All other form control elements do not inherit `text-transform` values.
* Correct `button` style inheritance in Chrome, Safari 5+, and IE 8+.
* Correct `select` style inheritance in Firefox 4+ and Opera.
*/
button,
select {
text-transform: none;
}
/**
* 1. Avoid the WebKit bug in Android 4.0.* where (2) destroys native `audio`
* and `video` controls.
* 2. Correct inability to style clickable `input` types in iOS.
* 3. Improve usability and consistency of cursor style between image-type
* `input` and others.
*/
button,
html input[type="button"], /* 1 */
input[type="reset"],
input[type="submit"] {
-webkit-appearance: button; /* 2 */
cursor: pointer; /* 3 */
}
/**
* Re-set default cursor for disabled elements.
*/
button[disabled],
html input[disabled] {
cursor: default;
}
/**
* 1. Address box sizing set to `content-box` in IE 8/9.
* 2. Remove excess padding in IE 8/9.
*/
input[type="checkbox"],
input[type="radio"] {
box-sizing: border-box; /* 1 */
padding: 0; /* 2 */
}
/**
* 1. Address `appearance` set to `searchfield` in Safari 5 and Chrome.
* 2. Address `box-sizing` set to `border-box` in Safari 5 and Chrome
* (include `-moz` to future-proof).
*/
input[type="search"] {
-webkit-appearance: textfield; /* 1 */
-moz-box-sizing: content-box;
-webkit-box-sizing: content-box; /* 2 */
box-sizing: content-box;
}
/**
* Remove inner padding and search cancel button in Safari 5 and Chrome
* on OS X.
*/
input[type="search"]::-webkit-search-cancel-button,
input[type="search"]::-webkit-search-decoration {
-webkit-appearance: none;
}
/**
* Remove inner padding and border in Firefox 4+.
*/
button::-moz-focus-inner,
input::-moz-focus-inner {
border: 0;
padding: 0;
}
/**
* 1. Remove default vertical scrollbar in IE 8/9.
* 2. Improve readability and alignment in all browsers.
*/
textarea {
overflow: auto; /* 1 */
vertical-align: top; /* 2 */
}
/* ==========================================================================
Tables
========================================================================== */
/**
* Remove most spacing between table cells.
*/
table {
border-collapse: collapse;
border-spacing: 0;
}
{-# START_FILE BASE64 static/img/glyphicons-halflings-white.png #-}
iVBORw0KGgoAAAANSUhEUgAAAdUAAACfCAMAAACY07N7AAAC2VBMVEX///8AAAAAAAD5+fn///8A
AAD////9/f1tbW0AAAD///////////8AAAAAAAD////w8PD+/v729vYAAAD8/PwAAAAAAAD/////
///a2toAAADCwsL09PT////////09PT39/f///8AAAAAAACzs7P9/f0AAADi4uKwsLD////////7
+/vn5+f+/v7///8AAADt7e0AAADPz88AAAD9/f329vbt7e37+/vn5+f6+vrh4eGSkpL+/v7+/v7B
wcGYmJh0dHTh4eHQ0NAAAADz8/O7u7uhoaGAgID9/f3U1NRiYmL////V1dX4+Pjc3Nz6+vr7+/vp
6en7+/v9/f39/f3R0dHy8vL8/Pz4+Pjr6+v8/Py2trbGxsbl5eXu7u719fX9/f1lZWVnZ2fw8PC2
trbg4OD39/f6+vrp6enl5eX6+vr4+PjLy8v///+EhITx8fF4eHj39/fd3d35+fnIyMjS0tLs7Oz6
+vre3t7i4uLm5ubz8/Obm5uoqKilpaXc3Nzu7u7////x8fHJycnw8PD////////e3t7Gxsa8vLzr
6+vW1tbQ0NDi4uL5+fn09PTi4uLs7Oz19fW0tLT////9/f37+/v8/Pz6+vrm5uYAAADk5OT8/Pz3
9/ewsLCZmZn9/f3s7Oz8/PzBwcHp6en////a2trw8PDw8PD19fXx8fH+/v74+Pj+/v6Ojo7i4uL7
+/v5+fnc3Nz////y8vL6+vqfn5/t7e339/f29vbo6Ojz8/P6+vr19fX19fWmpqbLy8v6+vr4+PjT
09Pr6+v6+vrr6+uqqqrz8/Pt7e2ioqLPz8/a2trW1taioqLr6+vi4uL5+flVVVXNzc3////W1tbj
4+Ph4eHq6ur8/Pz////29vb7+/vz8/P09PTMzMz////////5+fn19fX////y8vL9/f0AAADZ2dn8
/Pz7+/v8/Pzp6em/v7/7+/vq6urp6en+/v7////4ck/mAAAA8nRSTlMAGgDUzwIP8SMQ759fCgUv
qfDGFeIYA78fbxNTt98/hsV/BhdD4Q1rRI+vwo3ATxJTD18IoKWasozTETbQ4D40IX5hC6dAMR7R
XydvEsRuotKLkZCATYahkzOxQlFqmbZwJiUhFWy1wyJYcXI7gB2XIEFbgjxgiWFtfTSFMy8wSYgE
qFBDTSE2KCpnSyZZUaZHRFAsDuWBYJJ7AVZQpC0Z6njBKWjdN4dlMV30iN8bV7+zJJeHMRiDYsR6
U9yVYxdP2c1dj8CKFZZVFjtaaTxOI9cMKQk4NnBW4PKUOmiNI/kwWoQYUdQOSk6GvkUURFSM3n71
h14AAB4tSURBVHhe7J2HfyPHmaa/YicCDTQCQRAkQWgABpMcDSkOw3CGM5o8Gk2QRjlZOVjBsizb
cs5pndb22r7d23ybc7zbdDnnnHPO+d6/4FjdIGu6vmp280CtbF+/kkn/nip+aPSDDqA+FOm7J3nc
IoDi0NAQkY3d2IaJSws2NNZZnCouduhAsrgf7o4BYy59O4fvn3ROJQKoREkBGKqYytAJCCEQWh22
0I81TPFIozLaNiCMH4PJr47WIooL1C1isUUsFSwpkMqPAMARDUIFjLcYpj5tGbmqw+P6bhz49jZw
bZ9S9k8Kd20QQLDdzFbdIz/JJ0OFyJFaI6mOcZ6HGOzAGxdi0tN8JL063CmJwi9FviX34m4FUrlx
l0PgaBgIbrXJJfVp08yTrbq2tt99bINtCj9p/2TiZMMigCzYGa0WxwBgrEjxCBUici56obyLjsF+
/ez8KGLwUdxVJuq9HZcpljX16lgjlaeg8hTpmUVNqubcUjzNKnBbGIBbJS6pT8nMo5ilAms3kxsA
bElvsP0DqP2Ttt9KsEYIoBELpWxWDyHMocSDdUiCYMYDvJmAl5sUE+cDgiaiLMd6FrTJUmskFaTy
Eah8JPZsiru8WGL8ouLpx2rfqshkVQix+z/OoyRIte64GalXsb5/JFX7J4UfxsVI3EUcMyrVrbqA
tbVVB1x96q39f4Yo0goYpBJ6EmhWa31nx3WrUmskFaTyJah8iVSofNrqY2umHOeNsyIQ457ksUTn
lP0dq4NfVyuLrpTKLlHy0sUp1UASq/2Txr2ASAiiwJvNYrVzBLjUbJ4BjlS0qbdE//StUgAExAMy
WG2jI2EFDd3qujNsWcPOesxquY6d1OOSmiMbId4YCTT+BEq0xDjRKACM8mO1HwF2mYm+DnRdrRRh
t5hUmRPHAeD4CdL3jwBEBQ3OheC84VE/Xi2L1Q9fB14kOgFc/+zeVgmgJKuVTnzsPSh2iFoncY82
uVrw14aH1/xCNVbszO4heYa0vDPk30uc/+Oxv2LgBAAGdjSM8R548OvqoxHiUl0bYWyX7R8h1P5J
22+HUIlAxXSl5FYDeZS67hHgTO//2aoPbWy12r9JqFVifFsqsLYGbGtlJyq+V2TuBRrA3WTgs/AY
70S30519XFebg19X3520+bakctBO2j+Z+Nt23qsdwduyWCWnjjB1h/ZvdWkqhPxKVhi3gMamh2Il
hn304xeIaTVJpVlsTp9FLRt3F9DPgvtmX1czbf4FSeXghcT9k4WXLYxtg8oYrLJRKZNTC7XWa7R/
q1RDCDfq7RltpDwixPTcjIdii1R87MYnptUktdKYn6Pz89ZSJj6l6k8NcA+c9bqavvmF6jbdHqwW
0vYP5/q9dLGo7qVTrY5OXKnXr0yM7m3V+FzIAs4S0crEckCmBDOedY1UCmI3+tN0LjUucan0yDOy
cjD8PZk4VJDCB3+/qmmtSqlc68g2dUYKlLJ/UrgzMl73Gu3xESfFqorzwO0OsXiI4kmrCe/SRoQ4
T3slOK2ea0qa001Tgci0E2TiQkVk5tHooO9XnYJDWcP3TzovT4xOL5dJixDqXz29gHhGRZTRIRog
zT2l5mk6b8F+G5KhtyB5/j+2mie3mie3mlvNk1vNk1vNk1vNk1vNrZbouy65VR8+sST3UJbGpopj
JYZdoNsFXGOptDrpfAn9LGWvU5xaLJFvmr9Ycu3kzstYuiHrUuaUFsfGFg/yQOFa+HaCIAeHMNTn
PgA/wSrnrg3UPPD+1R8AHnwQ+IEUq7xONv4w+rk7ex2vBhRhng9ks+oyGAXU6XYrROTzXnTg4PrR
W3EAIQQI8tueVn3I+GarnNuoz4+OztdZ/+pl4KWXgMspVnmdbHwWIgxm91XHA7JxiJ1A64jHvJg0
WS0CmBqzWf3NLSG2NmGTnopCOm8l8RZKpNsDSbG0l1UfUXyjVcZLqE8EoGCirj1cC/20Eq3yOgjr
ML6wwHgLFoWxUGHzicx1iB4CQJy7Iee7S4biAw4QUM9k1XhodzE+1yRqzo2zk3YXkPZaZODoEJl4
8avVU5pVQQjFJltVUgHfZJX9N/DDuJ3Cerdr/asvA5icBPByolVeB6yO5B2go/OXdzpJLuAVVseu
GOv0/2M+ce6EnO0uIRO3elPbciars9UyhSlXZ/kJvoVSCS3OaeNRCTi/59j7UGFc0J7XVSWVad2h
pv5VEO9fPQXgwx8GcMr4CRybTHWg6ijungJOuRo/hp+gMD+Bw4Y6Xb3OrOSG1BTPdKxCJZNVfJn6
+bKhTnMcGG9yTv+5Zrb6CQT4LLtQEAkBIRKtFgR2IgpZrDa8aEzvX60AQBAAQIVi6bdzEa9jA7as
o3FnGph2NA58ncJ8HTBsz5/Q69QkD1OM9TmNju7yYsqxmtFqI46fo36eg8HSzwM/b7L3fR6RkYPw
fTdzQVBtOklWuT1ulfevCiH0/tV7sZt7zd1ovM5F4KKqozgBpHMA6BB1AIDNb0yuGOvIVPAk8YT1
BztW3fq5rXMb9fZjcexEEwEHpjPw+LjxDPwH2xHgvIIPMy5EBqtCiBSr6f2rswAaQjQAzCbsFVYn
2NwMVB3FCWD1AeC9RO8FADb/mZ6az7fzcf15+Wr7BzhWnYnV5irr1gPtWCX9swSbQHOrXN5qck61
ByTgfPY9DzUC/s6GICfsbVXCFKtp/atL/Y9pHQKAJUOZyUnwOnNzYR3GhWAcKmDzHbU9Gfpsvfcp
Psh11ZhNZXVTG5qbt6hJ8l/OT/eITPyjX6l9kG8mqe0cwGp6/+rdAHCd6Lr+ewKopNbh3Gx1kDoE
T/HBrqvGzCmrc6QlGFFA480k3jxdZpsJEoCgeE8lhfdQQ2JocjKj1fT+1RoAvJ/o/QBQS7fK63Ce
ZjW9TsOrM14dHW+r+an6vF3qZbJKyurBpGnQQpicNDY0E4aAXnQC73+Nh3XZsv5V1ow6RzQnv4/y
MjJZ6nDO64jMdaZHJxgvUHnZND+h/uguHdXmU0KEUF8PPpES0esZG5pJDAkxdDPOk/dC5Mmt5smt
5smt5smt5lbz5Fbz5Fbz5Fbz5FZzq+YGw13usyHXNjcHKKrHZwuvpKWLinmDsECGlAwdND5R2vIg
39VWq0atfV5Y14fs2ryIktVqjbUepmUW9zI2CUyes9AlnvJZtEfiaAEL+7OabBqJQ619rSnT4jwK
iCHaRaD08MdFvVDnWhVXWpm9jFYrEf5AwoYQz1INNQZ7QG91GJfJkH+GBzSyghWyJoUAhJi0SIXR
Aaw292W1eSBWE4uI3YAIGAOYVsWl1sGsvhLhY3FahN6SqXLs0xZKxud5QurmeQee0xGIRnrRD/VG
FE6iJKIQj0gdYsjI1RCzKhErnWrVj3Hy0Y3OwCDaqx2Ya92/VeBYhK8DbLplAbcC7MT2vh/EMZPV
yhraZAjgMGRe9S2RQiWJg519D+oMnPi4e1n1oReZJXLHKtJqNUFrNaZ1EKuzIswstzp+6dK44Vm+
3Ah+CmiZ9/sDxFNBnX6/rTYVHuwMvJBmdcFs1YdmtYp7yLVRdEFUSNBaiGsdwKqKxq0vAF+wuNVT
n+68buH7uQqxdRYnXWL5XXxtYKtChfHEgcHPwKEeSixPJO3BZHVdt1oQc64NwEZM3zqpxPn6+pth
9fiLwIvHmdUOwswaVDTPb+B+YnkYP3dwx2rmu6XWQZyBhdgogHj5XYTChhCm+oWqZtXttn4EYW7W
py+eqbi/Xshk1dqy9mMVH9ja+gCY1YcsIcQW0DGp+GkcJpYbeGlfVktAaXCrzYM5A6/Q3lZpJWE7
C9UYr0wBP4kwSh+TKrmSmsWqNdwctrhV0Q+3ipMnway6eF7usjYe4lZbpRpeIBbge/ZlVZnI0nyX
OjD4PTCHu8hk26tvh6gQ5ypKH5MacSWVW63G9VnDTriYLnNRhEyLdWSaWzLX8AU5/kn98zpXwW6X
1Mj/0NkCFhKOym0emVgYbKXag74HNtchGGyPTmyH2VbZ1adLVbykpGpW41xKJalV34qd30Kwjkxj
S2YX4WLXFfY+FmEakz3SYpt+H7lSXWFHJVud+vfXanNAqzxpj1vQpSpeLmQ7VUmpUivrTw9EmDJl
yty25SD6oVHD404zqTQiMaOF3R/S+IboZ6Mw4PrDB3UGFpRchxTkSX3cwePQd0ZW2P8ZNHkvRJ7c
ap7cap7cam41T241T241T241T241t+q2aOAs0rdVcquuXawYFrpdTF6/l6eDJUqOu0SDxvdpH8mt
us8eR9HUnQ3ftK4vANslPSdxisOlKcjZ8uc6jI9Ryzy/WKEuq+Un9KOHW5VA+VASn+rQAcR2wy/J
vAWwoYjyuD4vFDnwTdi33ZhV1z55ybJYx0B9sw2UDOvrRqK0dAHcZ16C2xp2T1ywntO4d3aCcJXP
H696M4EPm0s1aQWkISRQPpTEgcUWGQKAkLknBtIRlFbGm6yUokyeHDJyGLT6QKRVTcPJS8P6Wq/1
ibnlNg4b1tcFwHR3jOunn8KmEGLkhG3fMeJofPR8yQcWXX1+uTAa+MAFTWpBAKLAtALSEBIoH0ri
AIrdwa1KEVA2OAfMQyZ5csjM14llHX2tahqOX2PLSr0/6kkwrK9r6ts+FcKaq1eZix7h+AnG+4uZ
r+l8oUK+3p3hLiJURVhkjyANgQzUOJTEIWN3BrUqRSgbBs5KKcrlySHOE1tXIq1qGl8V1MPh0KJl
WF/X0AVYQjuk9xuvb7CGTzB+P6w6UL1D4wsoLrLttrEbW7cRjpGR8iFXcaMl3x3UKmxlw8BZKUWZ
PF6IS+VauVSVNjDWHQMu8PWBI6u1+EFc/aTBNQE7Um3Gf3RrZMIbLzgaf6cHKTV+gr+grF4w2iAj
5UNrGmeWpga2GmXNzHkpjbKXsc22v5HUutIAsDbEpao8gCg/xtcHJsn19XV/7kGE4VafkvVtMF5o
Ep0ul3QezHhSKvTXYfSpJ/Y6BSylSKd86A7FjZaqzwxsNXqEOxI4K2WmI2InI3z7fTLGDx93KHxL
Y5ZKvQ3IbDYN6wMDgLa+rnf5i16C1Y+Mb9cHGJdp+pwHMxsFAkjTGg3qUgkYlo7MlA85ihssWZMF
Z1Cr1rA6TgycWzVTFcP2+4lSh50hoqfkWxopleddFoD6nGl9YAD6+rptrB2SuE6xNNClubLjdtFg
fDtmHqworrRG72x0qQSEokzUOJTEw7daI71B75akTyXVwFkpTrlVrjVZ6hDRZZy8ZJZKzkUPjTNk
Wh/YsJL+xzzIeLfH8Z3YyZ0D8eS2ZSAUlUD5UBIH2qfPD/7ORvpUUg2clTJTocK33/zOpi91iFqw
fvCaQ+YEM43H1FjKerzN01UPqJ4O4nj1XAMyjXOrA/HktmUgFJVE+ZBELueNyeVmQk8mZW7dJ2nI
5VIljwaZP0Z5uFZzU34kdYiubY2cdygpwbRylLoeb7MwKkSB7ZjVaSEzvToYT25bFkK1IXPKh0Lk
cD7dowNIVNkx8ugLO/Y4TddqbsqPpA6R06TvvORxEnDeCzFo8l6IPLnVPLnVPLnV3Gqe3Gqe3Gqe
3Gqe3Gpu1dzf+5Zx1ShxcPUHT2uqktR9uN/4ST9UWThIq65taI95S7gaAsyddTWPzc/CB85JnHT3
ZdVuUULel2C1UsTCYK8at0XAUMsNrdqm9pi9uQd4+5kPq569Prk+gOISkaEPeXS+Dns/fJzXJ2op
lMnGAoC1fVlV28/kGVX529x750BW5YcvgEox7EYrAYAQrL835ICJW09Xq09b5vkNGPi5kYl5jbPH
VVmrjQMfqpWI9SE/QvTIRB0lnQdEgZlXarw+LRVBaTZ4o3opu9XOVQALCVK9+aqxkjcTDGT12RqK
QBG1Z4eIDgMAEevvlVyGc2/YKRScYc8033pmHIxbq1crgZWxPrm4qwyc/1CN9D7kCnwfldtxTOPR
Rxc4j3biuOLqyKOEmGy0apCptTJa7RYRxnTc3yvlFYxWpdRBrDZnPIQvjuYQUQ0QgkgIredTchnO
o5PRGufWZH3Y+VmPceDUZ12Ac1ld5zt/BF1G60MOqkA1CLxZjdPVlo01zkOpM+U4b9kpa5oxGyf7
/GQ2qz5UCyrLyoaSp1V6KKVtKfvirkNEDWCH1khlL74u8Trnl3oTTqXIOXBnbw0mTgSdQ6bXg4ze
h7wePrZX0/jVsF+S8UhqoPEppFhlNkaEAKA3cJJtvi3oYCfWY4a73BUu1Q+ri8JBWj0UjbP+Xsll
OPfCRtc7PJ3L+8RKMXsd8+OKKzgngMmqJ4TWh1xBtSq/HtL4j1uyC4vxUiRV449ZKVa5DfNBecmD
jHcpjh9FYyM81VSHg5S7XHZXPJBVMe9J2JgXQ0Rvi8ZZf2/IARO3Xd93bc5hd4rmOkIYuSASOien
WisBf7J2F+l9yMF8oTAfHNHrHHGGq8MOMY5Qqs6D4SqApHUDlY1Uq803IPNGM46xOb3S60F9JIHd
5Wa7K+5vjcj8B+dbxei9SbE1FPb3yrD+3r14ESgmzR+UE93xaQC1u8q8D1neA4/xOmO/UHAqBo67
AmKcnMK4B0qIspFqlVY3AGysanRzTgJrppx2l8vvige7W7pmeTPAjGddG+r394L19751nJzCFeDp
srEPucjmZ+dK+IxFhjAbKVZpxYK1osO56MGDlLtcdlc8sFVn+HQABKdl735Cf+9bwtUQwOBB1g+G
iYfZSLVKFxuXyBwn5S6X3RUPbpWcJgkx1JS9+wn9vW8lZ82xB1+fiU4ZEOYNCqablDXqLlfXGuz1
M3kvRJ7vZKt5cqu51Ty51Ty51Ty51Ty51Ty51dxqntyqe5W+rZP3A3dhd4g6NrpkSqc7BibV/gjt
M4twDXRsjIyxYXMI9dUcn7Lk1VdfVd/exFSAA18nOXs/8GGrhoUF1KzDxOyVbAAvMKv34RNkSGdx
bGyxY+b/+s84xFKCefnoFoCUngEebT3LoppfjM265ZZb1Lc3Ma94IgbcItsUxlPWSWZWk/ty8fyM
BXgzzzN5lSkAaH+NDdTwx2jM1aC7iDCLrpE/0XLZ86kBNZd4mvuwiv5f/Awt2sb5yGrV9d3kA8b3
GfUN9Yus0YdvTzrn6ySbrZYAWEJYAEqs6tGjkDG8iBrjj8Mj1oh1N71g8xZ6dTLg/Hvvk1w75Ot1
3JexOUCoMNvFViQVFzJYnZubU9/44svmAyb6ptNCFWHM/VvvT9p+kdFqtE4y36DIqi+tHo6a/Gp6
X64AgNtuAwBBsawB3tnpf6e/6Ih+E8DCC9p1+AjaaABAFUdM/E/9Zcm1C8/HPw5UiMUF4GY8VoWY
96zXZfuIQLWQwSoA9S198WX3BqRAH8AN7TBadAv8L36/hp28lO1YbTDbKuaO1cgq/KFIJ1yXrwGr
rLLzrHX661PsRbfUbQKsTBfWu/HRNoAfs9Dl/I87KxZ7HWwCm8o1270Zr6vB6T8ddRkqqZmtmhdf
5qsJTmktOoVJQCw7hl3/09jJV7JZ/WAJKsUUq/rfgG4AwFNP8fV+j27nttvkV/1Qsi4egcwXY/zy
jxKssFqLVB7Edae+9gBQb17Hgzfz49v8d/AXiUKuUkLjV4FfbaBkasYDipUYhdj9h7T8QhHe2/82
0TrtzyqX2kjSyhYX7QHmXf+z6KfRzGS1UT4FlXtSra6ryevJ/bp0224ols96zxchU9c3bwrX7wSA
10llro7umXcA9TNd1Odi3Jf8E+THOLk1fMZpt53PoObqUtsA2kpryrFakVJPFivqHjijVSa1Ol2V
WolpZVKJkqwGHqI8SZmsfrADFXzRZJWvnyyDaoH166afgXuHEMY7wzfvhVUA6N2Mz1i4f0KIiadg
ndH4kY9b6HU1fh/aPXr8ceq1tcWwi965ZQDL57xilmM1+szJb9b023sPO9Hu9uqA36n4QDum7gLk
bipUgQvEtTKpBCTcqI6KMN4ns1ktPwqVapNb5Vqj62q1wPqB0626dv/m52mHLeiOBypyRHvqbUwt
LEyhPezEeRXAn22hGuMdeB+LtvpjHjqx+qdXZfXK6ul20rHK+2/DjxTFhIwKwLoiZEbJ2Nb+OFvn
VH3TtUYbzy35ScveVvCJbFZbUMGXs7yzKURWC0OsHzjdqn18a1rMzwvWDP2xBsZ7D7GVyclZnnzy
He94cnLZ0Xhh8vfwR1/U1s4+iSj880rLTYrelzeXsxyr0lpAFIyyNd1hXuS6XEeYepmvc6q+6c+B
VYLSKqVyTc9ls3ofVKxeyjrJrBeC9c2mWD0+3CQKAmJpPrNVJlisDlFveWJiuUfE+Gv4B804ryCW
CsXSmBfzjf3/biku1Y2k8pzZ8ABv4wwNFBGlwF4HTYFtDuFks1qDyvNp6yRzq6pvlm/e6ip7uzTs
7NFlTGKkTNmzIgKNBCIWbXg6oGA6bclrngJbG9gYZ2VUiNEVh96sCCmdwYQnMCpUmJtC4YB7IRz6
7kneC5Ent5ont5ont5ont5pbzZNbzZNbzZNbzZNbXZhaiIPcagtRii5ljQsYJy+4rnn3dlGkNzH4
KFomHIbz0liR9T8fKF+cmlqUnMcdA7qUKXt0xNqAbZgeWu3/wFfRz4+QKa2rLUOTAYoV0/K0tg1q
ceFu7SzMi58i4Ul2i6a9VUzYIWiimdnqm7/u8amv3XPna5LzHEFjck6C9P7kvZrRhICBhVZFNPYw
+nmYWNzSGH7lGjR6yrhW47OwJbfxLOm53/spZhX4w8AFcXTDcJh1pn7jDRAL3viNqY7RKv2TqQVe
5tYwOuX9z+ncsvYz/zOFww/PSs7iAk/0KKYbt/ajm1pCP0uZXgUgwHZdGxiSdW6gnxts5/r/9Ff+
wB+CA7ZpMLRwNq2IW+ywqeBDXzVY/SMQBfpbv/Z3WDPhYvHO5burxFK9e/nO4qJOS/BBf+7P/wWM
6WUgU6vo02WqfN3jCBu5d/Gix3jiusrec/Txbz7WUFzlhJTUlTbSO25W2xFtr2brSSTg+IkTx/tW
zZNKLQDbSiXWjLyOMK/zVXf7WdCOyVP18w/z1xZukXX/0m3/6JeuxvmreHq1FBXSy5dWn8ar2km1
dm4d9Ff/2l//G3FMnVrYx/LpIhFfl1iueofDGvfGCwA4x11BcJeJg4jNP4a2Q80XiwCOkZ41yDSI
tzPxjht6dyjcezdlsirIsmDbsKwhQdRRkzrxS1UUbvWVCL/C/wh6FOtd+jF5hlaE+JtHYbD6Q//q
f20w7lBZCtmaVXg2VFQmB7doVu85VhinHwr+7t/TrJ56w5GgIDFb91iueodanMvV7oQQ0DmqZaJy
m3HzSrizuE5E3y/5rLlnt/5YpusqOW+X8O1ONqtEw8MWYA0Py3vg96pJ7yUVy020ejnCl+NUHvtR
jp/gloj+/jceZvZcImr+w18z2f7W534GeELhJ4Cf+dy3iIhZnZtdKkvQjOPuk6slIvrU5zWrHiLw
yHF4cX78EZKBxpU9nbcFkahqvAG0ulPhPmoYpFbntyYCfl0VMqB4ehvARo+41e2fMViVp195Et75
RAbAzjwjTpLV7g7vUkL31H0GS/TP/8UvnY3zf2kdiYp5hvm/9csNIVYUXhGi8cu/ZbJKn4kah30v
Rmvv8UHf+jef+7cg4usVU6nI1ysulihlHWONl4hKOn8SmHrwg6rzV5NaCJqKsOuqlncB79LZUZkf
/uHwG8USnn5h29LqhNjNhPZw5zYsZTXtryysCCuilpTBLP37//AfrfPxG/f/dLF29SVPXk/4/E99
49efIC1P/Po3PmWy2mtDpjYTo3dhHfRf/ut/Q50MDaKLfL3iCJs5kZHXKpWazh+HHNgUV8bxuEGq
AinXVbZKZ+oZODz9WoC0mnheP4T/vjKydbatWf3ts/XoKl4/+9vah0tDrRZapFuC/6n/+TAukpbg
Q7WvQAJtvufT538R3yQt38Qvfp58j1ml5Vtl/ncQg2VRAP2f2de2JhRj6xIPyk+eNHN8iZxjkqdK
5fufd3Pv+x5YzRI4Gi/xmrzONs8vC9q8GTvnJ0avTE5eGZ04H38dXdsagWVhZOtaDAsxJ67cALAZ
kJ4f916GBNr8mRr7vIdMsx4ekXNCZPwlEgjTK02it2Dd41NL9o0416Sy96vsuiqDqgIpZ2yQECOO
MyLEEJJn0YqYUwsZx+MUi46pcXRjeHiDmnxIPpasxvg98BiMOrPFBOcT/c5tymrV5azf/+zVVd/y
wfN2o3HseY2Pc6nckp5MZ2z+G0M2K1tGzVNXHGeF9pM59ZiDd1YzvDG1QQnrDI9OlN9EvjzN+6vL
wiQ1Zf8XKHOE+o2hoP9bDhzQAAAAIAjbqGIC+pezh55hRi4VlKhdsUuh7scAAAAASUVORK5CYII=
{-# START_FILE BASE64 static/img/glyphicons-halflings.png #-}
iVBORw0KGgoAAAANSUhEUgAAAdUAAACfCAQAAAAFBIvCAAAAGXRFWHRTb2Z0d2FyZQBBZG9iZSBJ
bWFnZVJlYWR5ccllPAAAMaFJREFUeNrtfW1sXEW6pleytF7JurZEJHxuHHcn/qA7dn/Rjsc4jW0w
+ZhrPGbZONmAsw4TPMtoMySIDCASCAxiLG1u5KDMDaMg0pMRF7jXEr6rMPHeH0wgWWA2cycdPgYU
rFECAby/rh237p/9U/u+p7r6nG6fU/VWpzsxS71Hidv2c+rUqfM+VW+9x/VUVZUxY8aWnVl11rzF
7GPe+WEm96PCI0MscNiaxBIUuD5r2roMF5+2+pZVg0xXCg8tc8ZuxzNWnXG8635Omv6j72/WGPxj
6Mf4Sbt+TMUAGxWje//gLQnG+vFIOCVf6O+dTbLCo3f2Qr/isjZFV7LVLMSicIa8GYKsncVZAv4P
MiutKFmz67AC8ECg77Em4fNBuy+atgKkBo61M2tY44Fo4BvfjdgtGWGN76ofs9dBwAfU6Dw+UPiV
jCdcwaObSss7KPh9hiMAm1F6hJb/lICHOjTD/SVtP25mom50SyoYwK+y5mzLOUrJ2NoroUTe7kmn
/Vl1MVmRqKxaXpygKB5dWVlFrb5mQOydwB7i0J6ubFjh7npdh1XXdKUdEAmoj3W5Db4m4QE1LVCa
pO1XgH2D/kB08JF83SNM9ZhZf5I9+7Rz8J/I3IIfrMb5LHcjByu+UvGUKxQ/kcaLYdZ40f8JWOkw
+A4iEBtlYSmddP1HFw/dKtShd1YQrncW61ZeqsIAcmYleEIEKAhx1ry8ND6aFh/8V9VHtiPdBPGO
bFcRVTzQgcz40RO7WEpW0ba3k2z3i6zBvlL9xO4ka/1EVnLTSa+uo+mkNzrwWDyPcz4lWOAxAp2+
TrKORXoPGvm6d5aKpzt50u4573rAOfhP1CUXfpbjl36l4XWpysmXBCr6PbGqqsTnSRvReJFj4Xl9
rvYfHFko/qPrb9YYEpV1CsKxTiSrXhisap/+C+6uu/8CZVz1iWlY7fGdnKxd2eM7WS2lcof2ANfj
rBHRsoomvoE+uiF/pXpsCFnJYVZIVk7UsM85PYeLXYofPYf9H42YsMdtUq/MTd79Ho4bf2S7Gq9P
VRxDC6lKG1VpVBV9cvFXGr6oVycSFZ/auXWquCnKooTpFvcfy0YiWVX+I/D8UOPXvp+E5+om3JHt
0IXP6MxS5U/AqovYd3l62+ltAxkkq6q7T7LR3xT+cz8gICtekEZU28Hq3d9JkEXhcfclufMmmZus
gqh+5ww+7k3Vwcd9XbHh1JbiELt3Fu67QYbvmRs/Cg5by/r3TnRlZXhu7ijl5o6qlZ+rQrpkGp3P
TVTZFKpwyqWabnH/ce5T6T+a+NhiV5b7vOiQWG1XNvGNzngqewJWX+O7+PupIVbDas6n8HPju1ZM
XmrvkcJ/hQ1Ya89RaqlV9P+u0DacBdfrcx5rlPXMqW5+/Vv8cfLHuP4t/6ZgDdhPFR8DGRmRoMk6
R6Yc9MgU65TdN+KH32y1gyJruJn9x3+Q4+1zUvkZZYoyqq52HfJR1T3OUca8Ss9VrVhgoR1nngEa
UXl+EwnEj+5Lg7fIsNx/sEWwXdT+I/D8UOO75zqXdKad2WS2XFS9L3XHH/H3m9r4nePnO/7Ys/k6
qErLYy0lJ6agZeeN/wwccYGT1QoEPwJqvCIveWiGhaw0jqw4olppFhqa8b/C+dTSMfJ8SlX/p+91
8A8+or5fxP/NTuvM3TtoeHe/ThlVC9NKslFVNwNc6blq86mEHcyuYlSiOqOvmLPKAkLhPzbxCP6j
62+9f0qwwjHOiiWI80kKVVktH0mD79lpNHuEPZ9yx6Q3iKpAKUiIS+dKK4ZmEpg0z1gZ/jhD12TD
Pydq2A6DMfTF/CCSlRZO0fLXPJsLM9o5/J+S1UU8jHffrIaAVo2H93qXRX3g/V5fZeaqtAxwpeeq
H3Trtr4z+oo5qyzjqus/uvixZ5JszVn3T9bAuDz2jM54qngC1XyGupJhFtiO+apVZZeFqvBG9bLT
64cJ8zEW2juBk3sMRUbTMA9ggQX/xuNExVKRpvwrklXWFA5ZaUTl2d/RNOseP4pZYB18QoGHvnMy
yNx5aXCbSf9x47s+V9Vv/Q2nBFacueFU+fxH298aemcj+AollosRz0QwI9ygM56qmBNbdKZpA5nY
orobKAtV1yzEXc4xMjWQ2Xzu+E7FzK0BZnfYN3ezIOaa7cYL+L91Kw6+wooX2cJdqES1Yl3fwkum
IJzZeGJX6gvVmzcdfOOV0JL6h1jjlZuVAa78e1Xd1scYiWP5mRhHlc9/9PFYhwhrwqz+fBOLKP8A
aClJVcxhKRb/bHAgM5D5bBD67tR1UFX8XUSS8JcpqS8QN340V4kWuHQHNRnlvBhKfbH7Vr8H6fkK
WPUwq6eGeuYgy1ZNqcPGOz6+R9SZ1V7of6CvfPi4Z0Y6zuSjamFa6bv2XhUpNzRDI2ruGXdyLNC1
U/Vs9fxHH4912DsxkOnMds9tPgd/PNEpvw99qvKrPL3r8FZaC3Vl26BE558ratV5h5brrxqrSjZW
e2oL/bGSS62BPrSGWgP31eFR1ZYP7/23Jv5tWjqelgG+Me9VoU1C5X6i5fIfCh7GYRjtwIM65C/h
nJc6S/9XnldPHdKgJoWtn6q6WQa0qq4yZuwG+Y/xN2PGjBkzZsyYMWPGjBkzZsyYMWPGjBkzZsyY
MWPGjBkzZsyYseVnpcgqGjNm7EYTNd1MEGK0kaUITo7BMiNUZj1D6RBgIRmWfxAO/FpHr1Vl6qOH
h2WCxTJWwxWpzzycMW1rU6TJ5QMexTRpz5cqLpp7Tvw4WJlhBGp+Bo7p79qA4m5Bmngs/5fXJWZF
OsN86VmYRFb3agsKnuuswqLabGc2wig6q2t+jKX3TfZN4tc1P6Y0CV1XT7c+uvjor4tXpcgXo5da
H5QVaUf8fJhRy0f8ShZltOdLW1lj1bW5cG1qRVxmL77HjjgmvE9R/zPNIBmL4pz2/S4zGXS56nQy
J70tVuA43/nhhXCDWLVTsHLHWSNKIav78VHwuOp/IIMipCx1YtdARq2zGvoUS986vnXcXu35aXmp
qlsfXTwuQ3eviwCdg68rVx9cjSm/72K8qp0Ka69yLaEXBOWD7i5NogZ0pBfagNRNqJFxxsqEFfWP
wLL+09uwHqe3jaYjJJ1eWCSe0SKcjaeJvbvxVmCVVIo0mRsZbeHSfvd3JVC1cDG3mnyFKyZVeNRZ
BYmKOKvFKsJysjg6o+zmrAAX9OBrN1HQg9KAVKq66wPik8r6uPCT1iQBH4jbAtCO9c7Gmb8KgVM+
fqdTH/yu9bWEasxz4a06Nd5xLnewJl9aLgT0WD2Vqon8Ot6IYncG62CUwRrSIF/gCGtkgnsnosow
2zrYZMcO3HPU/iPwqxhxq40cvmkhMjI00/aV/G5xiVySOYQtkapLVRdU5HNTVb3sG3VWD28VlUA7
vFWus3rbPl76oT28l06y2/aVj6ru+nC8vD4Cb/WFUMG/T4XH2hcKkKBASfsT6vpA4Buj1ydHk5Bq
Nakbb68qVa4+Fe7kXqsqkWWbd4sS5D7Nq8qnh9fhq6ASUbCGlDUMzYSvyueGPCTnI541tkrS2bvx
qGrS9jZl7inw218N/e75+2RdsdMygrCWQjrAh6pe8igqsjo4SsrB0VkV1VPprIau8tLvS92Xk+gM
XVU0X8ZyaqQIe9z14TWS14fjYceRL+1585dWnQL/P5PsR790/+RHvwQRrA/U9YliQHhQVZ/kNwJP
M6d8qumNqgkP/0mw8lE1zh7dUfyzR3fECSoZKDuzd6IZZrcwKtdQ8FVVjzwQWaTGlIj/8bZ2hrK8
/mKhznTC9jV7MiHrLH2pir3s0qaWj5Q6KQe3zmoyT2uZzqoVE5InEAzWijBJLnFcKMQlb2pRH8sW
puLEltWH42E86rbr1I2LlGV43EFndIv7J6NbZDvXuNsHHvmrqvpgcshjZLvsG56mlmoIoIpQuUZV
3SSUF1VlSr1JNtlU/LPJJlp9qqruehS/3vUolXr3DHZmdah6zyC/m3sGfdu/353R5d2ebHiTzlX1
GloX7+isiscu11nlsp9izM7nFX8lu4aOEJeoD253wLdAkNfHqb+4Uzne1nzFunMl2j7LFl/1byOn
/J452FykRVV+/wUv3dqB93QSKHKdW71RtRSqWnUDmQP7T287sJ/L6B3bIU1yVbtd284wVNPqYwVw
RMWR1T8ALqz12mMbzupQde2xzeesGEaAsoCZ+7I7D5y8HqqKTF+5qaqrs4r5U97TYn24Ui+MSl/L
5w4rGd/UaKUyJBf1YbWjaZALrVXVx6m/uFM5Pr+N0IR9NxOqNnLKB6m1enX53u354H7lm700rf1v
xKgKMUqcrYAU0Qq1jF6xzJjjwH6jGB6jaR4AQ964gTXA/zUUPFDv2r6dcu8vxEe+Hv9Z62vgq7WU
lzWibUsKgIsTMuWnqp7OqjUswt/eP/ExJx8CD9Nqw5NRlPrAcBdU67668PbGCiq8837RST9I1ded
8qspOrT6urVcqfn5++j4So+qOjPn0bQXVUcVbylY8MQuzMOLvLHqKgJ/aotc974YP33f44mOxUd+
QXtZI8ZXERIvM6rq6ay2vyHKvOOP+D3f70P2ZwTFdQkq1P71dV/18N6uK6tRZeuDNcJ3rzr4ys9V
6Ybqy0upij9VnFeLGzFqXMfGUzUvHTyrAXo3UF7W8PeqPBMsU6QUvxVqiFVVOPzcEKrq6Kx2LIoy
h1/G74dfFt/7adrru4qu7qseXp+qpdYHE1IDGTUeXnak9k5sPkfXuV36Z4X+9Xf2vHMO+W4LelR1
Tz2KPy8Pk9Pb/XrGsmM+2v4Gzp8YYrYjN9a7Y2eS5mu//t6bVJ1VlwJqkPepKi1UPRVd3fro43V1
fa+jPt2o2k7QrQ3Z+A4dnVsNXeKUBzolL1+bDK7rU/d6XTZELtRtroeDrMTsRDdVxowZM2bMmDFj
xowZM2bMmDFjxowZM2bMmDFjxowZM2bMmDFjxowZM2bMmDFjBeb6o+y0Pt5KEzRo61BQha4rq6dB
mzsnnUdfrlhLodptTKuFmDVJLn0sd0ZGdafebSRTli2lRY0tO8OVCkMzSS0VYAfPQuvfUp3VeDG+
iNKTVLFK3ZU7aM6KnDijC0TqWfiqSo2CGxdvO7TnwP7e2RBZwpo1jB9Nss3n5Eu3rMmwTX+dtTua
qr4lULqUjgBkOUvuaJT4gG7ntEQYW3qvxWdWaOgsrn8SpSdDAxm6CnAhXk3WKLNXSzKqWKU+VVGC
xCXi9rBegxCbcDgJy73WXiOQzpbYhBUUKy5Al9TxZ+pD6nolyZQaBC1QcgsKloK4S79Y/4gKvIWC
pm7TwRa3Pr271z2L1ZTe0ajwxWVTFnZSl9cVo5JMl3qq8r3WNSU5VVFTIKKhAlyMV5HVq9nKS9X2
J9xomXApF8O0Ckq3lHKYaKHfDZ7unU0wykYMos4oZh1fpFI18QcvyS8vpwJH7+QrGPOqi/X+o7EO
tngJHDEi6L/+s6hlU/D6CzWFkAqt1jpU9fZmf77wPSuKNxTJURXJp6cCXIyXk7WyVEWioaCnc/zg
vKzvcsbf3lmuczj6G5UcJoZr7ez5+7b/raojcFPVijWdBE3gs1SqYquqRNyKW05noTVR0lxzxxrt
ADVQQkBb8QA4yaiRVjGqFKqipK+sJvamNFdzeR5bmse+Cp930lWAvfEyslaWqrbu7DcFwcI3lIBq
78TU0NTQ3olkXn5ZZrftQ6mrX4LAaDthLszH6iaGTa4KaZ0gHqcWFMJVlqq6Gha6AapXcHpzA2A+
9y/WIqTUJ0/ySZ324drbsueLHBt5BYmKm4AEFqw6G89CemT1w/uTtfJUjRf0n3HCo++dPdC5iq1i
BzqFgrAi/L26+W2rL74B0S0vUNwd91fBRFHzx7TNkOL/Ncnu/h83n6q6Ghb6qhf6AW3lAmD0F0j9
pR0lQZ3a81a10iHJSLzUm9e/pRIXtfdACCJRo7YAeuPFHN6LfOvfklTWB7/+Le+zKk9V/V66+9Km
Nvy6qa37EiHI7otDd4QCa9F8aKImBUhkNY5MRVngeRKRjifZxqM3n6olvSrTPEMnQK1sAIyEG5li
IXcATLtXVxooBCX40ttDEN/mjzQUr4MXg4Hm+6O5M1y7+hSTD4SzpPvQeOGt9Pq3vM8qjaq9s6e3
UUa80qgahTzx6W2nt4UfjhK6g9DfgxxnP9+JzB7D+6ikuB8SXrEPKUSKfYZ731WOqtaYHXyNUQit
m8/VPUMnQK18AIwZdXcATLvXglGwRa89kT/+eCvWeKUNIr7b/pdn/d3kUxHVC+9P1NKoauvk14gN
LtTBZnFqW/3om1ngo8BHzaT9Q8Ps4eeEk20+B3vo/D0prRSwxlqvJdmdv6dQCbuMB/oqR9Xm3F3r
B8CVyAAvlwC4OANMFwHUzQB3gbokPzh//PFNuSlcxK+rEeSjELUYLyOqN1WHZmQ3Jza0EBtcEGgx
7wp2AkmSGGaURUlymJjHPZB/vTH4d/bcXPJXS9YenlZaBcRIEBNL/Jxn/lqJg82hnSQGbaTkeLeL
ydIgJQWcyw1/3Rlgan3UVHVUHIGB9lFKWq/oKkg+KlHdeGtMRlS/EMAf7955hpNV1RTFfwKhLYYp
kcO0DmK+rmlBqNnzfHFgwb9GrQUbJ8GfH9QrCZjh5zReUbZ5C7R4i85IKZIe7iPEdF6tlT9AXV4Z
YEHVUupTiqpxGahqZ55COsVyPGjMhsoZUhVuEYUC1cp61BaU31DOpsspEafyWxUrlW4L6tJN2VgB
/kghh6a0uX8w5o3nSQ/3gYmUcgacyw2v73NLz6HVpxRV41Iy8MtUCVj9ZwDGtNqzRf0TY8aMGTNm
zJgxY8aMGTNmzJgxY8aMGTNmzJgxY8aMGTNmzJgxY8ZujsFqucCyqMe0eRbGjEmI2nhR/HG6FDdm
TYPuyzRFFsxGn7Euw/qXMzQ8LucGaZThkjub4WXQkmmasrIxYyU5+brm7ksJ6coR7obNoDIUgX/N
So1DlOxuxtV32QT8D/gMRcKk+WOQRvmKgrSGoRNgjuA1djarJcu/XfgzuKpUq/x57MRgjX6dmqhh
orKyW1sW20ofqz5LDw/327dsPDLvLTS/WYrnS+JoZ1GwrvZM08R4nFand95Qtux+0ckDH00N9c6m
vpCPkbgwbCAzmsaF1mHFiklUiBnIgGh3SqwTbbyorOjBqK2ZFHhJTaTVuaW4fJ2rVTd4y4ZTvbN+
Mp0C35UdP4prB1cxaw+l/L0TQzNd2eM7Wa2VblPeAZe60pFBF+0fZbpYyll6+DgsJ4J4iTwNEms3
SxV4kZ2D3sJd1vkks6V4viSOdhYF67RnmFQjd/uTO2/wH8n98sJACwjIeqFfVtDa923hbnyiHUjW
te/LaB3l2FpnLV5UQW6rry2HDCmD4JavQB40nVsq1Dl4S+PFxovn1sGysmoFPsUaISwHAaxWdMs6
Zfmw1A+XwnESbjglb2gUssrpU4QoMuhcUYfLXulhaWfp4fEa7bhGl7gzgLN2s1RVRBlWuGySUcjq
haesV6Vj3e0ZJZJV4OWqZY5xqTSf0p3Cui/tvlW+EA2lJIZf5p9RFSHC5LQ+vLX4EcnVdNd86SDX
LMibAkc8FnTfQ/elwVvUeFRYbWZ87AO3PKnET9qhr01U2QJ8KHc6zNzjX1jaFQik0/5qN3ewtLN0
8bzlEyC7CkFY382mqnDZJIkaXnhaq1Kx7vakkdXB62qseJTuFObWYPAzFD0R4l6xD/Ecf2xssSvL
l2W7H1HiG9k4HGc4VguHkSv+OU3L7wHrL6OqwAeejwCWb+gxNHNunWIUmwyhHut0WNncjRfbc4r9
yfzXdkXAbCtAXIySZbgcLOUst2PRruI8pyiGwmn1SFZZqnKXpVHDC08VN6Nh3e1JqZE+USVk1SNq
VdWGs3w7DEiv2FtiyMLB7rnOrMcjysrG4aEZHKvzAixX6XM3TlQZMQR+3dTpbRAmx7uyeycgXK2W
45++twuSYu1CS0oSvm845SW3IQ+YhYAklapRl5uoz2o6qYcvplJYKSRTeaoW3rN/DOSNp+sQUrCF
RFVnX0T7g+i7psZKz1zR/eoStapq306uqNaWU1U7frc/tvdPibxomHNz/Rdk4fXGo32TDjbOKFQN
PBbN1V+eNMnv3BJiNfj11BbWIKNeTguq9vhOjCU4UWVqRrw3dG/npO5NedvTqepgKWedW6eHL6bS
0MzH99x8qrrvwT8G8sbTqUrB5uV13Eenuv3jTO/lnZWOF94vfz2jQ1TcoGhkymlmSLrU+GPHnoH5
5tniRzT2jCy87vjz4fWOsmCSRNWew3sneP2jykdfcC81+OKJQG0gK9ckalbUSKi8ijPVYQ8ihZAq
xakcLOUsoftIv0rSta8PyLiFVF5ReaqibyZJw4kXnkpVGlZ3Vx+n/cNM52VNuPh+A4/x1zN0oqK9
kxCPHLK7QanjNvTO2sFyzN13yaTKNpyNstW/7b8g0PKdXDBIwEwlTKoaWDXqkmOoocbnk0CgSEjD
gwRai7p8Tlbcyys3V02rwx57/K2mqB4XY2ln6eKF4Cq8zuqkyLhVmqrcN2nDiReeGqvQsXqKiPpk
9SAqzAw/Fa9ndOTHWPWR7Tju9cydT6mwWM0I7rA67/RdMvzJjV3ZcF6wuCsr8sc+wfgTuEGU6NtW
2ptF7Xvi5uELkwK0REIuyCaoHi/F0s7Sw+M1Np+DqUHjcnhZI9yVFvd54Sn0o2NLURR0yKrzsqbg
fq0AzvC2/63q9YzHxSEg7Jk7tkN9HsqD7p0YyHRme+Y2n4MkTqf8HFZzagv+uQF3dXCYWil6xYH9
fPotlHcP7Gcrbh7eTVZqxi8fZCtVj72wlLMEyn7Nr8Tb6sUdsmmNl/M6X2l4mqMLd7XqaHGfg3I+
qemngy3NeKvrvKwput/dt9p50MZSBD0hIOyW08gdBsOsOgX4DopKL2zMFMpJa4fUDsNWQLlu5d0V
NxfvNDc14+c4q1r12AtL0UrmKP6cVXiaevGNMXedKV7qoFyf1KOeBvZ6yKrzsqaoY4IGqKkyZszY
jeh2qiuHNmbMmDFjxowZM2bMmDFjxowZM2bMmDFjxowZM2bMmDFjxowZM2bMmLEym65O7/cNb59D
lp1cnvWvuA8FoEYxnda02A2oVVr3SlbMmlyuNM3p9MYZTaf3+4YXZ3EZMXp7JrOdWZ36VAp/oyzw
EUhYfkStC3XBXMGdZ/T3fXj+Pr0rWbHAAuhkTt7Mrobvb5ETbA24WrRYK0al01sani9qw/8rU34y
L2pW7vK5OPNKG7tyXq3b7+ges9SJXQMZSn1Kxe+doOkq2488o+0yGtSwJqNK3aPrpWoUBU+19k1A
4tGvBCMw4BPgpU/fW4n6U4nK97ewh4ZY00JeBg11evllhR6QXKfXwbudXYXvnf1kE67f/GQTLrCl
ly+EoNR4WEUKomYndtHrT7tftKaTHYtIiiR76CUQO5VrGOd0jzfegd9tvIPFkXzy+gidZHthoQbe
irVeo9QfhcebFqLajkWnhjUcyoum0UJyXVe3+qw9qF+5mtHDU0G8E7uGZij4MAggIB6F2W8eVdc1
xxdxfwssH+sfX1zXbP8CdXqdy6p1eh28+5Dju7K49g7Xb+KaPRxZaeX3zn58D6eICg8SMCusPVaM
1fK19pTyhQCoSpfYqguz3S+yBpvejQ+91HpN1tBc9xh6QxTlTMP/scNbVfUROhd8awUqXjgitpBc
V9maXA0uqO9YVGpYgTULzlNrvUYZi3VcHZQx54MgrZ6XcSeO9m2/EsSjL/EHUb+dlFXYlaMqq0HJ
vUROWteuP1+oGlsUI4wNy400/jq9Dl4canzCFRY1nUwQykf5rYEMEnx8AKmtwsO4wkJXezZbdVFG
qb+4A7UuMYq0JHFGyA7tObTHAodJSGcpXPeY1Q7N4J41sOofPkPDfyPHw3X2WAHcWqHpJBGfIyo8
yAYZHgPfkKtzUsl2uTFUagQ+Sri6bRgRPiqnq+PGI4miKK7pCsnpW0amaMRz16n1NfUc1SpqUcq8
liaahugm1/0mUOqI47vniptMrtNbGt5RlOGqMSr81BCrhyCvmjukGp+0FY9YfdNJlc6wwFsFUYQ/
3nEQqFG9Wg1I6B7z++T33ZmV1Qfx1p5WtopFc0KSBLxD1Fo5vulKVEu2ywurogaX23R1gZ2KGXCh
q8u3uuoLL6lP7+yxHbQsLmuhEFVkiXODT0hNZx0RND0tKe8r2L/o/ZNoMsF/uU6vg3f3L3J8V9ZR
bj23DkdJVfkBO5OYJ6oSjweEaiys1Bl28O5m8cez/s8G7Zlwv2WPrKj6JBP14LrHVgxHVBxZ8XNC
Wh/ET4cxcOdqOgT8mJuocvyxHY4ibqlUVVNDZ5ycGnILx3Zlp4akQezbmLEYmcKYRugSQyvVliOL
W0qWuPJUZf0ndjkt1DMHCUTubajTu9R1/XV6Hbz7kOMTtpg/zt0wu5UglG/L//cJotLq4w5o1XgR
8Kt1iVn10AwmkxC37qcdi7tflDU01z1mtdDAMDeH/2vXnFXVB/Awh7ddEEQ61PjmguSHHM9qsWR3
0C8XHiue2lCooUdVVvPkU47nPPmUXDKoHXWmu2F0tGMa1V4IelncUrLEhW1D1CvU0je0Arz+vCOL
4wYsfPqBOr3FaRaZTq+Dd/e6KnwUXnPg3G3lfJRYPu6WktCqj1793TGBXJcYI4HB0825lAkmmKSP
Jad7LDLAuFWIqj6ID92OLghjMAGPNYF62COqCm/rZ4X2TuCj108rqalRyuyTrRCS7yCCrhCVA6IG
8xHFLM7My5fFLSVLXPm00u5bU19g/XmKqyub+mL3rblfOYrrNJ3e0vAio1Wp8iuH586OYXCSfbJJ
rbjo6B5b800sQqqPLt5OdBHxnODHd6oFSJcE2wRqlOa8rIUH/KxFiQy675z6EoWeTNLNEt+ADDBE
WCipa4/atae2uJQLhU5vF1Wn93uGF2dxdXoKUuged2vVp1J4JxDWdRpa4Fua8x7Z3jMnn6V63Xl5
srjXkyWuPFWFjmhOW7mm6K71dHq/f3gx4yBjl2P9q/VdRgvdr9VCqCJdAWFbSha3mKz6RNW9W2PG
jBkzZsyYMWPGjBkzZsyYMWPGjBkzZsyYMWPGjBkzZsyYMWPGjBkzVgaDZXN7TCsYM1ZICw1dWVC6
QQmPPvtzn72m/6DGlfrg/DNqWUZc2dpzuOL3PW0xqhwm1PqMVtkZlcJBHsm8P2tcK13GNnkOD+/v
vpO+HbsxisPqZ3TdT0lXFzf2Ye9sfDEIq+ytySDoqfXOxj4kXWUMnTfI2tidv1evSQi8FGU/3qbR
AUwjleD/Ph18x/+98wrtj9KtsQi0Dl3a0gpwsU01Ta0CVY1kSfqyoDYx7f3UoPtlHse8f1m9R/Dw
/u67aO1PoG6H1DPn1a1SOl4QFddrXydZdXVxI+zh53D1IwoQ4kq/h5+LqB0y1nilmfHrbD7X/09q
qq4F2cz1D9hjWZ2y6aaDrJ0hldqhK/BzWi/87eze1wtEkX3P4TKeoAZBHINZDW2ZlK4AiHASrmMP
I8Y8J3i7z1NLeJafYOWmKldbLGV8kY824rdC/0gp47aka2qVyNlwmbtEvlUoMnF6eIeoOenV0skq
dHFhmS8s6hEKDBIdWlu/rwkwzz797NOop9acFxXzf4yBhXhOKWbvxIP7w0Bx1aiHzdH+RlXVnb+X
dxwYKLcXuGE7y4scE/APPtJ8VIYXY3wC1HcHMqDG9xK1ZWlUXSrmIV9clVcFBBkPR3sKjw2n6F2B
rF7Q2wWdBd2F38laNczU7bh0fJGPNs5vWUjIzsjr339h6b0Ov6zb/v5PQL897auEuMQLbXleYWvk
vxO6uPFF/C6+qNLFdfSL7nrgrgccXSPZpbmgaFd2/Cjr7jrULJUd4zYeyfVBk+vfiUrnwo3vRmGc
FuLeXAsI4oJ3qfhX1/SmZXg+dqE85+s/fP2HttQmaV8WvnGGeusMz/CUyV0LZbJSX8Q3CKkRfCYg
Yxoqj2sV1oA0ZtTxyCxKIKtVl/jcGV/EaJP4XDEWQaSE7u7oGvmVv/m1pfe6dVy3/S2JTFzPnF7n
6n4S1FC5aHLDySp0cWEwr4NmVOriOg/fTVX5xTsWcdQ+tWV0i3W5TdnPWcPWQRE+hhiOgOGr/iku
FCz5oDvJpu9DAtpiHXfbakUHKfjUV7DivsUfzw2FxkbTq0D+czSNomUUojZe5LVROW9JfTTIeDz7
k9Uu1UI/opZC1cLfq+sjiJokkRXlSHjsBi54OSyVzGEhrlIIVOhwZxRkNbr/iaX3+nhCt/1lio6P
/AKyLkw3A0ClKu+eChVBc2R1dHQDjwUeU+viVlVh4IsHUlV8lo9JCXgYR7YH34MkVK78w+v98a2f
rJvCG+udFSNfnPlJRvdNwoz2X1j1QGb1b/fZwlGwSUTN+n9Jsr5JP3z3JY6/96Uk23Icf+qPFwml
nrkZe5yfifTMRdTbTsS43Bt33pXzsnEYHXHpP9UD7eniRJ3YvX2tfQdvlS9g06OqQ1SxaQmdrPE8
Uf1Se1x5WcfpxweK7xRGwZryURVKa2j7yvuc7a9eP1VzOtlFh/18HV3c1vxWA/IAFSlafEjdanNX
9uHnAguRfOlIJ3981O5vkYL78j1kfIPfvGoggyPi+VTn/w7aJZ9P4cgJVwj64SGgTiMex3fMMVtp
f7xIKL3wU1a9+dzmc6z6hZ/aWz3UyYiKgakY4zefs+eVMf8HyLO+hf9UXUEgR9Tmj5vssv0zwJWl
qkNUGNe7+WxSvd2VQ1Y5Uf0cXFYj3Jug8E4H3tOPavzLhzG1L+5zjmwAolKVz8kLJV5zMZOujm5V
1WrGD6So+Cy9eH3/hWaXtH9X9nxKdUvYGHf+nq1wlO390OdTvbNtLPA8nII3Fg881gaP3/8KiIcE
yLuv/xCdhdVbB8NSPCaUgKJw/Qf3P7gf7wbJJ9vvLLDQmQWJ745czTsO7O/MBhbKNapiSCTkM8cj
uBFRkzQDXOy44hn4X4HvpwcZ1z7IL6d5d+NPug2nckQNOakf7wSXF1lVRF3q4JgJzonD+qSiQHPK
5ehd2cG/KydVYUx92/sMaIOacsxVsRXd3+cnN7o6urpzVXxrGylI+oBAp/ThiPFo306+cR2eI3/o
m8+1wTiM73mty63gWLLHz8WxI/a2E3f92Qq0MSGV7Z2JxhdSJzfi52bIdePXkxu7sjCK+b6/3XAW
pCFXiLrDllcrTm3ZcLZco6qgmi2HaW9EJM8Ao+PyZ/rZoMuFJZ0l77zDkPhtyu1WgF2UzLGcmXLh
dyqyylrefb/5eZsrE0y7Ck6+5G/ndalqBdp9znh0h/SVk6KDKWxTn+90dXH1qNp4sfvS6W2gTgd5
S8xVqgWgT25EYoNoZn3ra7w+zjYa3g+ddcBmVO8l/pD4w8B7h/YUpiA88ZCuuAeS+tsObWoDvKRG
zR9jwm1VvhvDr6vsCKH5Y9/yO7B3FYrtOJ6CQGRHuUZVQbX8Jo+pgiDJ5xrq0cs9bvBx1TVdaVC8
iAj5fad6Duo6uWvivLaR3S28xMqTuwnOmmwqJ1Wbj3rjYXirV4W11A5G1mRaurh6VO2+BE5Sk3Mr
kogjq/n4HiB3A87AemdpOrewTUIHhMBx+L+edI36TdAN/GwjkKhe1idHmd+jjCpe2nTbe42c2NU9
p3JF/bnqUpO6bp0OUfkkYWRKbMQwMiWfrlTail6KhNTdATzTfmenP9ZP82YqVdde88Y//Jw6rL1O
ooqelK4rm2+2W+BQvlXSc5J851GTu1InXedW8xotTClIDZ1Lv+SQng1tWcvVbrVcsb80fVmp61bT
RL0LzmjJzfhS8Km66jtnogXVLan7JxCFM2HXoeZNqAxErWijfQcftDFjxowZM2bMmDFjxowZM2bM
mDFjxowZM2bMmDFjxowZM2bMmDFjxoz9/2u4KsiaNO1gTOYkgWLZCarynNZV6uyy6zRcFwRkdJzX
1iee/64+hRBIyIR81S6W3CtZKy+HR53neZrO8zLFT0NXdhn+H9PyuTN2Gx0sqydraWHlz8rYyAyt
9KVXs7+JjBQLTzbfr0X0PUh2BQokTLBsuXhJvoED6LqNFxsvhph9BYoOXl3o2vjRBNN4jJlcMxzU
6Azmya41r+cgsAakBv9R0VQdJkfnOUHUeV6O+Lav+v9p5JV9T9zzWzXescZ3caU0LHMMSkrX1kku
bXlF1F7rEyWIzRaWJ1YI8UJ+vWSB16+Jzg594yoW/mr3rSqHCX6ZyHUDwY9U5a5rhvWhGVxmhkvQ
rMwqtq5ZXZvA853ZX3YnSRLZ1suo5rrhFOt/9umRqTbSWAaaCJdv/+cnn2omdQbN7Mmnbv9nGAX6
6FQFXZ1v7QXyhNqM/sY5lA6rqfNcKr53VkjTlr98EMwJxT6M/jryNUUQRvgnSgQNv4nLHP3JnWDu
tsQDqSHr8kGmr5jYw+quIMkKxNnnZX7Ax187qszwETXn17HPiqka+4zguOmVi21fJv5P97/GGatW
adrF3es8FX0iq+mdjbrwsGhXOdZYsTb20EsYH1DGow1HhSLrxq2jP7nzL8H3lOVPr17Y9wTraH9D
pkjh2NBM+xusY98TqxesacIIzFAYpapq3+P/KX37+9BRnVHVpo2JI3RNHqcInWe+sDn/DMbUeEd3
l4Lvyh7ZfmQ7X+VKK98RCFLhu7K4PPz1Hx7rO7YDZQeijBLbDN7CNS9RAXOlLzW6sk5b8gPJIRO0
YSuETolQz2Ir/NG6kulJxn20+9LgLYO3dF/icZMYVT2WTUvcyp7ZBlnH3A/+NW5vnuEqysfa7naX
3na3Yo7KintduOKkfJQMfglaBY0YH6h7Lej/j4j6vhK464GHXoj9m/9GVnZpz7UzkJlZYY3ZAtL8
mPSrPR42boyt+GRTO5wtn820XjuwH3XqqqpeDf588L89+vNfyHcrsPoii474yuBpf90mNKHzbJMj
tHeCk2nt+3J8VxaW9IecM1X4JNv9IkoH7H6RiudPQF1+B3QYG87iUkpWs6lNSL93EDrMppO87NVA
P/8F/j7rT6XL6T/odmRyurIfdFOnKiTtJgh+MT6J2hPAqB2r5NbdWn1eBfkFbs1MKPTGXcJmKqom
niroUZ6SYd9JFMrH8NDqnYR8lIwz1Cqwl4v3T42i6j+Nqqz655HB/3L/P7Yq8bazNIhHeXpb5Gsv
dORrl4JRA5bPz5a1z/ZXQ79DEtlLumsv3fp4p7w113z55FPOKmAWks/Puc6zmFGxBtzCBOKmRRm+
dxaUmxqceZIKbwuR2EurWQMfcVT4Yqr64xPfJNkPzvPPLS9QdKpzHVpO7ptLzhzbUb65Kj6nid2i
7Ind5VWZQLvQjyJKUTuixM/CuSa8CopMeBfSOytU4wsvK7/02k/d6LWfysMWPui7DwwGKFSym/4/
xLdEXk4qqSfCcPbvt/aN/iRJpLb1V9aQ9RfUVxp+0ws9/OZKfNB/AdRfifNVVGXBxDfWsFARYP8O
O0NZamvgPRzfc99VW6vlbd+ZLbz6xjuwfTuzMnz3pY13FLaAHG+rHjEeg3CRMBUegsZ+PobwMNsf
3/VtErf1CkBK73LHn/Nj2bc0og7NnNgF4j9xf8UO91zVGVVV6UlWPzKF5Y9MqQSCHC/GK9Co6oS+
PAwWvdyHXlT129sNpT90qWodXBLQSnKjuAPc0oDcf6eYQirBmLP+jj1r/238qAy//ljvLG59Yb/e
Aams1ZK5SWH5oWTscNe39uNs8Wwfe1zv+jZ2OJSkUrWq6oWfuretstKymRLkuX9mpTG5Bd1GfNWP
wjvkZfM9XETC3xoLLESlOs+Ij6Jy8Zh4UZBU4peOkip8e262iVMKOX7gPfx905W+yUd+ESVq+zpE
halqrTzT4Z6rOqOqak8ljP7wCu8kVDghav/s09t2bdvlfCdPpInQl4fBwrninrF6XHZzSXZg/8iU
E6jKqGqNtS2hXpskLYDOXqyg6EcMj1GvoXvbbZ+lvmCN0lT7miPbY4vWnq3juJ2ffG7iLt+qTo4k
3vceTwvH1sT7yRGrmkpVVr/h7Mq8m3QsHt/pj9394mrGZ7Yt94X++23vrYHwTla2o/MMhJ0Wesz+
Os8cn8CXKNPOmSp8MVXVeJA9j1mx1msq/IP7+XSrDc4YTbP+zwb3TsjlTt1EVc9oS5mr8iDYnlgo
5YiEUnbxIX+xI0JfHgaXHKtjv3jvj4BSnae3jR/FuYmMqm+2jR9FNURnGj6QGT/6ZpukqQNYUYeo
UenLlHxAiyLT1aFNkZej7Mh2ZUPXPvTSbdceTyRIGePeI11ZlLUMrkk93MGOKV/AHOvrYKmHg2v4
CKmmKgqSOmHYfz4hE1iz58shm6pX1l7d9BqGd9KSG5y2bCfoPDv4dndnScDTdKQFHl/bBT9KaJSf
YIOPI0U6ZmR4PaKWNld1PIOG0tIZ9swA29OL4mQyphFkaRm+1xafy4KMYyNoHMKsYzTt3/sABtQQ
Pxs8tOfQHki6pOC7RllvtPtWcL9O8Z4OO4Tdt0pcEfvAIPa2ic//Gj6EYAsoiojpdLgze9s+4qaK
weM7OxZxhrpGsYmHeN00kFljqwfjCIm1U78kd78uoL2FhZdk3dBhKmujq/N8o/BRFtUsv+0rePGS
uf1zGV6PqEvfq9LmqvwZUF7c6e5ugE/WrgNMNW2tSdt3bD8tLsqy09vS90o4HwsWp0bUAcPqhdUL
FP1CLi06MoUBwMiU3SHQzurMBS9ByiNi1dtfbSXMScQonA+U4iR8vFBaW6/3paAxvUese17nGSMa
ta7y8sRvPtcz1/Vt6HcPPyfHY3iso7db/F6VOleVay+XHmAnPf+w0H7Wpcbq+gZX0igV9WdRj7aq
YmaPdjdVjnrJ6E3+M7WRqcYr2I2RS+c6zxjRNHxH8R0QQxB0qvkEQcsrS/T/yqj6FntAqcrQxpYL
sVsw+DXt8P2x/wdFm3wBeW40TQAAAABJRU5ErkJggg==
{-# START_FILE templates/default-layout-wrapper.hamlet #-}
$newline never
\
\
\
\
\
#{pageTitle pc}
^{pageHead pc}
\
\
\
\
\
\