diff --git a/.stylish-haskell.yaml b/.stylish-haskell.yaml index da39207161df983304d861d679111d46a9190eb6..bc1a4056f53875c1f03503f034e87db0a7ab0803 100644 --- a/.stylish-haskell.yaml +++ b/.stylish-haskell.yaml @@ -31,7 +31,7 @@ steps: # - none: Do not perform any alignment. # # Default: global. - align: global + align: group # Folowing options affect only import list alignment. # diff --git a/app/server.hs b/app/server.hs index ee457166c7f94f66c1767175a99bae2d5089d3ff..ac62d252dffd9fdc2d77f555e87be1f5c79386c6 100644 --- a/app/server.hs +++ b/app/server.hs @@ -1,40 +1,49 @@ {-# LANGUAGE OverloadedStrings #-} -import Control.Lens -import Data.Monoid ((<>)) -import Data.Maybe (fromMaybe) +import Data.Maybe (fromMaybe) +import Data.Monoid ((<>)) import System.Environment (lookupEnv) -import Hakyll.Serve.Main (TLSConfiguration(..), Stage(..), - defaultServeConfiguration, port, stage, middleware, stagingTransform, - tlsConfiguration, tlsPort, prodTransform, path, serve) -import Hakyll.Serve.Middleware (Directive(..), (<#>), gzipMiddleware, - domainMiddleware, securityHeadersMiddleware, stsHeadersMiddleware, - cspHeadersMiddleware, deindexifyMiddleware, forceSSLMiddleware, - loggerMiddleware) -import Hakyll.Serve.Listeners (TLSSettings, tlsSettingsChain) + +import Control.Lens +import Data.Default (def) +import Network.Wai.Serve.Listeners (TLSSettings, tlsSettingsChain) +import Network.Wai.Serve.Main (serve) +import Network.Wai.Serve.Middleware (cspHeadersMiddleware, + deindexifyMiddleware, domainMiddleware, + forceSSLMiddleware, gzipMiddleware, + loggerMiddleware, + securityHeadersMiddleware, + stsHeadersMiddleware, (<#>)) +import Network.Wai.Serve.Types (Directive (..), Stage (..), + TLSConfiguration (..), scDevTransform, + scMiddleware, scPath, scPort, + scProdTransform, scStage, + scStagingTransform, scTlsConfiguration, + tlsPort, tlsSettings) directives :: [Directive] -directives - = [ DefaultSrc ["'self'"] - , ScriptSrc [ - "'self'", "'unsafe-inline'", "https://use.typekit.net", - "https://cdn.mathkax.org", "https://connect.facebook.net", - "https://*.twitter.com", "https://cdn.syndication.twimg.com", - "https://gist.github.com" - ] - , ImgSrc ["'self'", "https:", "data:", "platform.twitter.com"] - , FontSrc [ - "'self'", "data:", "https://use.typekit.net", "https://cdn.mathjax.org" - ] - , StyleSrc [ - "'self'", "'unsafe-inline'", "https://use.typekit.net", - "platform.twitter.com", "https://assets-cdn.github.com" - ] - , FrameSrc [ - "https://www.youtube.com", "https://www.slideshare.net", - "staticxx.facebook.com", "www.facebook.com" - ] +directives = + [ DefaultSrc ["'self'"] + , ScriptSrc [ + "'self'", "'unsafe-inline'", "https://use.typekit.net", + "https://cdn.mathkax.org", "https://connect.facebook.net", + "https://*.twitter.com", "https://cdn.syndication.twimg.com", + "https://gist.github.com" + ] + , ImgSrc ["'self'", "https:", "data:", "platform.twitter.com"] + , FontSrc [ + "'self'", "data:", "https://use.typekit.net", + "https://cdn.mathjax.org", "https://fonts.typekit.net" ] + , StyleSrc [ + "'self'", "'unsafe-inline'", "https://use.typekit.net", + "platform.twitter.com", "https://assets-cdn.github.com" + ] + , FrameSrc [ + "https://www.youtube.com", "https://www.slideshare.net", + "staticxx.facebook.com", "www.facebook.com" + ] + ] getTLSSettings :: IO TLSSettings getTLSSettings = do @@ -43,9 +52,9 @@ getTLSSettings = do keyPath <- lookupEnv "BLOG_TLS_KEY" return $ tlsSettingsChain - (fromMaybe "cert.pem" certPath) - [fromMaybe "fullchain.pem" chainPath] - (fromMaybe "privkey.pem" keyPath) + (fromMaybe "cert.pem" certPath) + [fromMaybe "fullchain.pem" chainPath] + (fromMaybe "privkey.pem" keyPath) -- | The entry point of the server application. main :: IO () @@ -53,41 +62,40 @@ main = do rawStage <- lookupEnv "BLOG_STAGE" rawPath <- lookupEnv "BLOG_PATH" - tlsSettings <- getTLSSettings + tlsSettings <- getTLSSettings let liveMiddleware = mempty <#> loggerMiddleware <#> cspHeadersMiddleware directives <#> securityHeadersMiddleware - <#> domainMiddleware "chromabits" + <#> domainMiddleware "chromabits.com" <#> forceSSLMiddleware <#> deindexifyMiddleware <#> gzipMiddleware - let prodMiddlware = (mempty <#> stsHeadersMiddleware) <> liveMiddleware + prodMiddlware = (mempty <#> stsHeadersMiddleware) <> liveMiddleware let tlsConf = TLSConfiguration (const liveMiddleware) tlsSettings 8443 - let serveConf - = defaultServeConfiguration - & stage .~ case rawStage of - Just "live" -> Production - Just "staging" -> Staging - _ -> Development - & port .~ 9090 - & middleware .~ mempty - <#> loggerMiddleware - <#> securityHeadersMiddleware - <#> deindexifyMiddleware - <#> gzipMiddleware - & path .~ rawPath - & stagingTransform .~ - ((set tlsConfiguration $ Just tlsConf) - . (set middleware liveMiddleware) - . (set port 8080)) - & prodTransform .~ - ((set tlsConfiguration $ Just (tlsConf & tlsPort .~ 443)) - . (set middleware prodMiddlware) - . (set port 80)) - - serve serveConf + serve $ def + & scStage .~ case rawStage of + Just "live" -> Production + Just "staging" -> Staging + _ -> Development + & scPort .~ 9090 + & scMiddleware .~ mempty + <#> loggerMiddleware + <#> securityHeadersMiddleware + <#> deindexifyMiddleware + <#> gzipMiddleware + & scPath .~ rawPath + & scStagingTransform .~ + ( (set scTlsConfiguration $ Just tlsConf) + . (set scMiddleware liveMiddleware) + . (set scPort 8080) + ) + & scProdTransform .~ + ( (set scTlsConfiguration $ Just (tlsConf & tlsPort .~ 443)) + . (set scMiddleware prodMiddlware) + . (set scPort 80) + ) diff --git a/app/site.hs b/app/site.hs index b3003eca6c1fab0a43958324057f218b41344bc4..64405bfffd1e7f387da3b17afca4c8b125978e6e 100644 --- a/app/site.hs +++ b/app/site.hs @@ -1,38 +1,45 @@ --------------------------------------------------------------------------------- {-# LANGUAGE OverloadedStrings #-} import Control.Applicative -import Control.Monad (liftM) -import Control.Lens ((&), (.~)) -import qualified Data.Map as M -import Data.Maybe (fromMaybe) -import Data.List (intersperse, isSuffixOf) -import Data.List.Split (splitOn) -import Hakyll -import Hakyll.Serve (ServeConfiguration, defaultServeConfiguration, - hakyllConfiguration, hakyllServeWith) -import Text.Highlighting.Kate.Styles (haddock) -import Text.Pandoc.Options -import System.FilePath (splitExtension) -import System.Random (randomRIO) - --------------------------------------------------------------------------------- +import Control.Monad (liftM, mapM_) +import Data.List (intersperse, isSuffixOf) +import Data.List.Split (splitOn) +import Data.Maybe (fromMaybe) +import Data.Monoid ((<>)) +import System.FilePath (splitExtension) +import System.Random (randomRIO) + +import Control.Lens ((&), (.~)) +import qualified Data.Aeson as A +import Data.Default (def) +import qualified Data.HashMap.Strict as HM +import qualified Data.Text as T +import Hakyll +import Hakyll.Serve.Main (HakyllServeConfiguration, + hakyllServeWith, + hscHakyllConfiguration) +import Text.Highlighting.Kate.Styles (haddock) +import Text.Pandoc.Options + +-- TYPES ---------------------------------------------------------------------- + data SiteConfiguration = SiteConfiguration { siteRoot :: String , siteGaId :: String } -serveConf :: ServeConfiguration -serveConf = defaultServeConfiguration & hakyllConfiguration .~ hakyllConf +serveConf :: HakyllServeConfiguration +serveConf = def & hscHakyllConfiguration .~ hakyllConf + +-- CONFIGURATION -------------------------------------------------------------- --------------------------------------------------------------------------------- hakyllConf :: Configuration hakyllConf = defaultConfiguration - { deployCommand = - "rsync -ave 'ssh' _site/* 45.79.220.75:/var/www/chromabits " ++ - "&& rsync -ave 'ssh' " ++ - ".stack-work/install/x86_64-linux/lts-5.2/7.10.3/bin/server " ++ - "45.79.220.75:/opt/chromabits" + { deployCommand + = "rsync -ave 'ssh' _site/* 45.79.220.75:/var/www/chromabits " + <> "&& rsync -ave 'ssh' " + <> ".stack-work/install/x86_64-linux/lts-6.7/7.10.3/bin/server " + <> "45.79.220.75:/opt/chromabits" } siteConf :: SiteConfiguration @@ -41,56 +48,31 @@ siteConf = SiteConfiguration , siteGaId = "UA-47694260-1" } --- feedConf :: String -> FeedConfiguration --- feedConf title = FeedConfiguration --- { feedTitle = "Chromabits: " ++ title --- , feedDescription = "Personal blog" --- , feedAuthorName = "Eduardo Trujillo" --- , feedAuthorEmail = "ed@chromabits.com" --- , feedRoot = "https://chromabits.com" --- } +colors :: [String] +colors = ["purple", "yellow", "orange", "red", "cyan", "green", "blue"] + +-- RULES ---------------------------------------------------------------------- --------------------------------------------------------------------------------- main :: IO () main = hakyllServeWith serveConf $ do let writerOptions = defaultHakyllWriterOptions { writerHtml5 = True , writerHighlightStyle = haddock - , writerHTMLMathMethod = MathJax $ "https://cdn.mathjax.org/" - ++ "mathjax/latest/MathJax.js?config=TeX-AMS-MML_HTMLorMML" + , writerHTMLMathMethod = MathJax + $ "https://cdn.mathjax.org/" + <> "mathjax/latest/MathJax.js?config=TeX-AMS-MML_HTMLorMML" } - - let pandocHtml5Compiler = - pandocCompilerWith defaultHakyllReaderOptions writerOptions - - match "images/*" $ do - route idRoute - compile copyFileCompiler - - match "images/posts/*" $ do - route idRoute - compile copyFileCompiler - - match "images/tumblr/*" $ do - route idRoute - compile copyFileCompiler - - match "css/app.css" $ do - route $ setExtension "css" - compile copyFileCompiler - - match "favicon.ico" $ do - route $ setExtension "ico" - compile copyFileCompiler - - match "keybase.txt" $ do - route $ setExtension "txt" - compile copyFileCompiler - - match "robots.txt" $ do - route $ setExtension "txt" - compile copyFileCompiler - + pandocHtml5Compiler = pandocCompilerWith + defaultHakyllReaderOptions + writerOptions + + mapM_ matchAndCopyDirectory ["images/*", "images/posts/*", "images/tumblr/*"] + mapM_ matchAndCopy + [ ("css/app.css", "css") + , ("favicon.ico", "ico") + , ("keybase.txt", "txt") + , ("robots.txt", "txt") + ] match "bower_components/font-awesome/fonts/*" $ do route $ gsubRoute "bower_components/font-awesome/" (const "") compile copyFileCompiler @@ -109,14 +91,17 @@ main = hakyllServeWith serveConf $ do >>= relativizeUrls >>= deIndexUrls - matchMetadata "posts/*" (M.member "legacy") $ version "legacy" $ do + matchMetadata "posts/*" (HM.member "legacy") $ version "legacy" $ do route $ legacyRoute `composeRoutes` setExtension "html" compile $ do color <- unsafeCompiler (randomRIO (0, length colors - 1) >>= \selection -> pure (colors !! selection)) + identifier <- getUnderlying - let ctx = constField "color" color `mappend` - postCtx + let ctx + = constField "color" color + <> constField "identifier" (show identifier) + <> postCtx pandocHtml5Compiler >>= loadAndApplyTemplate "templates/post.html" ctx @@ -125,14 +110,21 @@ main = hakyllServeWith serveConf $ do >>= relativizeUrls >>= deIndexUrls + match "posts/*" . version "markdown" $ do + route idRoute + compile copyFileCompiler + match "posts/*" $ do - route $ directorizeDate `composeRoutes` setExtension "html" + route $ directorizeDate "/index" `composeRoutes` setExtension "html" compile $ do color <- unsafeCompiler (randomRIO (0, length colors - 1) >>= \selection -> pure (colors !! selection)) + identifier <- getUnderlying - let ctx = constField "color" color `mappend` - postCtx + let ctx + = constField "color" color + <> constField "identifier" (show identifier) + <> postCtx pandocHtml5Compiler >>= loadAndApplyTemplate "templates/post.html" ctx @@ -145,7 +137,7 @@ main = hakyllServeWith serveConf $ do match "drafts/*" $ do route $ setExtension "html" compile $ do - let ctx = constField "color" "red" `mappend` postCtx + let ctx = constField "color" "red" <> postCtx pandocHtml5Compiler >>= loadAndApplyTemplate "templates/post.html" ctx @@ -158,8 +150,10 @@ main = hakyllServeWith serveConf $ do route $ indexify `composeRoutes` setExtension "html" compile $ do compiled <- pandocHtml5Compiler - full <- loadAndApplyTemplate "templates/project.html" - siteCtx compiled + full <- loadAndApplyTemplate + "templates/project.html" + siteCtx + compiled teaser <- loadAndApplyTemplate "templates/project-teaser.html" siteCtx $ dropMore compiled @@ -175,10 +169,10 @@ main = hakyllServeWith serveConf $ do compile $ do posts <- recentFirst =<< loadAll ("posts/*" .&&. hasNoVersion) - let archiveCtx = - listField "posts" postCtx (return posts) `mappend` - constField "title" "Archives" `mappend` - siteCtx + let archiveCtx + = listField "posts" postCtx (return posts) + <> constField "title" "Archives" + <> siteCtx makeItem "" >>= loadAndApplyTemplate "templates/archive.html" archiveCtx @@ -191,10 +185,10 @@ main = hakyllServeWith serveConf $ do compile $ do projects <- loadAllSnapshots "projects/*" "teaser" - let archiveCtx = - listField "posts" siteCtx (return projects) `mappend` - constField "title" "Projects" `mappend` - siteCtx + let archiveCtx + = listField "posts" siteCtx (return projects) + <> constField "title" "Projects" + <> siteCtx makeItem "" >>= loadAndApplyTemplate "templates/projects.html" archiveCtx @@ -211,13 +205,13 @@ main = hakyllServeWith serveConf $ do body <- readTemplate . itemBody <$> getResourceBody let paginateCtx = paginateContext pag 1 - let ctx = paginateCtx `mappend` indexCtx + let ctx = paginateCtx <> indexCtx loadAllSnapshots ("posts/*" .&&. hasNoVersion) "content" >>= fmap (take 3) . recentFirst >>= applyTemplateList tpl ctx >>= makeItem - >>= applyTemplate body (ctx `mappend` bodyField "posts") + >>= applyTemplate body (ctx <> bodyField "posts") >>= loadAndApplyTemplate "templates/default.html" ctx >>= relativizeUrls >>= deIndexUrls @@ -228,53 +222,54 @@ main = hakyllServeWith serveConf $ do tpl <- loadBody "templates/post-item-full.html" let paginateCtx = paginateContext pag pageNum - let ctx = paginateCtx `mappend` - constField "title" ("Page " ++ show pageNum) `mappend` - indexCtx + let ctx + = paginateCtx + <> constField "title" ("Page " ++ show pageNum) + <> indexCtx loadAllSnapshots pattern "content" >>= recentFirst >>= applyTemplateList tpl ctx >>= makeItem - >>= loadAndApplyTemplate "templates/paginated.html" - (ctx `mappend` bodyField "posts") - >>= loadAndApplyTemplate "templates/default.html" - (ctx `mappend` bodyField "posts") + >>= loadAndApplyTemplate + "templates/paginated.html" + (ctx <> bodyField "posts") + >>= loadAndApplyTemplate + "templates/default.html" + (ctx <> bodyField "posts") >>= relativizeUrls >>= deIndexUrls match "templates/*" $ compile templateCompiler --------------------------------------------------------------------------------- +-- CONTEXTS ------------------------------------------------------------------- + siteCtx :: Context String -siteCtx = - deIndexedUrlField "url" `mappend` - constField "root" (siteRoot siteConf) `mappend` - constField "gaId" (siteGaId siteConf) `mappend` - defaultContext +siteCtx + = deIndexedUrlField "url" + <> constField "root" (siteRoot siteConf) + <> constField "gaId" (siteGaId siteConf) + <> defaultContext postCtx :: Context String -postCtx = - dateField "date" "%B %e, %Y" `mappend` - dateField "datetime" "%Y-%m-%d" `mappend` - siteCtx +postCtx + = dateField "date" "%B %e, %Y" + <> dateField "datetime" "%Y-%m-%d" + <> siteCtx indexCtx :: Context String indexCtx = siteCtx --------------------------------------------------------------------------------- -colors :: [String] -colors = ["purple", "yellow", "orange", "red", "cyan", "green", "blue"] +-- ROUTE HELPERS -------------------------------------------------------------- --------------------------------------------------------------------------------- -directorizeDate :: Routes -directorizeDate = customRoute (\i -> directorize $ toFilePath i) +directorizeDate :: String -> Routes +directorizeDate postfix = customRoute (directorize . toFilePath) where - directorize path = dirs ++ "/index" ++ ext - where - (dirs, ext) = splitExtension $ concat $ - intersperse "/" date ++ ["/"] ++ intersperse "-" rest - (date, rest) = splitAt 3 $ splitOn "-" path + directorize path = dirs <> postfix <> ext + where + (dirs, ext) = splitExtension . concat + $ intersperse "/" date ++ ["/"] ++ intersperse "-" rest + (date, rest) = splitAt 3 $ splitOn "-" path indexify :: Routes indexify = customRoute (\i -> addIndex $ toFilePath i) @@ -283,12 +278,37 @@ indexify = customRoute (\i -> addIndex $ toFilePath i) where (original, ext) = splitExtension path +-- | A special route that will produce paths compatible with the old Chromabits +-- blog. The slug in that path is determined by a 'legacy' field on each post. +legacyRoute :: Routes +legacyRoute = metadataRoute $ \x -> constRoute . T.unpack . mconcat $ + [ "post/" + , fromMaybe "unknown" (HM.lookup "legacy" x >>= valueToText) + , "/index.html" + ] + +-- RULE HELPERS --------------------------------------------------------------- + +matchAndCopyDirectory :: Pattern -> Rules () +matchAndCopyDirectory dir = match dir $ do + route idRoute + compile copyFileCompiler + +matchAndCopy :: (Pattern, String) -> Rules () +matchAndCopy (path, extension) = match path $ do + route $ setExtension extension + compile copyFileCompiler + +-- IDENTIFIER HELPERS --------------------------------------------------------- + grouper :: MonadMetadata m => [Identifier] -> m [[Identifier]] grouper ids = (liftM (paginateEvery 3) . sortRecentFirst) ids makeId :: PageNumber -> Identifier makeId pageNum = fromFilePath $ "page/" ++ show pageNum ++ "/index.html" +-- UTILITIES ------------------------------------------------------------------ + stripIndex :: String -> String stripIndex url = if "index.html" `isSuffixOf` url && elem (head url) ("/." :: String) @@ -304,9 +324,6 @@ deIndexedUrlField key = field key dropMore :: Item String -> Item String dropMore = fmap (unlines . takeWhile (/= "<!--more-->") . lines) --- | A special route that will produce paths compatible with the old Chromabits --- blog. The slug in that path is determined by a 'legacy' field on each post. -legacyRoute :: Routes -legacyRoute = metadataRoute $ - \x -> constRoute $ - "post/" ++ fromMaybe "unknown" (M.lookup "legacy" x) ++ "/index.html" +valueToText :: A.Value -> Maybe T.Text +valueToText (A.String innerText) = Just innerText +valueToText _ = Nothing diff --git a/blog.cabal b/blog.cabal index d35db05ffab098f278039ce40f8264875136a604..1139abf0d676aec80698c16f358079b0ff0cb4f5 100644 --- a/blog.cabal +++ b/blog.cabal @@ -19,15 +19,19 @@ executable blog ghc-options: -threaded build-depends: base == 4.*, lens, - hakyll == 4.7.*, - hakyll-serve, + hakyll == 4.8.*, + kawaii, filepath == 1.4.*, split == 0.2.*, random, transformers, containers == 0.5.*, pandoc == 1.*, - highlighting-kate == 0.6.* + highlighting-kate == 0.6.*, + unordered-containers, + aeson, + text, + data-default executable server main-is: server.hs @@ -39,11 +43,12 @@ executable server text, lens, bytestring == 0.10.*, - hakyll-serve, + kawaii, warp == 3.*, warp-tls == 3.*, wai == 3.*, wai-extra >= 3.0.14, wai-app-static == 3.*, streaming-commons == 0.1.*, - containers + containers, + data-default diff --git a/css/app.css b/css/app.css index 415f17557150d9071522cf2bab17abf56abc6d33..fb92698d60a805b9aee88f27028c2959a065300c 100644 --- a/css/app.css +++ b/css/app.css @@ -1,7 +1,7 @@ @charset "UTF-8"; -/*! normalize.css v3.0.3 | MIT License | github.com/necolas/normalize.css */html{font-family:sans-serif;-ms-text-size-adjust:100%;-webkit-text-size-adjust:100%}body{margin:0}article,aside,details,figcaption,figure,footer,header,hgroup,main,menu,nav,section,summary{display:block}audio,canvas,progress,video{display:inline-block;vertical-align:baseline}audio:not([controls]){display:none;height:0}[hidden],template{display:none}a{background-color:transparent}a:active,a:hover{outline:0}abbr[title]{border-bottom:1px dotted}b,strong{font-weight:700}dfn{font-style:italic}h1{font-size:2em;margin:.67em 0}mark{background:#ff0;color:#000}small{font-size:80%}sub,sup{font-size:75%;line-height:0;position:relative;vertical-align:baseline}sup{top:-.5em}sub{bottom:-.25em}img{border:0}svg:not(:root){overflow:hidden}figure{margin:1em 40px}hr{box-sizing:content-box;height:0}pre{overflow:auto}code,kbd,pre,samp{font-family:monospace,monospace;font-size:1em}button,input,optgroup,select,textarea{color:inherit;font:inherit;margin:0}button{overflow:visible}button,select{text-transform:none}button,html input[type=button],input[type=reset],input[type=submit]{-webkit-appearance:button;cursor:pointer}button[disabled],html input[disabled]{cursor:default}button::-moz-focus-inner,input::-moz-focus-inner{border:0;padding:0}input{line-height:normal}input[type=checkbox],input[type=radio]{box-sizing:border-box;padding:0}input[type=number]::-webkit-inner-spin-button,input[type=number]::-webkit-outer-spin-button{height:auto}input[type=search]{-webkit-appearance:textfield;box-sizing:content-box}input[type=search]::-webkit-search-cancel-button,input[type=search]::-webkit-search-decoration{-webkit-appearance:none}fieldset{border:1px solid silver;margin:0 2px;padding:.35em .625em .75em}legend{border:0;padding:0}textarea{overflow:auto}optgroup{font-weight:700}table{border-collapse:collapse;border-spacing:0}td,th{padding:0}.foundation-mq{font-family:"small=0em&medium=40em&large=64em&xlarge=75em&xxlarge=90em"}body,html{font-size:100%;box-sizing:border-box}*,:after,:before{box-sizing:inherit}body{padding:0;margin:0;font-family:adelle-sans,Helvetica Neue,Helvetica,Roboto,Arial,sans-serif;font-weight:400;line-height:1.5;color:#0a0a0a;background:#fefefe;-webkit-font-smoothing:antialiased;-moz-osx-font-smoothing:grayscale}img{max-width:100%;height:auto;-ms-interpolation-mode:bicubic;display:inline-block;vertical-align:middle}textarea{height:auto;min-height:50px;border-radius:0}select{width:100%;border-radius:0}#map_canvas embed,#map_canvas img,#map_canvas object,.map_canvas embed,.map_canvas img,.map_canvas object,.mqa-display embed,.mqa-display img,.mqa-display object{max-width:none!important}button{-webkit-appearance:none;-moz-appearance:none;background:transparent;padding:0;border:0;border-radius:0;line-height:1}.row{max-width:62.5rem;display:-ms-flexbox;display:flex;-ms-flex-flow:row wrap;flex-flow:row wrap;margin-left:auto;margin-right:auto}.column-row .row,.row .row{margin-left:-.9375rem;margin-right:-.9375rem}.column,.columns{-ms-flex:1 1 0px;flex:1 1 0px;padding-left:.9375rem;padding-right:.9375rem}.small-1{-ms-flex:0 0 8.33333%;flex:0 0 8.33333%;max-width:8.33333%}.small-2{-ms-flex:0 0 16.66667%;flex:0 0 16.66667%;max-width:16.66667%}.small-3{-ms-flex:0 0 25%;flex:0 0 25%;max-width:25%}.small-4{-ms-flex:0 0 33.33333%;flex:0 0 33.33333%;max-width:33.33333%}.small-5{-ms-flex:0 0 41.66667%;flex:0 0 41.66667%;max-width:41.66667%}.small-6{-ms-flex:0 0 50%;flex:0 0 50%;max-width:50%}.small-7{-ms-flex:0 0 58.33333%;flex:0 0 58.33333%;max-width:58.33333%}.small-8{-ms-flex:0 0 66.66667%;flex:0 0 66.66667%;max-width:66.66667%}.small-9{-ms-flex:0 0 75%;flex:0 0 75%;max-width:75%}.small-10{-ms-flex:0 0 83.33333%;flex:0 0 83.33333%;max-width:83.33333%}.small-11{-ms-flex:0 0 91.66667%;flex:0 0 91.66667%;max-width:91.66667%}.small-12{-ms-flex:0 0 100%;flex:0 0 100%;max-width:100%}@media screen and (min-width:40em){.medium-1{-ms-flex:0 0 8.33333%;flex:0 0 8.33333%;max-width:8.33333%}.medium-2{-ms-flex:0 0 16.66667%;flex:0 0 16.66667%;max-width:16.66667%}.medium-3{-ms-flex:0 0 25%;flex:0 0 25%;max-width:25%}.medium-4{-ms-flex:0 0 33.33333%;flex:0 0 33.33333%;max-width:33.33333%}.medium-5{-ms-flex:0 0 41.66667%;flex:0 0 41.66667%;max-width:41.66667%}.medium-6{-ms-flex:0 0 50%;flex:0 0 50%;max-width:50%}.medium-7{-ms-flex:0 0 58.33333%;flex:0 0 58.33333%;max-width:58.33333%}.medium-8{-ms-flex:0 0 66.66667%;flex:0 0 66.66667%;max-width:66.66667%}.medium-9{-ms-flex:0 0 75%;flex:0 0 75%;max-width:75%}.medium-10{-ms-flex:0 0 83.33333%;flex:0 0 83.33333%;max-width:83.33333%}.medium-11{-ms-flex:0 0 91.66667%;flex:0 0 91.66667%;max-width:91.66667%}.medium-12{-ms-flex:0 0 100%;flex:0 0 100%;max-width:100%}}@media screen and (min-width:64em){.large-1{-ms-flex:0 0 8.33333%;flex:0 0 8.33333%;max-width:8.33333%}.large-2{-ms-flex:0 0 16.66667%;flex:0 0 16.66667%;max-width:16.66667%}.large-3{-ms-flex:0 0 25%;flex:0 0 25%;max-width:25%}.large-4{-ms-flex:0 0 33.33333%;flex:0 0 33.33333%;max-width:33.33333%}.large-5{-ms-flex:0 0 41.66667%;flex:0 0 41.66667%;max-width:41.66667%}.large-6{-ms-flex:0 0 50%;flex:0 0 50%;max-width:50%}.large-7{-ms-flex:0 0 58.33333%;flex:0 0 58.33333%;max-width:58.33333%}.large-8{-ms-flex:0 0 66.66667%;flex:0 0 66.66667%;max-width:66.66667%}.large-9{-ms-flex:0 0 75%;flex:0 0 75%;max-width:75%}.large-10{-ms-flex:0 0 83.33333%;flex:0 0 83.33333%;max-width:83.33333%}.large-11{-ms-flex:0 0 91.66667%;flex:0 0 91.66667%;max-width:91.66667%}.large-12{-ms-flex:0 0 100%;flex:0 0 100%;max-width:100%}}@media screen and (min-width:40em){.medium-expand{-ms-flex:1 1 0px;flex:1 1 0px}}@media screen and (min-width:64em){.large-expand{-ms-flex:1 1 0px;flex:1 1 0px}}.shrink{-ms-flex:0 0 auto;flex:0 0 auto}.row.medium-unstack .column{-ms-flex:0 0 100%;flex:0 0 100%}@media screen and (min-width:40em){.row.medium-unstack .column{-ms-flex:1 1 0px;flex:1 1 0px}}.row.large-unstack .column{-ms-flex:0 0 100%;flex:0 0 100%}@media screen and (min-width:64em){.row.large-unstack .column{-ms-flex:1 1 0px;flex:1 1 0px}}.small-order-1{-ms-flex-order:1;order:1}.small-order-2{-ms-flex-order:2;order:2}.small-order-3{-ms-flex-order:3;order:3}.small-order-4{-ms-flex-order:4;order:4}.small-order-5{-ms-flex-order:5;order:5}.small-order-6{-ms-flex-order:6;order:6}@media screen and (min-width:40em){.medium-order-1{-ms-flex-order:1;order:1}.medium-order-2{-ms-flex-order:2;order:2}.medium-order-3{-ms-flex-order:3;order:3}.medium-order-4{-ms-flex-order:4;order:4}.medium-order-5{-ms-flex-order:5;order:5}.medium-order-6{-ms-flex-order:6;order:6}}@media screen and (min-width:64em){.large-order-1{-ms-flex-order:1;order:1}.large-order-2{-ms-flex-order:2;order:2}.large-order-3{-ms-flex-order:3;order:3}.large-order-4{-ms-flex-order:4;order:4}.large-order-5{-ms-flex-order:5;order:5}.large-order-6{-ms-flex-order:6;order:6}}.row.align-right{-ms-flex-pack:end;justify-content:flex-end}.row.align-center{-ms-flex-pack:center;justify-content:center}.row.align-justify{-ms-flex-pack:justify;justify-content:space-between}.row.align-spaced{-ms-flex-pack:distribute;justify-content:space-around}.row.align-top{-ms-flex-align:start;-ms-grid-row-align:flex-start;align-items:flex-start}.column.align-top{-ms-flex-item-align:start;align-self:flex-start}.row.align-bottom{-ms-flex-align:end;-ms-grid-row-align:flex-end;align-items:flex-end}.column.align-bottom{-ms-flex-item-align:end;align-self:flex-end}.row.align-middle{-ms-flex-align:center;-ms-grid-row-align:center;align-items:center}.column.align-middle{-ms-flex-item-align:center;align-self:center}.row.align-stretch{-ms-flex-align:stretch;-ms-grid-row-align:stretch;align-items:stretch}.column.align-stretch{-ms-flex-item-align:stretch;align-self:stretch}blockquote,dd,div,dl,dt,form,h1,h2,h3,h4,h5,h6,li,ol,p,pre,td,th,ul{margin:0;padding:0}p{font-size:inherit;line-height:1.6;margin-bottom:1rem;text-rendering:optimizeLegibility}em,i{font-style:italic}b,em,i,strong{line-height:inherit}b,strong{font-weight:700}small{font-size:80%;line-height:inherit}h1,h2,h3,h4,h5,h6{font-family:adelle-sans,Helvetica Neue,Helvetica,Roboto,Arial,sans-serif;font-weight:700;font-style:normal;color:inherit;text-rendering:optimizeLegibility;margin-top:0;margin-bottom:.5rem;line-height:1.4}h1 small,h2 small,h3 small,h4 small,h5 small,h6 small{color:#cacaca;line-height:0}h1{font-size:1.5rem}h2{font-size:1.25rem}h3{font-size:1.1875rem}h4{font-size:1.125rem}h5{font-size:1.0625rem}h6{font-size:1rem}@media screen and (min-width:40em){h1{font-size:3rem}h2{font-size:2.125rem}h3{font-size:1.9375rem}h4{font-size:1.5625rem}h5{font-size:1.25rem}h6{font-size:1rem}}a{color:#2199e8;text-decoration:none;line-height:inherit;cursor:pointer}a:focus,a:hover{color:#1585cf}a img{border:0}hr{max-width:62.5rem;height:0;border-right:0;border-top:0;border-bottom:1px solid #cacaca;border-left:0;margin:1.25rem auto;clear:both}dl,ol,ul{line-height:1.6;margin-bottom:1rem;list-style-position:outside}li{font-size:inherit}ul{list-style-type:disc}ol,ul{margin-left:1.25rem}ol ol,ol ul,ul ol,ul ul{margin-left:1.25rem;margin-bottom:0;list-style-type:inherit}dl{margin-bottom:1rem}dl dt{margin-bottom:.3rem;font-weight:700}blockquote{margin:0 0 1rem;padding:.5625rem 1.25rem 0 1.1875rem;border-left:1px solid #cacaca}blockquote,blockquote p{line-height:1.6;color:#8a8a8a}cite{display:block;font-size:.8125rem;color:#8a8a8a}cite:before{content:'\2014 \0020'}abbr{color:#0a0a0a;cursor:help;border-bottom:1px dotted #0a0a0a}code{font-weight:400;border:1px solid #cacaca;padding:.125rem .3125rem .0625rem}code,kbd{font-family:Consolas,Liberation Mono,Courier,monospace;color:#0a0a0a;background-color:#e6e6e6}kbd{padding:.125rem .25rem 0;margin:0}.subheader{margin-top:.2rem;margin-bottom:.5rem;font-weight:400;line-height:1.4;color:#8a8a8a}.lead{font-size:125%;line-height:1.6}.stat{font-size:2.5rem;line-height:1}p+.stat{margin-top:-1rem}.no-bullet{margin-left:0;list-style:none}.text-left{text-align:left}.text-right{text-align:right}.text-center{text-align:center}.text-justify{text-align:justify}@media screen and (min-width:40em){.medium-text-left{text-align:left}.medium-text-right{text-align:right}.medium-text-center{text-align:center}.medium-text-justify{text-align:justify}}@media screen and (min-width:64em){.large-text-left{text-align:left}.large-text-right{text-align:right}.large-text-center{text-align:center}.large-text-justify{text-align:justify}}.show-for-print{display:none!important}@media print{*{background:transparent!important;color:#000!important;box-shadow:none!important;text-shadow:none!important}.show-for-print{display:block!important}.hide-for-print{display:none!important}table.show-for-print{display:table!important}thead.show-for-print{display:table-header-group!important}tbody.show-for-print{display:table-row-group!important}tr.show-for-print{display:table-row!important}td.show-for-print,th.show-for-print{display:table-cell!important}a,a:visited{text-decoration:underline}a[href]:after{content:" (" attr(href) ")"}.ir a:after,a[href^='#']:after,a[href^='javascript:']:after{content:''}abbr[title]:after{content:" (" attr(title) ")"}blockquote,pre{border:1px solid #999;page-break-inside:avoid}thead{display:table-header-group}img,tr{page-break-inside:avoid}img{max-width:100%!important}@page{margin:.5cm}h2,h3,p{orphans:3;widows:3}h2,h3{page-break-after:avoid}}.button{display:inline-block;text-align:center;line-height:1;cursor:pointer;-webkit-appearance:none;transition:all .25s ease-out;vertical-align:middle;border:1px solid transparent;border-radius:0;padding:.85em 1em;margin:0 1rem 1rem 0;font-size:.9rem;background:#2199e8;color:#fff}[data-whatinput=mouse] .button{outline:0}.button:focus,.button:hover{background:#1583cc;color:#fff}.button.tiny{font-size:.6rem}.button.small{font-size:.75rem}.button.large{font-size:1.25rem}.button.expanded{display:block;width:100%;margin-left:0;margin-right:0}.button.primary{background:#2199e8;color:#fff}.button.primary:focus,.button.primary:hover{background:#147cc0;color:#fff}.button.secondary{background:#777;color:#fff}.button.secondary:focus,.button.secondary:hover{background:#5f5f5f;color:#fff}.button.success{background:#3adb76;color:#fff}.button.success:focus,.button.success:hover{background:#22bb5b;color:#fff}.button.alert{background:#ec5840;color:#fff}.button.alert:focus,.button.alert:hover{background:#da3116;color:#fff}.button.warning{background:#ffae00;color:#fff}.button.warning:focus,.button.warning:hover{background:#cc8b00;color:#fff}.button.hollow{border:1px solid #2199e8;color:#2199e8}.button.hollow,.button.hollow:focus,.button.hollow:hover{background:transparent}.button.hollow:focus,.button.hollow:hover{border-color:#0c4d78;color:#0c4d78}.button.hollow.primary{border:1px solid #2199e8;color:#2199e8}.button.hollow.primary:focus,.button.hollow.primary:hover{border-color:#0c4d78;color:#0c4d78}.button.hollow.secondary{border:1px solid #777;color:#777}.button.hollow.secondary:focus,.button.hollow.secondary:hover{border-color:#3c3c3c;color:#3c3c3c}.button.hollow.success{border:1px solid #3adb76;color:#3adb76}.button.hollow.success:focus,.button.hollow.success:hover{border-color:#157539;color:#157539}.button.hollow.alert{border:1px solid #ec5840;color:#ec5840}.button.hollow.alert:focus,.button.hollow.alert:hover{border-color:#881f0e;color:#881f0e}.button.hollow.warning{border:1px solid #ffae00;color:#ffae00}.button.hollow.warning:focus,.button.hollow.warning:hover{border-color:#805700;color:#805700}.button.disabled,.button[disabled]{opacity:.25;cursor:not-allowed;pointer-events:none}.button.dropdown:after{content:'';display:block;width:0;height:0;border:.4em inset;border-color:#fefefe transparent transparent;border-top-style:solid;position:relative;top:.4em;float:right;margin-left:1em;display:inline-block}.button.arrow-only:after{margin-left:0;float:none;top:.2em}[type=color],[type=date],[type=datetime-local],[type=datetime],[type=email],[type=month],[type=number],[type=password],[type=search],[type=tel],[type=text],[type=time],[type=url],[type=week],textarea{display:block;box-sizing:border-box;width:100%;height:2.4375rem;padding:.5rem;border:1px solid #cacaca;margin:0 0 1rem;font-family:inherit;font-size:1rem;color:#8a8a8a;background-color:#fefefe;box-shadow:inset 0 1px 2px hsla(0,0%,4%,.1);border-radius:0;transition:box-shadow .5s,border-color .25s ease-in-out;-webkit-appearance:none;-moz-appearance:none}[type=color]:focus,[type=date]:focus,[type=datetime-local]:focus,[type=datetime]:focus,[type=email]:focus,[type=month]:focus,[type=number]:focus,[type=password]:focus,[type=search]:focus,[type=tel]:focus,[type=text]:focus,[type=time]:focus,[type=url]:focus,[type=week]:focus,textarea:focus{border:1px solid #8a8a8a;background:#fefefe;outline:none;box-shadow:0 0 5px #cacaca;transition:box-shadow .5s,border-color .25s ease-in-out}textarea{max-width:100%}textarea[rows]{height:auto}input:disabled,input[readonly],textarea:disabled,textarea[readonly]{background-color:#e6e6e6;cursor:default}[type=button],[type=submit]{border-radius:0;-webkit-appearance:none;-moz-appearance:none}input[type=search]{box-sizing:border-box}[type=checkbox],[type=file],[type=radio]{margin:0 0 1rem}[type=checkbox]+label,[type=radio]+label{display:inline-block;margin-left:.5rem;margin-right:1rem;margin-bottom:0;vertical-align:baseline}label>[type=checkbox],label>[type=label]{margin-right:.5rem}[type=file]{width:100%}label{display:block;margin:0;font-size:.875rem;font-weight:400;line-height:1.8;color:#0a0a0a}label.middle{margin:0 0 1rem;padding:.5625rem 0}.help-text{margin-top:-.5rem;font-size:.8125rem;font-style:italic;color:#333}.input-group{display:table;width:100%;margin-bottom:1rem}.input-group>:first-child,.input-group>:last-child>*{border-radius:0 0 0 0}.input-group-button,.input-group-field,.input-group-label{display:table-cell;margin:0;vertical-align:middle}.input-group-label{text-align:center;width:1%;height:100%;padding:0 1rem;background:#e6e6e6;color:#0a0a0a;border:1px solid #cacaca}.input-group-label:first-child{border-right:0}.input-group-label:last-child{border-left:0}.input-group-field{border-radius:0;height:2.5rem}.input-group-button{height:100%;padding-top:0;padding-bottom:0;text-align:center;width:1%}.input-group-button a,.input-group-button button,.input-group-button input{margin:0}fieldset{border:0;padding:0;margin:0}legend{margin-bottom:.5rem}.fieldset{border:1px solid #cacaca;padding:1.25rem;margin:1.125rem 0}.fieldset legend{background:#fefefe;padding:0 .1875rem;margin:0;margin-left:-.1875rem}select{height:2.4375rem;padding:.5rem;border:1px solid #cacaca;margin:0 0 1rem;font-size:1rem;font-family:inherit;line-height:normal;color:#8a8a8a;background-color:#fafafa;border-radius:0;-webkit-appearance:none;-moz-appearance:none;background-image:url('data:image/svg+xml;utf8,<svg xmlns="http://www.w3.org/2000/svg" version="1.1" width="32" height="24" viewBox="0 0 32 24"><polygon points="0,0 32,0 16,24" style="fill: rgb(51, 51, 51)"></polygon></svg>');background-size:9px 6px;background-position:right .5rem center;background-repeat:no-repeat}@media screen and (min-width:0\0){select{background-image:url("data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAACAAAAAYCAYAAACbU/80AAAAGXRFWHRTb2Z0d2FyZQBBZG9iZSBJbWFnZVJlYWR5ccllPAAAAIpJREFUeNrEkckNgDAMBBfRkEt0ObRBBdsGXUDgmQfK4XhH2m8czQAAy27R3tsw4Qfe2x8uOO6oYLb6GlOor3GF+swURAOmUJ+RwtEJs9WvTGEYxBXqI1MQAZhCfUQKRzDMVj+TwrAIV6jvSUEkYAr1LSkcyTBb/V+KYfX7xAeusq3sLDtGH3kEGACPWIflNZfhRQAAAABJRU5ErkJggg==")}}select:disabled{background-color:#e6e6e6;cursor:default}select::-ms-expand{display:none}select[multiple]{height:auto}.is-invalid-input:not(:focus){background-color:rgba(236,88,64,.1);border-color:#ec5840}.form-error,.is-invalid-label{color:#ec5840}.form-error{display:none;margin-top:-.5rem;margin-bottom:1rem;font-size:.75rem;font-weight:700}.form-error.is-visible{display:block}.hide{display:none!important}.invisible{visibility:hidden}@media screen and (min-width:0em) and (max-width:39.9375em){.hide-for-small-only{display:none!important}}@media screen and (max-width:0em),screen and (min-width:40em){.show-for-small-only{display:none!important}}@media screen and (min-width:40em){.hide-for-medium{display:none!important}}@media screen and (max-width:39.9375em){.show-for-medium{display:none!important}}@media screen and (min-width:40em) and (max-width:63.9375em){.hide-for-medium-only{display:none!important}}@media screen and (max-width:39.9375em),screen and (min-width:64em){.show-for-medium-only{display:none!important}}@media screen and (min-width:64em){.hide-for-large{display:none!important}}@media screen and (max-width:63.9375em){.show-for-large{display:none!important}}@media screen and (min-width:64em) and (max-width:74.9375em){.hide-for-large-only{display:none!important}}@media screen and (max-width:63.9375em),screen and (min-width:75em){.show-for-large-only{display:none!important}}.show-for-sr,.show-on-focus{position:absolute!important;width:1px;height:1px;overflow:hidden;clip:rect(0,0,0,0)}.show-on-focus:active,.show-on-focus:focus{position:static!important;height:auto;width:auto;overflow:visible;clip:auto}.hide-for-portrait,.show-for-landscape{display:block!important}@media screen and (orientation:landscape){.hide-for-portrait,.show-for-landscape{display:block!important}}@media screen and (orientation:portrait){.hide-for-portrait,.show-for-landscape{display:none!important}}.hide-for-landscape,.show-for-portrait{display:none!important}@media screen and (orientation:landscape){.hide-for-landscape,.show-for-portrait{display:none!important}}@media screen and (orientation:portrait){.hide-for-landscape,.show-for-portrait{display:block!important}}.float-left{float:left!important}.float-right{float:right!important}.float-center{display:block;margin-left:auto;margin-right:auto}.clearfix:after,.clearfix:before{content:' ';display:table}.clearfix:after{clear:both}.accordion{list-style-type:none;background:#fefefe;border:1px solid #e6e6e6;border-radius:0;margin-left:0}.accordion-title{display:block;padding:1.25rem 1rem;line-height:1;font-size:.75rem;color:#2199e8;position:relative;border-bottom:1px solid #e6e6e6}.accordion-title:focus,.accordion-title:hover{background-color:#e6e6e6}:last-child>.accordion-title{border-bottom-width:0}.accordion-title:before{content:'+';position:absolute;right:1rem;top:50%;margin-top:-.5rem}.is-active>.accordion-title:before{content:'–'}.accordion-content{padding:1.25rem 1rem;display:none;border-bottom:1px solid #e6e6e6}.is-accordion-submenu-parent>a{position:relative}.is-accordion-submenu-parent>a:after{content:'';display:block;width:0;height:0;border:6px inset;border-color:#2199e8 transparent transparent;border-top-style:solid;position:absolute;top:50%;margin-top:-4px;right:1rem}.is-accordion-submenu-parent[aria-expanded=true]>a:after{-ms-transform-origin:50% 50%;transform-origin:50% 50%;-ms-transform:scaleY(-1);transform:scaleY(-1)}.badge{display:inline-block;padding:.3em;min-width:2.1em;font-size:.6rem;text-align:center;border-radius:50%;background:#2199e8;color:#fefefe}.badge.secondary{background:#777;color:#fefefe}.badge.success{background:#3adb76;color:#fefefe}.badge.alert{background:#ec5840;color:#fefefe}.badge.warning{background:#ffae00;color:#fefefe}.breadcrumbs{list-style:none;margin:0 0 1rem}.breadcrumbs:after,.breadcrumbs:before{content:' ';display:table}.breadcrumbs:after{clear:both}.breadcrumbs li{float:left;color:#0a0a0a;font-size:.6875rem;cursor:default;text-transform:uppercase}.breadcrumbs li:not(:last-child):after{color:#cacaca;content:"/";margin:0 .75rem;position:relative;top:1px;opacity:1}.breadcrumbs a{color:#2199e8}.breadcrumbs a:hover{text-decoration:underline}.breadcrumbs .disabled{color:#cacaca}.button-group{margin-bottom:1rem;font-size:.9rem}.button-group:after,.button-group:before{content:' ';display:table}.button-group:after{clear:both}.button-group .button{float:left;margin:0;font-size:inherit}.button-group .button:not(:last-child){border-right:1px solid #fefefe}.button-group.tiny{font-size:.6rem}.button-group.small{font-size:.75rem}.button-group.large{font-size:1.25rem}.button-group.expanded .button:nth-last-child(2):first-child,.button-group.expanded .button:nth-last-child(2):first-child~.button{width:50%}.button-group.expanded .button:nth-last-child(3):first-child,.button-group.expanded .button:nth-last-child(3):first-child~.button{width:33.33333%}.button-group.expanded .button:nth-last-child(4):first-child,.button-group.expanded .button:nth-last-child(4):first-child~.button{width:25%}.button-group.expanded .button:nth-last-child(5):first-child,.button-group.expanded .button:nth-last-child(5):first-child~.button{width:20%}.button-group.expanded .button:nth-last-child(6):first-child,.button-group.expanded .button:nth-last-child(6):first-child~.button{width:16.66667%}.button-group.primary .button{background:#2199e8;color:#fff}.button-group.primary .button:focus,.button-group.primary .button:hover{background:#147cc0;color:#fff}.button-group.secondary .button{background:#777;color:#fff}.button-group.secondary .button:focus,.button-group.secondary .button:hover{background:#5f5f5f;color:#fff}.button-group.success .button{background:#3adb76;color:#fff}.button-group.success .button:focus,.button-group.success .button:hover{background:#22bb5b;color:#fff}.button-group.alert .button{background:#ec5840;color:#fff}.button-group.alert .button:focus,.button-group.alert .button:hover{background:#da3116;color:#fff}.button-group.warning .button{background:#ffae00;color:#fff}.button-group.warning .button:focus,.button-group.warning .button:hover{background:#cc8b00;color:#fff}.button-group.stacked-for-small .button,.button-group.stacked .button{width:100%;border-right:0}@media screen and (min-width:40em){.button-group.stacked-for-small .button{width:auto}.button-group.stacked-for-small .button:not(:last-child){border-right:1px solid #fefefe}}.callout{margin:0 0 1rem;padding:1rem;border:1px solid hsla(0,0%,4%,.25);border-radius:0;position:relative;color:#0a0a0a;background-color:#fff}.callout>:first-child{margin-top:0}.callout>:last-child{margin-bottom:0}.callout.primary{background-color:#def0fc}.callout.secondary{background-color:#ebebeb}.callout.success{background-color:#e1faea}.callout.alert{background-color:#fce6e2}.callout.warning{background-color:#fff3d9}.callout.small{padding:.5rem}.callout.large{padding:3rem}.close-button{position:absolute;color:#8a8a8a;right:1rem;top:.5rem;font-size:2em;line-height:1;cursor:pointer}[data-whatinput=mouse] .close-button{outline:0}.close-button:focus,.close-button:hover{color:#0a0a0a}.is-drilldown{position:relative;overflow:hidden}.is-drilldown-submenu{position:absolute;top:0;left:100%;z-index:-1;height:100%;width:100%;background:#fefefe;transition:transform .15s linear}.is-drilldown-submenu.is-active{z-index:1;display:block;-ms-transform:translateX(-100%);transform:translateX(-100%)}.is-drilldown-submenu.is-closing{-ms-transform:translateX(100%);transform:translateX(100%)}.is-drilldown-submenu-parent>a{position:relative}.is-drilldown-submenu-parent>a:after{content:'';display:block;width:0;height:0;border:6px inset;border-color:transparent transparent transparent #2199e8;border-left-style:solid;position:absolute;top:50%;margin-top:-6px;right:1rem}.js-drilldown-back:before{content:'';display:block;width:0;height:0;border:6px inset;border-color:transparent #2199e8 transparent transparent;border-right-style:solid;float:left;margin-right:.75rem;margin-left:.6rem;margin-top:14px}.dropdown-pane{background-color:#fefefe;border:1px solid #cacaca;display:block;padding:1rem;position:absolute;visibility:hidden;width:300px;z-index:10;border-radius:0}.dropdown-pane.is-open{visibility:visible}.dropdown-pane.tiny{width:100px}.dropdown-pane.small{width:200px}.dropdown-pane.large{width:400px}[data-whatinput=mouse] .dropdown.menu a{outline:0}.dropdown.menu .is-dropdown-submenu-parent{position:relative}.dropdown.menu .is-dropdown-submenu-parent a:after{float:right;margin-top:3px;margin-left:10px}.dropdown.menu .is-dropdown-submenu-parent.is-down-arrow a{padding-right:1.5rem;position:relative}.dropdown.menu .is-dropdown-submenu-parent.is-down-arrow>a:after{content:'';display:block;width:0;height:0;border:5px inset;border-color:#2199e8 transparent transparent;border-top-style:solid;position:absolute;top:.825rem;right:5px}.dropdown.menu .is-dropdown-submenu-parent.is-left-arrow>a:after{content:'';display:block;width:0;height:0;border:5px inset;border-color:transparent #2199e8 transparent transparent;border-right-style:solid;float:left;margin-left:0;margin-right:10px}.dropdown.menu .is-dropdown-submenu-parent.is-right-arrow>a:after{content:'';display:block;width:0;height:0;border:5px inset;border-color:transparent transparent transparent #2199e8;border-left-style:solid}.dropdown.menu .is-dropdown-submenu-parent.is-left-arrow.opens-inner .submenu{right:0;left:auto}.dropdown.menu .is-dropdown-submenu-parent.is-right-arrow.opens-inner .submenu{left:0;right:auto}.dropdown.menu .is-dropdown-submenu-parent.opens-inner .submenu{top:100%}.no-js .dropdown.menu ul{display:none}.dropdown.menu .submenu{display:none;position:absolute;top:0;left:100%;min-width:200px;z-index:1;background:#fefefe;border:1px solid #cacaca}.dropdown.menu .submenu>li{width:100%}.dropdown.menu .submenu.first-sub{top:100%;left:0;right:auto}.dropdown.menu .submenu.js-dropdown-active,.dropdown.menu .submenu:not(.js-dropdown-nohover)>.is-dropdown-submenu-parent:hover>.dropdown.menu .submenu{display:block}.dropdown.menu .is-dropdown-submenu-parent.opens-left .submenu{left:auto;right:100%}.dropdown.menu.align-right .submenu.first-sub{top:100%;left:auto;right:0}.is-dropdown-menu.vertical{width:100px}.is-dropdown-menu.vertical.align-right{float:right}.is-dropdown-menu.vertical>li .submenu{top:0;left:100%}.flex-video{position:relative;height:0;padding-top:1.5625rem;padding-bottom:75%;margin-bottom:1rem;overflow:hidden}.flex-video embed,.flex-video iframe,.flex-video object,.flex-video video{position:absolute;top:0;left:0;width:100%;height:100%}.flex-video.widescreen{padding-bottom:56.25%}.flex-video.vimeo{padding-top:0}.label{display:inline-block;padding:.33333rem .5rem;font-size:.8rem;line-height:1;white-space:nowrap;cursor:default;border-radius:0;background:#2199e8;color:#fefefe}.label.secondary{background:#777;color:#fefefe}.label.success{background:#3adb76;color:#fefefe}.label.alert{background:#ec5840;color:#fefefe}.label.warning{background:#ffae00;color:#fefefe}.media-object{margin-bottom:1rem;display:block}.media-object img{max-width:none}@media screen and (min-width:0em) and (max-width:39.9375em){.media-object.stack-for-small .media-object-section{display:block;padding:0;padding-bottom:1rem}.media-object.stack-for-small .media-object-section img{width:100%}}.media-object-section{display:table-cell;vertical-align:top}.media-object-section:first-child{padding-right:1rem}.media-object-section:last-child:not(+.media-object-section:first-child){padding-left:1rem}.media-object-section.middle{vertical-align:middle}.media-object-section.bottom{vertical-align:bottom}.menu{margin:0;list-style-type:none}.menu>li{display:table-cell;vertical-align:middle}[data-whatinput=mouse] .menu>li{outline:0}.menu>li:not(.menu-text)>a{display:block;padding:.7rem 1rem;line-height:1}.menu a,.menu button,.menu input{margin-bottom:0}.menu>li>a>i,.menu>li>a>img,.menu>li>a>span{vertical-align:middle}.menu>li>a>i,.menu>li>a>img{display:inline-block;margin-right:.25rem}.menu>li{display:table-cell}.menu.vertical>li{display:block}@media screen and (min-width:40em){.menu.medium-horizontal>li{display:table-cell}.menu.medium-vertical>li{display:block}}@media screen and (min-width:64em){.menu.large-horizontal>li{display:table-cell}.menu.large-vertical>li{display:block}}.menu.simple a{padding:0;margin-right:1rem}.menu.align-right>li{float:right}.menu.expanded{display:table;width:100%}.menu.expanded>li:nth-last-child(2):first-child,.menu.expanded>li:nth-last-child(2):first-child~li{width:50%}.menu.expanded>li:nth-last-child(3):first-child,.menu.expanded>li:nth-last-child(3):first-child~li{width:33.33333%}.menu.expanded>li:nth-last-child(4):first-child,.menu.expanded>li:nth-last-child(4):first-child~li{width:25%}.menu.expanded>li:nth-last-child(5):first-child,.menu.expanded>li:nth-last-child(5):first-child~li{width:20%}.menu.expanded>li:nth-last-child(6):first-child,.menu.expanded>li:nth-last-child(6):first-child~li{width:16.66667%}.menu.expanded>li:first-child:last-child{width:100%}.menu.icon-top>li>a{text-align:center}.menu.icon-top>li>a>i,.menu.icon-top>li>a>img{display:block;margin:0 auto .25rem}.menu.nested{margin-left:1rem}.menu-text{font-weight:700;color:inherit;line-height:1;padding-top:0;padding-bottom:0;padding:.7rem 1rem}.no-js [data-responsive-menu] ul{display:none}body,html{height:100%}.off-canvas-wrapper{width:100%;overflow-x:hidden;position:relative;backface-visibility:hidden;-webkit-overflow-scrolling:auto}.off-canvas-wrapper-inner{position:relative;width:100%;transition:transform .5s ease}.off-canvas-wrapper-inner:after,.off-canvas-wrapper-inner:before{content:' ';display:table}.off-canvas-wrapper-inner:after{clear:both}.off-canvas-content{min-height:100%;background:#fefefe;transition:transform .5s ease;backface-visibility:hidden;z-index:1;box-shadow:0 0 10px hsla(0,0%,4%,.5)}.js-off-canvas-exit{display:none;position:absolute;top:0;left:0;width:100%;height:100%;background:hsla(0,0%,100%,.25);cursor:pointer;transition:background .5s ease}.is-off-canvas-open .js-off-canvas-exit{display:block}.off-canvas{position:absolute;background:#e6e6e6;z-index:-1;max-height:100%;overflow-y:auto;-ms-transform:translateX(0);transform:translateX(0)}[data-whatinput=mouse] .off-canvas{outline:0}.off-canvas.position-left{left:-250px;top:0;width:250px}.is-open-left{-ms-transform:translateX(250px);transform:translateX(250px)}.off-canvas.position-right{right:-250px;top:0;width:250px}.is-open-right{-ms-transform:translateX(-250px);transform:translateX(-250px)}@media screen and (min-width:40em){.position-left.reveal-for-medium{left:0;z-index:auto;position:fixed}.position-left.reveal-for-medium~.off-canvas-content{margin-left:250px}.position-right.reveal-for-medium{right:0;z-index:auto;position:fixed}.position-right.reveal-for-medium~.off-canvas-content{margin-right:250px}}@media screen and (min-width:64em){.position-left.reveal-for-large{left:0;z-index:auto;position:fixed}.position-left.reveal-for-large~.off-canvas-content{margin-left:250px}.position-right.reveal-for-large{right:0;z-index:auto;position:fixed}.position-right.reveal-for-large~.off-canvas-content{margin-right:250px}}.orbit,.orbit-container{position:relative}.orbit-container{margin:0;overflow:hidden;list-style:none}.orbit-slide{width:100%;max-height:100%}.orbit-slide.no-motionui.is-active{top:0;left:0}.orbit-figure{margin:0}.orbit-image{margin:0;width:100%;max-width:100%}.orbit-caption{bottom:0;width:100%;margin-bottom:0;background-color:hsla(0,0%,4%,.5)}.orbit-caption,.orbit-next,.orbit-previous{position:absolute;padding:1rem;color:#fefefe}.orbit-next,.orbit-previous{top:50%;-ms-transform:translateY(-50%);transform:translateY(-50%);z-index:10}[data-whatinput=mouse] .orbit-next,[data-whatinput=mouse] .orbit-previous{outline:0}.orbit-next:active,.orbit-next:focus,.orbit-next:hover,.orbit-previous:active,.orbit-previous:focus,.orbit-previous:hover{background-color:hsla(0,0%,4%,.5)}.orbit-previous{left:0}.orbit-next{left:auto;right:0}.orbit-bullets{position:relative;margin-top:.8rem;margin-bottom:.8rem;text-align:center}[data-whatinput=mouse] .orbit-bullets{outline:0}.orbit-bullets button{width:1.2rem;height:1.2rem;margin:.1rem;background-color:#cacaca;border-radius:50%}.orbit-bullets button.is-active,.orbit-bullets button:hover{background-color:#8a8a8a}.pagination{margin-left:0;margin-bottom:1rem}.pagination:after,.pagination:before{content:' ';display:table}.pagination:after{clear:both}.pagination li{font-size:.875rem;margin-right:.0625rem;display:none;border-radius:0}.pagination li:first-child,.pagination li:last-child{display:inline-block}@media screen and (min-width:40em){.pagination li{display:inline-block}}.pagination a,.pagination button{color:#0a0a0a;display:block;padding:.1875rem .625rem;border-radius:0}.pagination a:hover,.pagination button:hover{background:#e6e6e6}.pagination .current{padding:.1875rem .625rem;background:#2199e8;color:#fefefe;cursor:default}.pagination .disabled{padding:.1875rem .625rem;color:#cacaca;cursor:default}.pagination .disabled:hover{background:transparent}.pagination .ellipsis:after{content:'…';padding:.1875rem .625rem;color:#0a0a0a}.pagination-previous.disabled:before,.pagination-previous a:before{content:'«';display:inline-block;margin-right:.5rem}.pagination-next.disabled:after,.pagination-next a:after{content:'»';display:inline-block;margin-left:.5rem}.progress{background-color:#cacaca;height:1rem;margin-bottom:1rem;border-radius:0}.progress.primary .progress-meter{background-color:#2199e8}.progress.secondary .progress-meter{background-color:#777}.progress.success .progress-meter{background-color:#3adb76}.progress.alert .progress-meter{background-color:#ec5840}.progress.warning .progress-meter{background-color:#ffae00}.progress-meter{position:relative;display:block;width:0;height:100%;background-color:#2199e8;border-radius:0}.progress-meter .progress-meter-text{position:absolute;top:50%;left:50%;-ms-transform:translate(-50%,-50%);transform:translate(-50%,-50%);margin:0;font-size:.75rem;font-weight:700;color:#fefefe;white-space:nowrap}.slider{position:relative;height:.5rem;margin-top:1.25rem;margin-bottom:2.25rem;background-color:#e6e6e6;cursor:pointer;-webkit-user-select:none;-moz-user-select:none;-ms-user-select:none;user-select:none;-ms-touch-action:none;touch-action:none}.slider-fill{position:absolute;top:0;left:0;display:inline-block;max-width:100%;height:.5rem;background-color:#cacaca;transition:all .2s ease-in-out}.slider-fill.is-dragging{transition:all 0s linear}.slider-handle{top:50%;-ms-transform:translateY(-50%);transform:translateY(-50%);position:absolute;left:0;z-index:1;display:inline-block;width:1.4rem;height:1.4rem;background-color:#2199e8;transition:all .2s ease-in-out;-ms-touch-action:manipulation;touch-action:manipulation;border-radius:0}[data-whatinput=mouse] .slider-handle{outline:0}.slider-handle:hover{background-color:#1583cc}.slider-handle.is-dragging{transition:all 0s linear}.slider.disabled,.slider[disabled]{opacity:.25;cursor:not-allowed}.slider.vertical{display:inline-block;width:.5rem;height:12.5rem;margin:0 1.25rem;-ms-transform:scaleY(-1);transform:scaleY(-1)}.slider.vertical .slider-fill{top:0;width:.5rem;max-height:100%}.slider.vertical .slider-handle{position:absolute;top:0;left:50%;width:1.4rem;height:1.4rem;-ms-transform:translateX(-50%);transform:translateX(-50%)}.sticky-container{position:relative}.sticky{position:absolute;z-index:0;transform:translateZ(0)}.sticky.is-stuck{position:fixed;z-index:5}.sticky.is-stuck.is-at-top{top:0}.sticky.is-stuck.is-at-bottom{bottom:0}.sticky.is-anchored{position:absolute;left:auto;right:auto}.sticky.is-anchored.is-at-bottom{bottom:0}body.is-reveal-open{overflow:hidden}.reveal-overlay{display:none;position:fixed;top:0;bottom:0;left:0;right:0;z-index:1005;background-color:hsla(0,0%,4%,.45);overflow-y:scroll}.reveal{display:none;z-index:1006;padding:1rem;border:1px solid #cacaca;margin:100px auto 0;background-color:#fefefe;border-radius:0;position:absolute;overflow-y:auto}[data-whatinput=mouse] .reveal{outline:0}@media screen and (min-width:40em){.reveal{min-height:0}}.reveal .column,.reveal .columns{min-width:0}.reveal>:last-child{margin-bottom:0}@media screen and (min-width:40em){.reveal{width:600px;max-width:62.5rem}}.reveal.collapse{padding:0}@media screen and (min-width:40em){.reveal .reveal{left:auto;right:auto;margin:0 auto}}@media screen and (min-width:40em){.reveal.tiny{width:30%;max-width:62.5rem}}@media screen and (min-width:40em){.reveal.small{width:50%;max-width:62.5rem}}@media screen and (min-width:40em){.reveal.large{width:90%;max-width:62.5rem}}.reveal.full{top:0;left:0;width:100%;height:100%;height:100vh;min-height:100vh;max-width:none;margin-left:0;border:none}.switch{margin-bottom:1rem;outline:0;position:relative;-webkit-user-select:none;-moz-user-select:none;-ms-user-select:none;user-select:none;color:#fefefe;font-weight:700;font-size:.875rem}.switch-input{opacity:0;position:absolute}.switch-paddle{background:#cacaca;cursor:pointer;display:block;position:relative;width:4rem;height:2rem;transition:all .25s ease-out;border-radius:0;color:inherit;font-weight:inherit}input+.switch-paddle{margin:0}.switch-paddle:after{background:#fefefe;content:'';display:block;position:absolute;height:1.5rem;left:.25rem;top:.25rem;width:1.5rem;transition:all .25s ease-out;transform:translateZ(0);border-radius:0}input:checked~.switch-paddle{background:#2199e8}input:checked~.switch-paddle:after{left:2.25rem}[data-whatinput=mouse] input:focus~.switch-paddle{outline:0}.switch-active,.switch-inactive{position:absolute;top:50%;-ms-transform:translateY(-50%);transform:translateY(-50%)}.switch-active{left:8%;display:none}input:checked+label>.switch-active{display:block}.switch-inactive{right:15%}input:checked+label>.switch-inactive{display:none}.switch.tiny .switch-paddle{width:3rem;height:1.5rem;font-size:.625rem}.switch.tiny .switch-paddle:after{width:1rem;height:1rem}.switch.tiny input:checked~.switch-paddle:after{left:1.75rem}.switch.small .switch-paddle{width:3.5rem;height:1.75rem;font-size:.75rem}.switch.small .switch-paddle:after{width:1.25rem;height:1.25rem}.switch.small input:checked~.switch-paddle:after{left:2rem}.switch.large .switch-paddle{width:5rem;height:2.5rem;font-size:1rem}.switch.large .switch-paddle:after{width:2rem;height:2rem}.switch.large input:checked~.switch-paddle:after{left:2.75rem}table{margin-bottom:1rem;border-radius:0}tbody,tfoot,thead{border:1px solid #f1f1f1;background-color:#fefefe}caption{font-weight:700;padding:.5rem .625rem .625rem}tfoot,thead{background:#f8f8f8;color:#0a0a0a}tfoot tr,thead tr{background:transparent}tfoot td,tfoot th,thead td,thead th{padding:.5rem .625rem .625rem;font-weight:700;text-align:left}tbody tr:nth-child(even){background-color:#f1f1f1}tbody td,tbody th{padding:.5rem .625rem .625rem}@media screen and (max-width:63.9375em){table.stack tfoot,table.stack thead{display:none}table.stack td,table.stack th,table.stack tr{display:block}table.stack td{border-top:0}}table.scroll{display:block;width:100%;overflow-y:scroll}table.hover tr:hover{background-color:#f9f9f9}table.hover tr:nth-of-type(even):hover{background-color:#ececec}.tabs{margin:0;list-style-type:none;background:#fefefe;border:1px solid #e6e6e6}.tabs:after,.tabs:before{content:' ';display:table}.tabs:after{clear:both}.tabs.simple>li>a{padding:0}.tabs.simple>li>a:hover{background:transparent}.tabs.vertical>li{width:auto;float:none;display:block}.tabs.primary{background:#2199e8}.tabs.primary>li>a{color:#fefefe}.tabs.primary>li>a:focus,.tabs.primary>li>a:hover{background:#1893e4}.tabs-title{float:left}.tabs-title>a{display:block;padding:1.25rem 1.5rem;line-height:1;font-size:12px;color:#2199e8}.tabs-title>a:hover{background:#fefefe}.tabs-title>a:focus,.tabs-title>a[aria-selected=true]{background:#e6e6e6}.tabs-content{background:#fefefe;transition:all .5s ease;border:1px solid #e6e6e6;border-top:0}.tabs-content.vertical{border:1px solid #e6e6e6;border-left:0}.tabs-panel{display:none;padding:1rem}.tabs-panel.is-active{display:block}.thumbnail{border:4px solid #fefefe;box-shadow:0 0 0 1px hsla(0,0%,4%,.2);display:inline-block;line-height:0;max-width:100%;transition:box-shadow .2s ease-out;border-radius:0;margin-bottom:1rem}.thumbnail:focus,.thumbnail:hover{box-shadow:0 0 6px 1px rgba(33,153,232,.5)}.title-bar{background:#0a0a0a;color:#fefefe;padding:.5rem}.title-bar:after,.title-bar:before{content:' ';display:table}.title-bar:after{clear:both}.title-bar .menu-icon{margin-left:.25rem;margin-right:.5rem}.title-bar-left{float:left}.title-bar-right{float:right;text-align:right}.title-bar-title{font-weight:700}.menu-icon,.title-bar-title{vertical-align:middle;display:inline-block}.menu-icon{position:relative;cursor:pointer;width:20px;height:16px}.menu-icon:after{content:'';position:absolute;display:block;width:100%;height:2px;background:#fefefe;top:0;left:0;box-shadow:0 7px 0 #fefefe,0 14px 0 #fefefe}.menu-icon:hover:after{background:#cacaca;box-shadow:0 7px 0 #cacaca,0 14px 0 #cacaca}.has-tip{border-bottom:1px dotted #8a8a8a;font-weight:700;position:relative;display:inline-block;cursor:help}.tooltip{background-color:#0a0a0a;color:#fefefe;font-size:80%;padding:.75rem;position:absolute;z-index:10;top:calc(100% + .6495rem);max-width:10rem!important;border-radius:0}.tooltip:before{border:.75rem inset;border-color:transparent transparent #0a0a0a;border-bottom-style:solid;bottom:100%;position:absolute;left:50%;-ms-transform:translateX(-50%);transform:translateX(-50%)}.tooltip.top:before,.tooltip:before{content:'';display:block;width:0;height:0}.tooltip.top:before{border:.75rem inset;border-color:#0a0a0a transparent transparent;border-top-style:solid;top:100%;bottom:auto}.tooltip.left:before{border:.75rem inset;border-color:transparent transparent transparent #0a0a0a;border-left-style:solid;left:100%}.tooltip.left:before,.tooltip.right:before{content:'';display:block;width:0;height:0;bottom:auto;top:50%;-ms-transform:translateY(-50%);transform:translateY(-50%)}.tooltip.right:before{border:.75rem inset;border-color:transparent #0a0a0a transparent transparent;border-right-style:solid;left:auto;right:100%}.top-bar{padding:.5rem}.top-bar:after,.top-bar:before{content:' ';display:table}.top-bar:after{clear:both}.top-bar,.top-bar ul{background-color:#eee}.top-bar a{color:#fff}.top-bar input{width:200px;margin-right:1rem}.top-bar input.button{width:auto}@media screen and (max-width:39.9375em){.stacked-for-small .top-bar-left,.stacked-for-small .top-bar-right{width:100%}}@media screen and (max-width:63.9375em){.stacked-for-medium .top-bar-left,.stacked-for-medium .top-bar-right{width:100%}}@media screen and (max-width:74.9375em){.stacked-for-large .top-bar-left,.stacked-for-large .top-bar-right{width:100%}}@media screen and (max-width:39.9375em){.top-bar-left,.top-bar-right{width:100%}}.top-bar-left{float:left}.top-bar-right{float:right} +/*! normalize.css v3.0.3 | MIT License | github.com/necolas/normalize.css */html{font-family:sans-serif;-ms-text-size-adjust:100%;-webkit-text-size-adjust:100%}body{margin:0}article,aside,details,figcaption,figure,footer,header,hgroup,main,menu,nav,section,summary{display:block}audio,canvas,progress,video{display:inline-block;vertical-align:baseline}audio:not([controls]){display:none;height:0}[hidden],template{display:none}a{background-color:transparent}a:active,a:hover{outline:0}abbr[title]{border-bottom:1px dotted}b,strong{font-weight:700}dfn{font-style:italic}h1{font-size:2em;margin:.67em 0}mark{background:#ff0;color:#000}small{font-size:80%}sub,sup{font-size:75%;line-height:0;position:relative;vertical-align:baseline}sup{top:-.5em}sub{bottom:-.25em}img{border:0}svg:not(:root){overflow:hidden}figure{margin:1em 40px}hr{box-sizing:content-box;height:0}pre{overflow:auto}code,kbd,pre,samp{font-family:monospace,monospace;font-size:1em}button,input,optgroup,select,textarea{color:inherit;font:inherit;margin:0}button{overflow:visible}button,select{text-transform:none}button,html input[type=button],input[type=reset],input[type=submit]{-webkit-appearance:button;cursor:pointer}button[disabled],html input[disabled]{cursor:default}button::-moz-focus-inner,input::-moz-focus-inner{border:0;padding:0}input{line-height:normal}input[type=checkbox],input[type=radio]{box-sizing:border-box;padding:0}input[type=number]::-webkit-inner-spin-button,input[type=number]::-webkit-outer-spin-button{height:auto}input[type=search]{-webkit-appearance:textfield;box-sizing:content-box}input[type=search]::-webkit-search-cancel-button,input[type=search]::-webkit-search-decoration{-webkit-appearance:none}fieldset{border:1px solid silver;margin:0 2px;padding:.35em .625em .75em}legend{border:0;padding:0}textarea{overflow:auto}optgroup{font-weight:700}table{border-collapse:collapse;border-spacing:0}td,th{padding:0}.foundation-mq{font-family:"small=0em&medium=40em&large=64em&xlarge=75em&xxlarge=90em"}body,html{font-size:100%;box-sizing:border-box}*,:after,:before{box-sizing:inherit}body{padding:0;margin:0;font-family:adelle-sans,Helvetica Neue,Helvetica,Roboto,Arial,sans-serif;font-weight:400;line-height:1.5;color:#0a0a0a;background:#fefefe;-webkit-font-smoothing:antialiased;-moz-osx-font-smoothing:grayscale}img{max-width:100%;height:auto;-ms-interpolation-mode:bicubic;display:inline-block;vertical-align:middle}textarea{height:auto;min-height:50px;border-radius:0}select{width:100%;border-radius:0}#map_canvas embed,#map_canvas img,#map_canvas object,.map_canvas embed,.map_canvas img,.map_canvas object,.mqa-display embed,.mqa-display img,.mqa-display object{max-width:none!important}button{-webkit-appearance:none;-moz-appearance:none;background:transparent;padding:0;border:0;border-radius:0;line-height:1}.row{max-width:62.5rem;display:-ms-flexbox;display:flex;-ms-flex-flow:row wrap;flex-flow:row wrap;margin-left:auto;margin-right:auto}.column-row .row,.row .row{margin-left:-.9375rem;margin-right:-.9375rem}.column,.columns{-ms-flex:1 1 0px;flex:1 1 0px;padding-left:.9375rem;padding-right:.9375rem}.small-1{-ms-flex:0 0 8.33333%;flex:0 0 8.33333%;max-width:8.33333%}.small-2{-ms-flex:0 0 16.66667%;flex:0 0 16.66667%;max-width:16.66667%}.small-3{-ms-flex:0 0 25%;flex:0 0 25%;max-width:25%}.small-4{-ms-flex:0 0 33.33333%;flex:0 0 33.33333%;max-width:33.33333%}.small-5{-ms-flex:0 0 41.66667%;flex:0 0 41.66667%;max-width:41.66667%}.small-6{-ms-flex:0 0 50%;flex:0 0 50%;max-width:50%}.small-7{-ms-flex:0 0 58.33333%;flex:0 0 58.33333%;max-width:58.33333%}.small-8{-ms-flex:0 0 66.66667%;flex:0 0 66.66667%;max-width:66.66667%}.small-9{-ms-flex:0 0 75%;flex:0 0 75%;max-width:75%}.small-10{-ms-flex:0 0 83.33333%;flex:0 0 83.33333%;max-width:83.33333%}.small-11{-ms-flex:0 0 91.66667%;flex:0 0 91.66667%;max-width:91.66667%}.small-12{-ms-flex:0 0 100%;flex:0 0 100%;max-width:100%}@media screen and (min-width:40em){.medium-1{-ms-flex:0 0 8.33333%;flex:0 0 8.33333%;max-width:8.33333%}.medium-2{-ms-flex:0 0 16.66667%;flex:0 0 16.66667%;max-width:16.66667%}.medium-3{-ms-flex:0 0 25%;flex:0 0 25%;max-width:25%}.medium-4{-ms-flex:0 0 33.33333%;flex:0 0 33.33333%;max-width:33.33333%}.medium-5{-ms-flex:0 0 41.66667%;flex:0 0 41.66667%;max-width:41.66667%}.medium-6{-ms-flex:0 0 50%;flex:0 0 50%;max-width:50%}.medium-7{-ms-flex:0 0 58.33333%;flex:0 0 58.33333%;max-width:58.33333%}.medium-8{-ms-flex:0 0 66.66667%;flex:0 0 66.66667%;max-width:66.66667%}.medium-9{-ms-flex:0 0 75%;flex:0 0 75%;max-width:75%}.medium-10{-ms-flex:0 0 83.33333%;flex:0 0 83.33333%;max-width:83.33333%}.medium-11{-ms-flex:0 0 91.66667%;flex:0 0 91.66667%;max-width:91.66667%}.medium-12{-ms-flex:0 0 100%;flex:0 0 100%;max-width:100%}}@media screen and (min-width:64em){.large-1{-ms-flex:0 0 8.33333%;flex:0 0 8.33333%;max-width:8.33333%}.large-2{-ms-flex:0 0 16.66667%;flex:0 0 16.66667%;max-width:16.66667%}.large-3{-ms-flex:0 0 25%;flex:0 0 25%;max-width:25%}.large-4{-ms-flex:0 0 33.33333%;flex:0 0 33.33333%;max-width:33.33333%}.large-5{-ms-flex:0 0 41.66667%;flex:0 0 41.66667%;max-width:41.66667%}.large-6{-ms-flex:0 0 50%;flex:0 0 50%;max-width:50%}.large-7{-ms-flex:0 0 58.33333%;flex:0 0 58.33333%;max-width:58.33333%}.large-8{-ms-flex:0 0 66.66667%;flex:0 0 66.66667%;max-width:66.66667%}.large-9{-ms-flex:0 0 75%;flex:0 0 75%;max-width:75%}.large-10{-ms-flex:0 0 83.33333%;flex:0 0 83.33333%;max-width:83.33333%}.large-11{-ms-flex:0 0 91.66667%;flex:0 0 91.66667%;max-width:91.66667%}.large-12{-ms-flex:0 0 100%;flex:0 0 100%;max-width:100%}}@media screen and (min-width:40em){.medium-expand{-ms-flex:1 1 0px;flex:1 1 0px}}@media screen and (min-width:64em){.large-expand{-ms-flex:1 1 0px;flex:1 1 0px}}.shrink{-ms-flex:0 0 auto;flex:0 0 auto}.row.medium-unstack .column{-ms-flex:0 0 100%;flex:0 0 100%}@media screen and (min-width:40em){.row.medium-unstack .column{-ms-flex:1 1 0px;flex:1 1 0px}}.row.large-unstack .column{-ms-flex:0 0 100%;flex:0 0 100%}@media screen and (min-width:64em){.row.large-unstack .column{-ms-flex:1 1 0px;flex:1 1 0px}}.small-order-1{-ms-flex-order:1;order:1}.small-order-2{-ms-flex-order:2;order:2}.small-order-3{-ms-flex-order:3;order:3}.small-order-4{-ms-flex-order:4;order:4}.small-order-5{-ms-flex-order:5;order:5}.small-order-6{-ms-flex-order:6;order:6}@media screen and (min-width:40em){.medium-order-1{-ms-flex-order:1;order:1}.medium-order-2{-ms-flex-order:2;order:2}.medium-order-3{-ms-flex-order:3;order:3}.medium-order-4{-ms-flex-order:4;order:4}.medium-order-5{-ms-flex-order:5;order:5}.medium-order-6{-ms-flex-order:6;order:6}}@media screen and (min-width:64em){.large-order-1{-ms-flex-order:1;order:1}.large-order-2{-ms-flex-order:2;order:2}.large-order-3{-ms-flex-order:3;order:3}.large-order-4{-ms-flex-order:4;order:4}.large-order-5{-ms-flex-order:5;order:5}.large-order-6{-ms-flex-order:6;order:6}}.row.align-right{-ms-flex-pack:end;justify-content:flex-end}.row.align-center{-ms-flex-pack:center;justify-content:center}.row.align-justify{-ms-flex-pack:justify;justify-content:space-between}.row.align-spaced{-ms-flex-pack:distribute;justify-content:space-around}.row.align-top{-ms-flex-align:start;-ms-grid-row-align:flex-start;align-items:flex-start}.column.align-top{-ms-flex-item-align:start;align-self:flex-start}.row.align-bottom{-ms-flex-align:end;-ms-grid-row-align:flex-end;align-items:flex-end}.column.align-bottom{-ms-flex-item-align:end;align-self:flex-end}.row.align-middle{-ms-flex-align:center;-ms-grid-row-align:center;align-items:center}.column.align-middle{-ms-flex-item-align:center;align-self:center}.row.align-stretch{-ms-flex-align:stretch;-ms-grid-row-align:stretch;align-items:stretch}.column.align-stretch{-ms-flex-item-align:stretch;align-self:stretch}blockquote,dd,div,dl,dt,form,h1,h2,h3,h4,h5,h6,li,ol,p,pre,td,th,ul{margin:0;padding:0}p{font-size:inherit;line-height:1.6;margin-bottom:1rem;text-rendering:optimizeLegibility}em,i{font-style:italic}b,em,i,strong{line-height:inherit}b,strong{font-weight:700}small{font-size:80%;line-height:inherit}h1,h2,h3,h4,h5,h6{font-family:adelle-sans,Helvetica Neue,Helvetica,Roboto,Arial,sans-serif;font-weight:700;font-style:normal;color:inherit;text-rendering:optimizeLegibility;margin-top:0;margin-bottom:.5rem;line-height:1.4}h1 small,h2 small,h3 small,h4 small,h5 small,h6 small{color:#cacaca;line-height:0}h1{font-size:1.5rem}h2{font-size:1.25rem}h3{font-size:1.1875rem}h4{font-size:1.125rem}h5{font-size:1.0625rem}h6{font-size:1rem}@media screen and (min-width:40em){h1{font-size:3rem}h2{font-size:2.125rem}h3{font-size:1.9375rem}h4{font-size:1.5625rem}h5{font-size:1.25rem}h6{font-size:1rem}}a{color:#2199e8;text-decoration:none;line-height:inherit;cursor:pointer}a:focus,a:hover{color:#1585cf}a img{border:0}hr{max-width:62.5rem;height:0;border-right:0;border-top:0;border-bottom:1px solid #cacaca;border-left:0;margin:1.25rem auto;clear:both}dl,ol,ul{line-height:1.6;margin-bottom:1rem;list-style-position:outside}li{font-size:inherit}ul{list-style-type:disc}ol,ul{margin-left:1.25rem}ol ol,ol ul,ul ol,ul ul{margin-left:1.25rem;margin-bottom:0;list-style-type:inherit}dl{margin-bottom:1rem}dl dt{margin-bottom:.3rem;font-weight:700}blockquote{margin:0 0 1rem;padding:.5625rem 1.25rem 0 1.1875rem;border-left:1px solid #cacaca}blockquote,blockquote p{line-height:1.6;color:#8a8a8a}cite{display:block;font-size:.8125rem;color:#8a8a8a}cite:before{content:'\2014 \0020'}abbr{color:#0a0a0a;cursor:help;border-bottom:1px dotted #0a0a0a}code{font-weight:400;border:1px solid #cacaca;padding:.125rem .3125rem .0625rem}code,kbd{font-family:Consolas,Liberation Mono,Courier,monospace;color:#0a0a0a;background-color:#e6e6e6}kbd{padding:.125rem .25rem 0;margin:0}.subheader{margin-top:.2rem;margin-bottom:.5rem;font-weight:400;line-height:1.4;color:#8a8a8a}.lead{font-size:125%;line-height:1.6}.stat{font-size:2.5rem;line-height:1}p+.stat{margin-top:-1rem}.no-bullet{margin-left:0;list-style:none}.text-left{text-align:left}.text-right{text-align:right}.text-center{text-align:center}.text-justify{text-align:justify}@media screen and (min-width:40em){.medium-text-left{text-align:left}.medium-text-right{text-align:right}.medium-text-center{text-align:center}.medium-text-justify{text-align:justify}}@media screen and (min-width:64em){.large-text-left{text-align:left}.large-text-right{text-align:right}.large-text-center{text-align:center}.large-text-justify{text-align:justify}}.show-for-print{display:none!important}@media print{*{background:transparent!important;color:#000!important;box-shadow:none!important;text-shadow:none!important}.show-for-print{display:block!important}.hide-for-print{display:none!important}table.show-for-print{display:table!important}thead.show-for-print{display:table-header-group!important}tbody.show-for-print{display:table-row-group!important}tr.show-for-print{display:table-row!important}td.show-for-print,th.show-for-print{display:table-cell!important}a,a:visited{text-decoration:underline}a[href]:after{content:" (" attr(href) ")"}.ir a:after,a[href^='#']:after,a[href^='javascript:']:after{content:''}abbr[title]:after{content:" (" attr(title) ")"}blockquote,pre{border:1px solid #999;page-break-inside:avoid}thead{display:table-header-group}img,tr{page-break-inside:avoid}img{max-width:100%!important}@page{margin:.5cm}h2,h3,p{orphans:3;widows:3}h2,h3{page-break-after:avoid}}.button{display:inline-block;text-align:center;line-height:1;cursor:pointer;-webkit-appearance:none;transition:all .25s ease-out;vertical-align:middle;border:1px solid transparent;border-radius:0;padding:.85em 1em;margin:0 1rem 1rem 0;font-size:.9rem;background:#2199e8;color:#fff}[data-whatinput=mouse] .button{outline:0}.button:focus,.button:hover{background:#1583cc;color:#fff}.button.tiny{font-size:.6rem}.button.small{font-size:.75rem}.button.large{font-size:1.25rem}.button.expanded{display:block;width:100%;margin-left:0;margin-right:0}.button.primary{background:#2199e8;color:#fff}.button.primary:focus,.button.primary:hover{background:#147cc0;color:#fff}.button.secondary{background:#777;color:#fff}.button.secondary:focus,.button.secondary:hover{background:#5f5f5f;color:#fff}.button.success{background:#3adb76;color:#fff}.button.success:focus,.button.success:hover{background:#22bb5b;color:#fff}.button.alert{background:#ec5840;color:#fff}.button.alert:focus,.button.alert:hover{background:#da3116;color:#fff}.button.warning{background:#ffae00;color:#fff}.button.warning:focus,.button.warning:hover{background:#cc8b00;color:#fff}.button.hollow{border:1px solid #2199e8;color:#2199e8}.button.hollow,.button.hollow:focus,.button.hollow:hover{background:transparent}.button.hollow:focus,.button.hollow:hover{border-color:#0c4d78;color:#0c4d78}.button.hollow.primary{border:1px solid #2199e8;color:#2199e8}.button.hollow.primary:focus,.button.hollow.primary:hover{border-color:#0c4d78;color:#0c4d78}.button.hollow.secondary{border:1px solid #777;color:#777}.button.hollow.secondary:focus,.button.hollow.secondary:hover{border-color:#3c3c3c;color:#3c3c3c}.button.hollow.success{border:1px solid #3adb76;color:#3adb76}.button.hollow.success:focus,.button.hollow.success:hover{border-color:#157539;color:#157539}.button.hollow.alert{border:1px solid #ec5840;color:#ec5840}.button.hollow.alert:focus,.button.hollow.alert:hover{border-color:#881f0e;color:#881f0e}.button.hollow.warning{border:1px solid #ffae00;color:#ffae00}.button.hollow.warning:focus,.button.hollow.warning:hover{border-color:#805700;color:#805700}.button.disabled,.button[disabled]{opacity:.25;cursor:not-allowed;pointer-events:none}.button.dropdown:after{content:'';display:block;width:0;height:0;border:.4em inset;border-color:#fefefe transparent transparent;border-top-style:solid;position:relative;top:.4em;float:right;margin-left:1em;display:inline-block}.button.arrow-only:after{margin-left:0;float:none;top:.2em}[type=color],[type=date],[type=datetime-local],[type=datetime],[type=email],[type=month],[type=number],[type=password],[type=search],[type=tel],[type=text],[type=time],[type=url],[type=week],textarea{display:block;box-sizing:border-box;width:100%;height:2.4375rem;padding:.5rem;border:1px solid #cacaca;margin:0 0 1rem;font-family:inherit;font-size:1rem;color:#8a8a8a;background-color:#fefefe;box-shadow:inset 0 1px 2px hsla(0,0%,4%,.1);border-radius:0;transition:box-shadow .5s,border-color .25s ease-in-out;-webkit-appearance:none;-moz-appearance:none}[type=color]:focus,[type=date]:focus,[type=datetime-local]:focus,[type=datetime]:focus,[type=email]:focus,[type=month]:focus,[type=number]:focus,[type=password]:focus,[type=search]:focus,[type=tel]:focus,[type=text]:focus,[type=time]:focus,[type=url]:focus,[type=week]:focus,textarea:focus{border:1px solid #8a8a8a;background:#fefefe;outline:none;box-shadow:0 0 5px #cacaca;transition:box-shadow .5s,border-color .25s ease-in-out}textarea{max-width:100%}textarea[rows]{height:auto}input:disabled,input[readonly],textarea:disabled,textarea[readonly]{background-color:#e6e6e6;cursor:default}[type=button],[type=submit]{border-radius:0;-webkit-appearance:none;-moz-appearance:none}input[type=search]{box-sizing:border-box}[type=checkbox],[type=file],[type=radio]{margin:0 0 1rem}[type=checkbox]+label,[type=radio]+label{display:inline-block;margin-left:.5rem;margin-right:1rem;margin-bottom:0;vertical-align:baseline}label>[type=checkbox],label>[type=label]{margin-right:.5rem}[type=file]{width:100%}label{display:block;margin:0;font-size:.875rem;font-weight:400;line-height:1.8;color:#0a0a0a}label.middle{margin:0 0 1rem;padding:.5625rem 0}.help-text{margin-top:-.5rem;font-size:.8125rem;font-style:italic;color:#333}.input-group{display:table;width:100%;margin-bottom:1rem}.input-group>:first-child,.input-group>:last-child>*{border-radius:0 0 0 0}.input-group-button,.input-group-field,.input-group-label{display:table-cell;margin:0;vertical-align:middle}.input-group-label{text-align:center;width:1%;height:100%;padding:0 1rem;background:#e6e6e6;color:#0a0a0a;border:1px solid #cacaca}.input-group-label:first-child{border-right:0}.input-group-label:last-child{border-left:0}.input-group-field{border-radius:0;height:2.5rem}.input-group-button{height:100%;padding-top:0;padding-bottom:0;text-align:center;width:1%}.input-group-button a,.input-group-button button,.input-group-button input{margin:0}fieldset{border:0;padding:0;margin:0}legend{margin-bottom:.5rem}.fieldset{border:1px solid #cacaca;padding:1.25rem;margin:1.125rem 0}.fieldset legend{background:#fefefe;padding:0 .1875rem;margin:0;margin-left:-.1875rem}select{height:2.4375rem;padding:.5rem;border:1px solid #cacaca;margin:0 0 1rem;font-size:1rem;font-family:inherit;line-height:normal;color:#8a8a8a;background-color:#fafafa;border-radius:0;-webkit-appearance:none;-moz-appearance:none;background-image:url('data:image/svg+xml;utf8,<svg xmlns="http://www.w3.org/2000/svg" version="1.1" width="32" height="24" viewBox="0 0 32 24"><polygon points="0,0 32,0 16,24" style="fill: rgb(51, 51, 51)"></polygon></svg>');background-size:9px 6px;background-position:right .5rem center;background-repeat:no-repeat}@media screen and (min-width:0\0){select{background-image:url("data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAACAAAAAYCAYAAACbU/80AAAAGXRFWHRTb2Z0d2FyZQBBZG9iZSBJbWFnZVJlYWR5ccllPAAAAIpJREFUeNrEkckNgDAMBBfRkEt0ObRBBdsGXUDgmQfK4XhH2m8czQAAy27R3tsw4Qfe2x8uOO6oYLb6GlOor3GF+swURAOmUJ+RwtEJs9WvTGEYxBXqI1MQAZhCfUQKRzDMVj+TwrAIV6jvSUEkYAr1LSkcyTBb/V+KYfX7xAeusq3sLDtGH3kEGACPWIflNZfhRQAAAABJRU5ErkJggg==")}}select:disabled{background-color:#e6e6e6;cursor:default}select::-ms-expand{display:none}select[multiple]{height:auto}.is-invalid-input:not(:focus){background-color:rgba(236,88,64,.1);border-color:#ec5840}.form-error,.is-invalid-label{color:#ec5840}.form-error{display:none;margin-top:-.5rem;margin-bottom:1rem;font-size:.75rem;font-weight:700}.form-error.is-visible{display:block}.hide{display:none!important}.invisible{visibility:hidden}@media screen and (min-width:0em) and (max-width:39.9375em){.hide-for-small-only{display:none!important}}@media screen and (max-width:0em),screen and (min-width:40em){.show-for-small-only{display:none!important}}@media screen and (min-width:40em){.hide-for-medium{display:none!important}}@media screen and (max-width:39.9375em){.show-for-medium{display:none!important}}@media screen and (min-width:40em) and (max-width:63.9375em){.hide-for-medium-only{display:none!important}}@media screen and (max-width:39.9375em),screen and (min-width:64em){.show-for-medium-only{display:none!important}}@media screen and (min-width:64em){.hide-for-large{display:none!important}}@media screen and (max-width:63.9375em){.show-for-large{display:none!important}}@media screen and (min-width:64em) and (max-width:74.9375em){.hide-for-large-only{display:none!important}}@media screen and (max-width:63.9375em),screen and (min-width:75em){.show-for-large-only{display:none!important}}.show-for-sr,.show-on-focus{position:absolute!important;width:1px;height:1px;overflow:hidden;clip:rect(0,0,0,0)}.show-on-focus:active,.show-on-focus:focus{position:static!important;height:auto;width:auto;overflow:visible;clip:auto}.hide-for-portrait,.show-for-landscape{display:block!important}@media screen and (orientation:landscape){.hide-for-portrait,.show-for-landscape{display:block!important}}@media screen and (orientation:portrait){.hide-for-portrait,.show-for-landscape{display:none!important}}.hide-for-landscape,.show-for-portrait{display:none!important}@media screen and (orientation:landscape){.hide-for-landscape,.show-for-portrait{display:none!important}}@media screen and (orientation:portrait){.hide-for-landscape,.show-for-portrait{display:block!important}}.float-left{float:left!important}.float-right{float:right!important}.float-center{display:block;margin-left:auto;margin-right:auto}.clearfix:after,.clearfix:before{content:' ';display:table}.clearfix:after{clear:both}.accordion{list-style-type:none;background:#fefefe;border:1px solid #e6e6e6;border-radius:0;margin-left:0}.accordion-title{display:block;padding:1.25rem 1rem;line-height:1;font-size:.75rem;color:#2199e8;position:relative;border-bottom:1px solid #e6e6e6}.accordion-title:focus,.accordion-title:hover{background-color:#e6e6e6}:last-child>.accordion-title{border-bottom-width:0}.accordion-title:before{content:'+';position:absolute;right:1rem;top:50%;margin-top:-.5rem}.is-active>.accordion-title:before{content:'–'}.accordion-content{padding:1.25rem 1rem;display:none;border-bottom:1px solid #e6e6e6}.is-accordion-submenu-parent>a{position:relative}.is-accordion-submenu-parent>a:after{content:'';display:block;width:0;height:0;border:6px inset;border-color:#2199e8 transparent transparent;border-top-style:solid;position:absolute;top:50%;margin-top:-4px;right:1rem}.is-accordion-submenu-parent[aria-expanded=true]>a:after{-ms-transform-origin:50% 50%;transform-origin:50% 50%;-ms-transform:scaleY(-1);transform:scaleY(-1)}.badge{display:inline-block;padding:.3em;min-width:2.1em;font-size:.6rem;text-align:center;border-radius:50%;background:#2199e8;color:#fefefe}.badge.secondary{background:#777;color:#fefefe}.badge.success{background:#3adb76;color:#fefefe}.badge.alert{background:#ec5840;color:#fefefe}.badge.warning{background:#ffae00;color:#fefefe}.breadcrumbs{list-style:none;margin:0 0 1rem}.breadcrumbs:after,.breadcrumbs:before{content:' ';display:table}.breadcrumbs:after{clear:both}.breadcrumbs li{float:left;color:#0a0a0a;font-size:.6875rem;cursor:default;text-transform:uppercase}.breadcrumbs li:not(:last-child):after{color:#cacaca;content:"/";margin:0 .75rem;position:relative;top:1px;opacity:1}.breadcrumbs a{color:#2199e8}.breadcrumbs a:hover{text-decoration:underline}.breadcrumbs .disabled{color:#cacaca}.button-group{margin-bottom:1rem;font-size:.9rem}.button-group:after,.button-group:before{content:' ';display:table}.button-group:after{clear:both}.button-group .button{float:left;margin:0;font-size:inherit}.button-group .button:not(:last-child){border-right:1px solid #fefefe}.button-group.tiny{font-size:.6rem}.button-group.small{font-size:.75rem}.button-group.large{font-size:1.25rem}.button-group.expanded .button:nth-last-child(2):first-child,.button-group.expanded .button:nth-last-child(2):first-child~.button{width:50%}.button-group.expanded .button:nth-last-child(3):first-child,.button-group.expanded .button:nth-last-child(3):first-child~.button{width:33.33333%}.button-group.expanded .button:nth-last-child(4):first-child,.button-group.expanded .button:nth-last-child(4):first-child~.button{width:25%}.button-group.expanded .button:nth-last-child(5):first-child,.button-group.expanded .button:nth-last-child(5):first-child~.button{width:20%}.button-group.expanded .button:nth-last-child(6):first-child,.button-group.expanded .button:nth-last-child(6):first-child~.button{width:16.66667%}.button-group.primary .button{background:#2199e8;color:#fff}.button-group.primary .button:focus,.button-group.primary .button:hover{background:#147cc0;color:#fff}.button-group.secondary .button{background:#777;color:#fff}.button-group.secondary .button:focus,.button-group.secondary .button:hover{background:#5f5f5f;color:#fff}.button-group.success .button{background:#3adb76;color:#fff}.button-group.success .button:focus,.button-group.success .button:hover{background:#22bb5b;color:#fff}.button-group.alert .button{background:#ec5840;color:#fff}.button-group.alert .button:focus,.button-group.alert .button:hover{background:#da3116;color:#fff}.button-group.warning .button{background:#ffae00;color:#fff}.button-group.warning .button:focus,.button-group.warning .button:hover{background:#cc8b00;color:#fff}.button-group.stacked-for-small .button,.button-group.stacked .button{width:100%;border-right:0}@media screen and (min-width:40em){.button-group.stacked-for-small .button{width:auto}.button-group.stacked-for-small .button:not(:last-child){border-right:1px solid #fefefe}}.callout{margin:0 0 1rem;padding:1rem;border:1px solid hsla(0,0%,4%,.25);border-radius:0;position:relative;color:#0a0a0a;background-color:#fff}.callout>:first-child{margin-top:0}.callout>:last-child{margin-bottom:0}.callout.primary{background-color:#def0fc}.callout.secondary{background-color:#ebebeb}.callout.success{background-color:#e1faea}.callout.alert{background-color:#fce6e2}.callout.warning{background-color:#fff3d9}.callout.small{padding:.5rem}.callout.large{padding:3rem}.close-button{position:absolute;color:#8a8a8a;right:1rem;top:.5rem;font-size:2em;line-height:1;cursor:pointer}[data-whatinput=mouse] .close-button{outline:0}.close-button:focus,.close-button:hover{color:#0a0a0a}.is-drilldown{position:relative;overflow:hidden}.is-drilldown-submenu{position:absolute;top:0;left:100%;z-index:-1;height:100%;width:100%;background:#fefefe;transition:transform .15s linear}.is-drilldown-submenu.is-active{z-index:1;display:block;-ms-transform:translateX(-100%);transform:translateX(-100%)}.is-drilldown-submenu.is-closing{-ms-transform:translateX(100%);transform:translateX(100%)}.is-drilldown-submenu-parent>a{position:relative}.is-drilldown-submenu-parent>a:after{content:'';display:block;width:0;height:0;border:6px inset;border-color:transparent transparent transparent #2199e8;border-left-style:solid;position:absolute;top:50%;margin-top:-6px;right:1rem}.js-drilldown-back:before{content:'';display:block;width:0;height:0;border:6px inset;border-color:transparent #2199e8 transparent transparent;border-right-style:solid;float:left;margin-right:.75rem;margin-left:.6rem;margin-top:14px}.dropdown-pane{background-color:#fefefe;border:1px solid #cacaca;display:block;padding:1rem;position:absolute;visibility:hidden;width:300px;z-index:10;border-radius:0}.dropdown-pane.is-open{visibility:visible}.dropdown-pane.tiny{width:100px}.dropdown-pane.small{width:200px}.dropdown-pane.large{width:400px}[data-whatinput=mouse] .dropdown.menu a{outline:0}.dropdown.menu .is-dropdown-submenu-parent{position:relative}.dropdown.menu .is-dropdown-submenu-parent a:after{float:right;margin-top:3px;margin-left:10px}.dropdown.menu .is-dropdown-submenu-parent.is-down-arrow a{padding-right:1.5rem;position:relative}.dropdown.menu .is-dropdown-submenu-parent.is-down-arrow>a:after{content:'';display:block;width:0;height:0;border:5px inset;border-color:#2199e8 transparent transparent;border-top-style:solid;position:absolute;top:.825rem;right:5px}.dropdown.menu .is-dropdown-submenu-parent.is-left-arrow>a:after{content:'';display:block;width:0;height:0;border:5px inset;border-color:transparent #2199e8 transparent transparent;border-right-style:solid;float:left;margin-left:0;margin-right:10px}.dropdown.menu .is-dropdown-submenu-parent.is-right-arrow>a:after{content:'';display:block;width:0;height:0;border:5px inset;border-color:transparent transparent transparent #2199e8;border-left-style:solid}.dropdown.menu .is-dropdown-submenu-parent.is-left-arrow.opens-inner .submenu{right:0;left:auto}.dropdown.menu .is-dropdown-submenu-parent.is-right-arrow.opens-inner .submenu{left:0;right:auto}.dropdown.menu .is-dropdown-submenu-parent.opens-inner .submenu{top:100%}.no-js .dropdown.menu ul{display:none}.dropdown.menu .submenu{display:none;position:absolute;top:0;left:100%;min-width:200px;z-index:1;background:#fefefe;border:1px solid #cacaca}.dropdown.menu .submenu>li{width:100%}.dropdown.menu .submenu.first-sub{top:100%;left:0;right:auto}.dropdown.menu .submenu.js-dropdown-active,.dropdown.menu .submenu:not(.js-dropdown-nohover)>.is-dropdown-submenu-parent:hover>.dropdown.menu .submenu{display:block}.dropdown.menu .is-dropdown-submenu-parent.opens-left .submenu{left:auto;right:100%}.dropdown.menu.align-right .submenu.first-sub{top:100%;left:auto;right:0}.is-dropdown-menu.vertical{width:100px}.is-dropdown-menu.vertical.align-right{float:right}.is-dropdown-menu.vertical>li .submenu{top:0;left:100%}.flex-video{position:relative;height:0;padding-top:1.5625rem;padding-bottom:75%;margin-bottom:1rem;overflow:hidden}.flex-video embed,.flex-video iframe,.flex-video object,.flex-video video{position:absolute;top:0;left:0;width:100%;height:100%}.flex-video.widescreen{padding-bottom:56.25%}.flex-video.vimeo{padding-top:0}.label{display:inline-block;padding:.33333rem .5rem;font-size:.8rem;line-height:1;white-space:nowrap;cursor:default;border-radius:0;background:#2199e8;color:#fefefe}.label.secondary{background:#777;color:#fefefe}.label.success{background:#3adb76;color:#fefefe}.label.alert{background:#ec5840;color:#fefefe}.label.warning{background:#ffae00;color:#fefefe}.media-object{margin-bottom:1rem;display:block}.media-object img{max-width:none}@media screen and (min-width:0em) and (max-width:39.9375em){.media-object.stack-for-small .media-object-section{display:block;padding:0;padding-bottom:1rem}.media-object.stack-for-small .media-object-section img{width:100%}}.media-object-section{display:table-cell;vertical-align:top}.media-object-section:first-child{padding-right:1rem}.media-object-section:last-child:not(+.media-object-section:first-child){padding-left:1rem}.media-object-section.middle{vertical-align:middle}.media-object-section.bottom{vertical-align:bottom}.menu{margin:0;list-style-type:none}.menu>li{display:table-cell;vertical-align:middle}[data-whatinput=mouse] .menu>li{outline:0}.menu>li:not(.menu-text)>a{display:block;padding:.7rem 1rem;line-height:1}.menu a,.menu button,.menu input{margin-bottom:0}.menu>li>a>i,.menu>li>a>img,.menu>li>a>span{vertical-align:middle}.menu>li>a>i,.menu>li>a>img{display:inline-block;margin-right:.25rem}.menu>li{display:table-cell}.menu.vertical>li{display:block}@media screen and (min-width:40em){.menu.medium-horizontal>li{display:table-cell}.menu.medium-vertical>li{display:block}}@media screen and (min-width:64em){.menu.large-horizontal>li{display:table-cell}.menu.large-vertical>li{display:block}}.menu.simple a{padding:0;margin-right:1rem}.menu.align-right>li{float:right}.menu.expanded{display:table;width:100%}.menu.expanded>li:nth-last-child(2):first-child,.menu.expanded>li:nth-last-child(2):first-child~li{width:50%}.menu.expanded>li:nth-last-child(3):first-child,.menu.expanded>li:nth-last-child(3):first-child~li{width:33.33333%}.menu.expanded>li:nth-last-child(4):first-child,.menu.expanded>li:nth-last-child(4):first-child~li{width:25%}.menu.expanded>li:nth-last-child(5):first-child,.menu.expanded>li:nth-last-child(5):first-child~li{width:20%}.menu.expanded>li:nth-last-child(6):first-child,.menu.expanded>li:nth-last-child(6):first-child~li{width:16.66667%}.menu.expanded>li:first-child:last-child{width:100%}.menu.icon-top>li>a{text-align:center}.menu.icon-top>li>a>i,.menu.icon-top>li>a>img{display:block;margin:0 auto .25rem}.menu.nested{margin-left:1rem}.menu-text{font-weight:700;color:inherit;line-height:1;padding-top:0;padding-bottom:0;padding:.7rem 1rem}.no-js [data-responsive-menu] ul{display:none}body,html{height:100%}.off-canvas-wrapper{width:100%;overflow-x:hidden;position:relative;backface-visibility:hidden;-webkit-overflow-scrolling:auto}.off-canvas-wrapper-inner{position:relative;width:100%;transition:transform .5s ease}.off-canvas-wrapper-inner:after,.off-canvas-wrapper-inner:before{content:' ';display:table}.off-canvas-wrapper-inner:after{clear:both}.off-canvas-content{min-height:100%;background:#fefefe;transition:transform .5s ease;backface-visibility:hidden;z-index:1;box-shadow:0 0 10px hsla(0,0%,4%,.5)}.js-off-canvas-exit{display:none;position:absolute;top:0;left:0;width:100%;height:100%;background:hsla(0,0%,100%,.25);cursor:pointer;transition:background .5s ease}.is-off-canvas-open .js-off-canvas-exit{display:block}.off-canvas{position:absolute;background:#e6e6e6;z-index:-1;max-height:100%;overflow-y:auto;-ms-transform:translateX(0);transform:translateX(0)}[data-whatinput=mouse] .off-canvas{outline:0}.off-canvas.position-left{left:-250px;top:0;width:250px}.is-open-left{-ms-transform:translateX(250px);transform:translateX(250px)}.off-canvas.position-right{right:-250px;top:0;width:250px}.is-open-right{-ms-transform:translateX(-250px);transform:translateX(-250px)}@media screen and (min-width:40em){.position-left.reveal-for-medium{left:0;z-index:auto;position:fixed}.position-left.reveal-for-medium~.off-canvas-content{margin-left:250px}.position-right.reveal-for-medium{right:0;z-index:auto;position:fixed}.position-right.reveal-for-medium~.off-canvas-content{margin-right:250px}}@media screen and (min-width:64em){.position-left.reveal-for-large{left:0;z-index:auto;position:fixed}.position-left.reveal-for-large~.off-canvas-content{margin-left:250px}.position-right.reveal-for-large{right:0;z-index:auto;position:fixed}.position-right.reveal-for-large~.off-canvas-content{margin-right:250px}}.orbit,.orbit-container{position:relative}.orbit-container{margin:0;overflow:hidden;list-style:none}.orbit-slide{width:100%;max-height:100%}.orbit-slide.no-motionui.is-active{top:0;left:0}.orbit-figure{margin:0}.orbit-image{margin:0;width:100%;max-width:100%}.orbit-caption{bottom:0;width:100%;margin-bottom:0;background-color:hsla(0,0%,4%,.5)}.orbit-caption,.orbit-next,.orbit-previous{position:absolute;padding:1rem;color:#fefefe}.orbit-next,.orbit-previous{top:50%;-ms-transform:translateY(-50%);transform:translateY(-50%);z-index:10}[data-whatinput=mouse] .orbit-next,[data-whatinput=mouse] .orbit-previous{outline:0}.orbit-next:active,.orbit-next:focus,.orbit-next:hover,.orbit-previous:active,.orbit-previous:focus,.orbit-previous:hover{background-color:hsla(0,0%,4%,.5)}.orbit-previous{left:0}.orbit-next{left:auto;right:0}.orbit-bullets{position:relative;margin-top:.8rem;margin-bottom:.8rem;text-align:center}[data-whatinput=mouse] .orbit-bullets{outline:0}.orbit-bullets button{width:1.2rem;height:1.2rem;margin:.1rem;background-color:#cacaca;border-radius:50%}.orbit-bullets button.is-active,.orbit-bullets button:hover{background-color:#8a8a8a}.pagination{margin-left:0;margin-bottom:1rem}.pagination:after,.pagination:before{content:' ';display:table}.pagination:after{clear:both}.pagination li{font-size:.875rem;margin-right:.0625rem;display:none;border-radius:0}.pagination li:first-child,.pagination li:last-child{display:inline-block}@media screen and (min-width:40em){.pagination li{display:inline-block}}.pagination a,.pagination button{color:#0a0a0a;display:block;padding:.1875rem .625rem;border-radius:0}.pagination a:hover,.pagination button:hover{background:#e6e6e6}.pagination .current{padding:.1875rem .625rem;background:#2199e8;color:#fefefe;cursor:default}.pagination .disabled{padding:.1875rem .625rem;color:#cacaca;cursor:default}.pagination .disabled:hover{background:transparent}.pagination .ellipsis:after{content:'…';padding:.1875rem .625rem;color:#0a0a0a}.pagination-previous.disabled:before,.pagination-previous a:before{content:'«';display:inline-block;margin-right:.5rem}.pagination-next.disabled:after,.pagination-next a:after{content:'»';display:inline-block;margin-left:.5rem}.progress{background-color:#cacaca;height:1rem;margin-bottom:1rem;border-radius:0}.progress.primary .progress-meter{background-color:#2199e8}.progress.secondary .progress-meter{background-color:#777}.progress.success .progress-meter{background-color:#3adb76}.progress.alert .progress-meter{background-color:#ec5840}.progress.warning .progress-meter{background-color:#ffae00}.progress-meter{position:relative;display:block;width:0;height:100%;background-color:#2199e8;border-radius:0}.progress-meter .progress-meter-text{position:absolute;top:50%;left:50%;-ms-transform:translate(-50%,-50%);transform:translate(-50%,-50%);margin:0;font-size:.75rem;font-weight:700;color:#fefefe;white-space:nowrap}.slider{position:relative;height:.5rem;margin-top:1.25rem;margin-bottom:2.25rem;background-color:#e6e6e6;cursor:pointer;-webkit-user-select:none;-moz-user-select:none;-ms-user-select:none;user-select:none;-ms-touch-action:none;touch-action:none}.slider-fill{position:absolute;top:0;left:0;display:inline-block;max-width:100%;height:.5rem;background-color:#cacaca;transition:all .2s ease-in-out}.slider-fill.is-dragging{transition:all 0s linear}.slider-handle{top:50%;-ms-transform:translateY(-50%);transform:translateY(-50%);position:absolute;left:0;z-index:1;display:inline-block;width:1.4rem;height:1.4rem;background-color:#2199e8;transition:all .2s ease-in-out;-ms-touch-action:manipulation;touch-action:manipulation;border-radius:0}[data-whatinput=mouse] .slider-handle{outline:0}.slider-handle:hover{background-color:#1583cc}.slider-handle.is-dragging{transition:all 0s linear}.slider.disabled,.slider[disabled]{opacity:.25;cursor:not-allowed}.slider.vertical{display:inline-block;width:.5rem;height:12.5rem;margin:0 1.25rem;-ms-transform:scaleY(-1);transform:scaleY(-1)}.slider.vertical .slider-fill{top:0;width:.5rem;max-height:100%}.slider.vertical .slider-handle{position:absolute;top:0;left:50%;width:1.4rem;height:1.4rem;-ms-transform:translateX(-50%);transform:translateX(-50%)}.sticky-container{position:relative}.sticky{position:absolute;z-index:0;transform:translateZ(0)}.sticky.is-stuck{position:fixed;z-index:5}.sticky.is-stuck.is-at-top{top:0}.sticky.is-stuck.is-at-bottom{bottom:0}.sticky.is-anchored{position:absolute;left:auto;right:auto}.sticky.is-anchored.is-at-bottom{bottom:0}body.is-reveal-open{overflow:hidden}.reveal-overlay{display:none;position:fixed;top:0;bottom:0;left:0;right:0;z-index:1005;background-color:hsla(0,0%,4%,.45);overflow-y:scroll}.reveal{display:none;z-index:1006;padding:1rem;border:1px solid #cacaca;margin:100px auto 0;background-color:#fefefe;border-radius:0;position:absolute;overflow-y:auto}[data-whatinput=mouse] .reveal{outline:0}@media screen and (min-width:40em){.reveal{min-height:0}}.reveal .column,.reveal .columns{min-width:0}.reveal>:last-child{margin-bottom:0}@media screen and (min-width:40em){.reveal{width:600px;max-width:62.5rem}}.reveal.collapse{padding:0}@media screen and (min-width:40em){.reveal .reveal{left:auto;right:auto;margin:0 auto}}@media screen and (min-width:40em){.reveal.tiny{width:30%;max-width:62.5rem}}@media screen and (min-width:40em){.reveal.small{width:50%;max-width:62.5rem}}@media screen and (min-width:40em){.reveal.large{width:90%;max-width:62.5rem}}.reveal.full{top:0;left:0;width:100%;height:100%;height:100vh;min-height:100vh;max-width:none;margin-left:0;border:none}.switch{margin-bottom:1rem;outline:0;position:relative;-webkit-user-select:none;-moz-user-select:none;-ms-user-select:none;user-select:none;color:#fefefe;font-weight:700;font-size:.875rem}.switch-input{opacity:0;position:absolute}.switch-paddle{background:#cacaca;cursor:pointer;display:block;position:relative;width:4rem;height:2rem;transition:all .25s ease-out;border-radius:0;color:inherit;font-weight:inherit}input+.switch-paddle{margin:0}.switch-paddle:after{background:#fefefe;content:'';display:block;position:absolute;height:1.5rem;left:.25rem;top:.25rem;width:1.5rem;transition:all .25s ease-out;transform:translateZ(0);border-radius:0}input:checked~.switch-paddle{background:#2199e8}input:checked~.switch-paddle:after{left:2.25rem}[data-whatinput=mouse] input:focus~.switch-paddle{outline:0}.switch-active,.switch-inactive{position:absolute;top:50%;-ms-transform:translateY(-50%);transform:translateY(-50%)}.switch-active{left:8%;display:none}input:checked+label>.switch-active{display:block}.switch-inactive{right:15%}input:checked+label>.switch-inactive{display:none}.switch.tiny .switch-paddle{width:3rem;height:1.5rem;font-size:.625rem}.switch.tiny .switch-paddle:after{width:1rem;height:1rem}.switch.tiny input:checked~.switch-paddle:after{left:1.75rem}.switch.small .switch-paddle{width:3.5rem;height:1.75rem;font-size:.75rem}.switch.small .switch-paddle:after{width:1.25rem;height:1.25rem}.switch.small input:checked~.switch-paddle:after{left:2rem}.switch.large .switch-paddle{width:5rem;height:2.5rem;font-size:1rem}.switch.large .switch-paddle:after{width:2rem;height:2rem}.switch.large input:checked~.switch-paddle:after{left:2.75rem}table{margin-bottom:1rem;border-radius:0}tbody,tfoot,thead{border:1px solid #f1f1f1;background-color:#fefefe}caption{font-weight:700;padding:.5rem .625rem .625rem}tfoot,thead{background:#f8f8f8;color:#0a0a0a}tfoot tr,thead tr{background:transparent}tfoot td,tfoot th,thead td,thead th{padding:.5rem .625rem .625rem;font-weight:700;text-align:left}tbody tr:nth-child(even){background-color:#f1f1f1}tbody td,tbody th{padding:.5rem .625rem .625rem}@media screen and (max-width:63.9375em){table.stack tfoot,table.stack thead{display:none}table.stack td,table.stack th,table.stack tr{display:block}table.stack td{border-top:0}}table.scroll{display:block;width:100%;overflow-y:scroll}table.hover tr:hover{background-color:#f9f9f9}table.hover tr:nth-of-type(even):hover{background-color:#ececec}.tabs{margin:0;list-style-type:none;background:#fefefe;border:1px solid #e6e6e6}.tabs:after,.tabs:before{content:' ';display:table}.tabs:after{clear:both}.tabs.simple>li>a{padding:0}.tabs.simple>li>a:hover{background:transparent}.tabs.vertical>li{width:auto;float:none;display:block}.tabs.primary{background:#2199e8}.tabs.primary>li>a{color:#fefefe}.tabs.primary>li>a:focus,.tabs.primary>li>a:hover{background:#1893e4}.tabs-title{float:left}.tabs-title>a{display:block;padding:1.25rem 1.5rem;line-height:1;font-size:12px;color:#2199e8}.tabs-title>a:hover{background:#fefefe}.tabs-title>a:focus,.tabs-title>a[aria-selected=true]{background:#e6e6e6}.tabs-content{background:#fefefe;transition:all .5s ease;border:1px solid #e6e6e6;border-top:0}.tabs-content.vertical{border:1px solid #e6e6e6;border-left:0}.tabs-panel{display:none;padding:1rem}.tabs-panel.is-active{display:block}.thumbnail{border:4px solid #fefefe;box-shadow:0 0 0 1px hsla(0,0%,4%,.2);display:inline-block;line-height:0;max-width:100%;transition:box-shadow .2s ease-out;border-radius:0;margin-bottom:1rem}.thumbnail:focus,.thumbnail:hover{box-shadow:0 0 6px 1px rgba(33,153,232,.5)}.title-bar{background:#0a0a0a;color:#fefefe;padding:.5rem}.title-bar:after,.title-bar:before{content:' ';display:table}.title-bar:after{clear:both}.title-bar .menu-icon{margin-left:.25rem;margin-right:.5rem}.title-bar-left{float:left}.title-bar-right{float:right;text-align:right}.title-bar-title{font-weight:700}.menu-icon,.title-bar-title{vertical-align:middle;display:inline-block}.menu-icon{position:relative;cursor:pointer;width:20px;height:16px}.menu-icon:after{content:'';position:absolute;display:block;width:100%;height:2px;background:#fefefe;top:0;left:0;box-shadow:0 7px 0 #fefefe,0 14px 0 #fefefe}.menu-icon:hover:after{background:#cacaca;box-shadow:0 7px 0 #cacaca,0 14px 0 #cacaca}.has-tip{border-bottom:1px dotted #8a8a8a;font-weight:700;position:relative;display:inline-block;cursor:help}.tooltip{background-color:#0a0a0a;color:#fefefe;font-size:80%;padding:.75rem;position:absolute;z-index:10;top:calc(100% + .6495rem);max-width:10rem!important;border-radius:0}.tooltip:before{border:.75rem inset;border-color:transparent transparent #0a0a0a;border-bottom-style:solid;bottom:100%;position:absolute;left:50%;-ms-transform:translateX(-50%);transform:translateX(-50%)}.tooltip.top:before,.tooltip:before{content:'';display:block;width:0;height:0}.tooltip.top:before{border:.75rem inset;border-color:#0a0a0a transparent transparent;border-top-style:solid;top:100%;bottom:auto}.tooltip.left:before{border:.75rem inset;border-color:transparent transparent transparent #0a0a0a;border-left-style:solid;left:100%}.tooltip.left:before,.tooltip.right:before{content:'';display:block;width:0;height:0;bottom:auto;top:50%;-ms-transform:translateY(-50%);transform:translateY(-50%)}.tooltip.right:before{border:.75rem inset;border-color:transparent #0a0a0a transparent transparent;border-right-style:solid;left:auto;right:100%}.top-bar{padding:.5rem}.top-bar:after,.top-bar:before{content:' ';display:table}.top-bar:after{clear:both}.top-bar,.top-bar ul{background-color:#eee}.top-bar a{color:#fff}.top-bar input{width:200px;margin-right:1rem}.top-bar input.button{width:auto}.stacked-for-small .top-bar-left,.stacked-for-small .top-bar-right{width:100%}@media screen and (max-width:63.9375em){.stacked-for-medium .top-bar-left,.stacked-for-medium .top-bar-right{width:100%}}@media screen and (max-width:74.9375em){.stacked-for-large .top-bar-left,.stacked-for-large .top-bar-right{width:100%}}.top-bar-left,.top-bar-right{width:100%}.top-bar-left{float:left}.top-bar-right{float:right} /*! * Font Awesome 4.5.0 by @davegandy - http://fontawesome.io - @fontawesome * License - http://fontawesome.io/license (Font: SIL OFL 1.1, CSS: MIT License) - */@font-face{font-family:FontAwesome;src:url(/fonts/fontawesome-webfont.eot?v=4.5.0);src:url(/fonts/fontawesome-webfont.eot?#iefix&v=4.5.0) format("embedded-opentype"),url(/fonts/fontawesome-webfont.woff2?v=4.5.0) format("woff2"),url(/fonts/fontawesome-webfont.woff?v=4.5.0) format("woff"),url(/fonts/fontawesome-webfont.ttf?v=4.5.0) format("truetype"),url(/fonts/fontawesome-webfont.svg?v=4.5.0#fontawesomeregular) format("svg");font-weight:400;font-style:normal}.fa{display:inline-block;font:normal normal normal 14px/1 FontAwesome;font-size:inherit;text-rendering:auto;-webkit-font-smoothing:antialiased;-moz-osx-font-smoothing:grayscale}.fa-lg{font-size:1.33333em;line-height:.75em;vertical-align:-15%}.fa-2x{font-size:2em}.fa-3x{font-size:3em}.fa-4x{font-size:4em}.fa-5x{font-size:5em}.fa-fw{width:1.28571em;text-align:center}.fa-ul{padding-left:0;margin-left:2.14286em;list-style-type:none}.fa-ul>li{position:relative}.fa-li{position:absolute;left:-2.14286em;width:2.14286em;top:.14286em;text-align:center}.fa-li.fa-lg{left:-1.85714em}.fa-border{padding:.2em .25em .15em;border:.08em solid #eee;border-radius:.1em}.fa-pull-left{float:left}.fa-pull-right{float:right}.fa.fa-pull-left{margin-right:.3em}.fa.fa-pull-right{margin-left:.3em}.pull-right{float:right}.pull-left{float:left}.fa.pull-left{margin-right:.3em}.fa.pull-right{margin-left:.3em}.fa-spin{animation:a 2s infinite linear}.fa-pulse{animation:a 1s infinite steps(8)}@keyframes a{0%{transform:rotate(0deg)}to{transform:rotate(359deg)}}.fa-rotate-90{filter:progid:DXImageTransform.Microsoft.BasicImage(rotation=1);-ms-transform:rotate(90deg);transform:rotate(90deg)}.fa-rotate-180{filter:progid:DXImageTransform.Microsoft.BasicImage(rotation=2);-ms-transform:rotate(180deg);transform:rotate(180deg)}.fa-rotate-270{filter:progid:DXImageTransform.Microsoft.BasicImage(rotation=3);-ms-transform:rotate(270deg);transform:rotate(270deg)}.fa-flip-horizontal{filter:progid:DXImageTransform.Microsoft.BasicImage(rotation=0);-ms-transform:scaleX(-1);transform:scaleX(-1)}.fa-flip-vertical{filter:progid:DXImageTransform.Microsoft.BasicImage(rotation=2);-ms-transform:scaleY(-1);transform:scaleY(-1)}:root .fa-flip-horizontal,:root .fa-flip-vertical,:root .fa-rotate-90,:root .fa-rotate-180,:root .fa-rotate-270{-webkit-filter:none;filter:none}.fa-stack{position:relative;display:inline-block;width:2em;height:2em;line-height:2em;vertical-align:middle}.fa-stack-1x,.fa-stack-2x{position:absolute;left:0;width:100%;text-align:center}.fa-stack-1x{line-height:inherit}.fa-stack-2x{font-size:2em}.fa-inverse{color:#fff}.fa-glass:before{content:""}.fa-music:before{content:"ï€"}.fa-search:before{content:""}.fa-envelope-o:before{content:""}.fa-heart:before{content:""}.fa-star:before{content:""}.fa-star-o:before{content:""}.fa-user:before{content:""}.fa-film:before{content:""}.fa-th-large:before{content:""}.fa-th:before{content:""}.fa-th-list:before{content:""}.fa-check:before{content:""}.fa-close:before,.fa-remove:before,.fa-times:before{content:"ï€"}.fa-search-plus:before{content:""}.fa-search-minus:before{content:"ï€"}.fa-power-off:before{content:""}.fa-signal:before{content:""}.fa-cog:before,.fa-gear:before{content:""}.fa-trash-o:before{content:""}.fa-home:before{content:""}.fa-file-o:before{content:""}.fa-clock-o:before{content:""}.fa-road:before{content:""}.fa-download:before{content:""}.fa-arrow-circle-o-down:before{content:""}.fa-arrow-circle-o-up:before{content:""}.fa-inbox:before{content:""}.fa-play-circle-o:before{content:"ï€"}.fa-repeat:before,.fa-rotate-right:before{content:""}.fa-refresh:before{content:""}.fa-list-alt:before{content:""}.fa-lock:before{content:""}.fa-flag:before{content:""}.fa-headphones:before{content:""}.fa-volume-off:before{content:""}.fa-volume-down:before{content:""}.fa-volume-up:before{content:""}.fa-qrcode:before{content:""}.fa-barcode:before{content:""}.fa-tag:before{content:""}.fa-tags:before{content:""}.fa-book:before{content:"ï€"}.fa-bookmark:before{content:""}.fa-print:before{content:""}.fa-camera:before{content:""}.fa-font:before{content:""}.fa-bold:before{content:""}.fa-italic:before{content:""}.fa-text-height:before{content:""}.fa-text-width:before{content:""}.fa-align-left:before{content:""}.fa-align-center:before{content:""}.fa-align-right:before{content:""}.fa-align-justify:before{content:""}.fa-list:before{content:""}.fa-dedent:before,.fa-outdent:before{content:""}.fa-indent:before{content:""}.fa-video-camera:before{content:""}.fa-image:before,.fa-photo:before,.fa-picture-o:before{content:""}.fa-pencil:before{content:"ï€"}.fa-map-marker:before{content:"ï"}.fa-adjust:before{content:"ï‚"}.fa-tint:before{content:"ïƒ"}.fa-edit:before,.fa-pencil-square-o:before{content:"ï„"}.fa-share-square-o:before{content:"ï…"}.fa-check-square-o:before{content:"ï†"}.fa-arrows:before{content:"ï‡"}.fa-step-backward:before{content:"ïˆ"}.fa-fast-backward:before{content:"ï‰"}.fa-backward:before{content:"ïŠ"}.fa-play:before{content:"ï‹"}.fa-pause:before{content:"ïŒ"}.fa-stop:before{content:"ï"}.fa-forward:before{content:"ïŽ"}.fa-fast-forward:before{content:"ï"}.fa-step-forward:before{content:"ï‘"}.fa-eject:before{content:"ï’"}.fa-chevron-left:before{content:"ï“"}.fa-chevron-right:before{content:"ï”"}.fa-plus-circle:before{content:"ï•"}.fa-minus-circle:before{content:"ï–"}.fa-times-circle:before{content:"ï—"}.fa-check-circle:before{content:"ï˜"}.fa-question-circle:before{content:"ï™"}.fa-info-circle:before{content:"ïš"}.fa-crosshairs:before{content:"ï›"}.fa-times-circle-o:before{content:"ïœ"}.fa-check-circle-o:before{content:"ï"}.fa-ban:before{content:"ïž"}.fa-arrow-left:before{content:"ï "}.fa-arrow-right:before{content:"ï¡"}.fa-arrow-up:before{content:"ï¢"}.fa-arrow-down:before{content:"ï£"}.fa-mail-forward:before,.fa-share:before{content:"ï¤"}.fa-expand:before{content:"ï¥"}.fa-compress:before{content:"ï¦"}.fa-plus:before{content:"ï§"}.fa-minus:before{content:"ï¨"}.fa-asterisk:before{content:"ï©"}.fa-exclamation-circle:before{content:"ïª"}.fa-gift:before{content:"ï«"}.fa-leaf:before{content:"ï¬"}.fa-fire:before{content:"ï"}.fa-eye:before{content:"ï®"}.fa-eye-slash:before{content:"ï°"}.fa-exclamation-triangle:before,.fa-warning:before{content:"ï±"}.fa-plane:before{content:"ï²"}.fa-calendar:before{content:"ï³"}.fa-random:before{content:"ï´"}.fa-comment:before{content:"ïµ"}.fa-magnet:before{content:"ï¶"}.fa-chevron-up:before{content:"ï·"}.fa-chevron-down:before{content:"ï¸"}.fa-retweet:before{content:"ï¹"}.fa-shopping-cart:before{content:"ïº"}.fa-folder:before{content:"ï»"}.fa-folder-open:before{content:"ï¼"}.fa-arrows-v:before{content:"ï½"}.fa-arrows-h:before{content:"ï¾"}.fa-bar-chart-o:before,.fa-bar-chart:before{content:"ï‚€"}.fa-twitter-square:before{content:"ï‚"}.fa-facebook-square:before{content:"ï‚‚"}.fa-camera-retro:before{content:""}.fa-key:before{content:"ï‚„"}.fa-cogs:before,.fa-gears:before{content:"ï‚…"}.fa-comments:before{content:""}.fa-thumbs-o-up:before{content:""}.fa-thumbs-o-down:before{content:""}.fa-star-half:before{content:""}.fa-heart-o:before{content:"ï‚Š"}.fa-sign-out:before{content:"ï‚‹"}.fa-linkedin-square:before{content:"ï‚Œ"}.fa-thumb-tack:before{content:"ï‚"}.fa-external-link:before{content:"ï‚Ž"}.fa-sign-in:before{content:"ï‚"}.fa-trophy:before{content:"ï‚‘"}.fa-github-square:before{content:"ï‚’"}.fa-upload:before{content:"ï‚“"}.fa-lemon-o:before{content:"ï‚”"}.fa-phone:before{content:"ï‚•"}.fa-square-o:before{content:"ï‚–"}.fa-bookmark-o:before{content:"ï‚—"}.fa-phone-square:before{content:""}.fa-twitter:before{content:"ï‚™"}.fa-facebook-f:before,.fa-facebook:before{content:"ï‚š"}.fa-github:before{content:"ï‚›"}.fa-unlock:before{content:"ï‚œ"}.fa-credit-card:before{content:"ï‚"}.fa-feed:before,.fa-rss:before{content:"ï‚ž"}.fa-hdd-o:before{content:"ï‚ "}.fa-bullhorn:before{content:"ï‚¡"}.fa-bell:before{content:""}.fa-certificate:before{content:"ï‚£"}.fa-hand-o-right:before{content:""}.fa-hand-o-left:before{content:"ï‚¥"}.fa-hand-o-up:before{content:""}.fa-hand-o-down:before{content:""}.fa-arrow-circle-left:before{content:""}.fa-arrow-circle-right:before{content:"ï‚©"}.fa-arrow-circle-up:before{content:""}.fa-arrow-circle-down:before{content:"ï‚«"}.fa-globe:before{content:""}.fa-wrench:before{content:"ï‚"}.fa-tasks:before{content:"ï‚®"}.fa-filter:before{content:"ï‚°"}.fa-briefcase:before{content:""}.fa-arrows-alt:before{content:""}.fa-group:before,.fa-users:before{content:""}.fa-chain:before,.fa-link:before{content:"ïƒ"}.fa-cloud:before{content:""}.fa-flask:before{content:""}.fa-cut:before,.fa-scissors:before{content:""}.fa-copy:before,.fa-files-o:before{content:""}.fa-paperclip:before{content:""}.fa-floppy-o:before,.fa-save:before{content:""}.fa-square:before{content:""}.fa-bars:before,.fa-navicon:before,.fa-reorder:before{content:""}.fa-list-ul:before{content:""}.fa-list-ol:before{content:""}.fa-strikethrough:before{content:""}.fa-underline:before{content:"ïƒ"}.fa-table:before{content:""}.fa-magic:before{content:"ïƒ"}.fa-truck:before{content:""}.fa-pinterest:before{content:""}.fa-pinterest-square:before{content:""}.fa-google-plus-square:before{content:""}.fa-google-plus:before{content:""}.fa-money:before{content:""}.fa-caret-down:before{content:""}.fa-caret-up:before{content:""}.fa-caret-left:before{content:""}.fa-caret-right:before{content:""}.fa-columns:before{content:""}.fa-sort:before,.fa-unsorted:before{content:""}.fa-sort-desc:before,.fa-sort-down:before{content:"ïƒ"}.fa-sort-asc:before,.fa-sort-up:before{content:""}.fa-envelope:before{content:"ïƒ "}.fa-linkedin:before{content:""}.fa-rotate-left:before,.fa-undo:before{content:""}.fa-gavel:before,.fa-legal:before{content:""}.fa-dashboard:before,.fa-tachometer:before{content:""}.fa-comment-o:before{content:""}.fa-comments-o:before{content:""}.fa-bolt:before,.fa-flash:before{content:""}.fa-sitemap:before{content:""}.fa-umbrella:before{content:""}.fa-clipboard:before,.fa-paste:before{content:""}.fa-lightbulb-o:before{content:""}.fa-exchange:before{content:""}.fa-cloud-download:before{content:"ïƒ"}.fa-cloud-upload:before{content:""}.fa-user-md:before{content:""}.fa-stethoscope:before{content:""}.fa-suitcase:before{content:""}.fa-bell-o:before{content:"ï‚¢"}.fa-coffee:before{content:""}.fa-cutlery:before{content:""}.fa-file-text-o:before{content:""}.fa-building-o:before{content:""}.fa-hospital-o:before{content:""}.fa-ambulance:before{content:""}.fa-medkit:before{content:""}.fa-fighter-jet:before{content:""}.fa-beer:before{content:""}.fa-h-square:before{content:""}.fa-plus-square:before{content:""}.fa-angle-double-left:before{content:"ï„€"}.fa-angle-double-right:before{content:"ï„"}.fa-angle-double-up:before{content:"ï„‚"}.fa-angle-double-down:before{content:""}.fa-angle-left:before{content:"ï„„"}.fa-angle-right:before{content:"ï„…"}.fa-angle-up:before{content:""}.fa-angle-down:before{content:""}.fa-desktop:before{content:""}.fa-laptop:before{content:""}.fa-tablet:before{content:"ï„Š"}.fa-mobile-phone:before,.fa-mobile:before{content:"ï„‹"}.fa-circle-o:before{content:"ï„Œ"}.fa-quote-left:before{content:"ï„"}.fa-quote-right:before{content:"ï„Ž"}.fa-spinner:before{content:"ï„"}.fa-circle:before{content:"ï„‘"}.fa-mail-reply:before,.fa-reply:before{content:"ï„’"}.fa-github-alt:before{content:"ï„“"}.fa-folder-o:before{content:"ï„”"}.fa-folder-open-o:before{content:"ï„•"}.fa-smile-o:before{content:""}.fa-frown-o:before{content:"ï„™"}.fa-meh-o:before{content:"ï„š"}.fa-gamepad:before{content:"ï„›"}.fa-keyboard-o:before{content:"ï„œ"}.fa-flag-o:before{content:"ï„"}.fa-flag-checkered:before{content:"ï„ž"}.fa-terminal:before{content:"ï„ "}.fa-code:before{content:"ï„¡"}.fa-mail-reply-all:before,.fa-reply-all:before{content:"ï„¢"}.fa-star-half-empty:before,.fa-star-half-full:before,.fa-star-half-o:before{content:"ï„£"}.fa-location-arrow:before{content:""}.fa-crop:before{content:"ï„¥"}.fa-code-fork:before{content:""}.fa-chain-broken:before,.fa-unlink:before{content:""}.fa-question:before{content:""}.fa-info:before{content:"ï„©"}.fa-exclamation:before{content:""}.fa-superscript:before{content:"ï„«"}.fa-subscript:before{content:""}.fa-eraser:before{content:"ï„"}.fa-puzzle-piece:before{content:"ï„®"}.fa-microphone:before{content:"ï„°"}.fa-microphone-slash:before{content:""}.fa-shield:before{content:""}.fa-calendar-o:before{content:""}.fa-fire-extinguisher:before{content:"ï„´"}.fa-rocket:before{content:""}.fa-maxcdn:before{content:""}.fa-chevron-circle-left:before{content:"ï„·"}.fa-chevron-circle-right:before{content:""}.fa-chevron-circle-up:before{content:""}.fa-chevron-circle-down:before{content:""}.fa-html5:before{content:"ï„»"}.fa-css3:before{content:""}.fa-anchor:before{content:""}.fa-unlock-alt:before{content:""}.fa-bullseye:before{content:"ï…€"}.fa-ellipsis-h:before{content:"ï…"}.fa-ellipsis-v:before{content:"ï…‚"}.fa-rss-square:before{content:"ï…ƒ"}.fa-play-circle:before{content:"ï…„"}.fa-ticket:before{content:"ï……"}.fa-minus-square:before{content:"ï…†"}.fa-minus-square-o:before{content:"ï…‡"}.fa-level-up:before{content:"ï…ˆ"}.fa-level-down:before{content:"ï…‰"}.fa-check-square:before{content:"ï…Š"}.fa-pencil-square:before{content:"ï…‹"}.fa-external-link-square:before{content:"ï…Œ"}.fa-share-square:before{content:"ï…"}.fa-compass:before{content:"ï…Ž"}.fa-caret-square-o-down:before,.fa-toggle-down:before{content:"ï…"}.fa-caret-square-o-up:before,.fa-toggle-up:before{content:"ï…‘"}.fa-caret-square-o-right:before,.fa-toggle-right:before{content:"ï…’"}.fa-eur:before,.fa-euro:before{content:"ï…“"}.fa-gbp:before{content:"ï…”"}.fa-dollar:before,.fa-usd:before{content:"ï…•"}.fa-inr:before,.fa-rupee:before{content:"ï…–"}.fa-cny:before,.fa-jpy:before,.fa-rmb:before,.fa-yen:before{content:"ï…—"}.fa-rouble:before,.fa-rub:before,.fa-ruble:before{content:"ï…˜"}.fa-krw:before,.fa-won:before{content:"ï…™"}.fa-bitcoin:before,.fa-btc:before{content:"ï…š"}.fa-file:before{content:"ï…›"}.fa-file-text:before{content:"ï…œ"}.fa-sort-alpha-asc:before{content:"ï…"}.fa-sort-alpha-desc:before{content:"ï…ž"}.fa-sort-amount-asc:before{content:"ï… "}.fa-sort-amount-desc:before{content:"ï…¡"}.fa-sort-numeric-asc:before{content:"ï…¢"}.fa-sort-numeric-desc:before{content:"ï…£"}.fa-thumbs-up:before{content:"ï…¤"}.fa-thumbs-down:before{content:"ï…¥"}.fa-youtube-square:before{content:"ï…¦"}.fa-youtube:before{content:"ï…§"}.fa-xing:before{content:"ï…¨"}.fa-xing-square:before{content:"ï…©"}.fa-youtube-play:before{content:"ï…ª"}.fa-dropbox:before{content:"ï…«"}.fa-stack-overflow:before{content:"ï…¬"}.fa-instagram:before{content:"ï…"}.fa-flickr:before{content:"ï…®"}.fa-adn:before{content:"ï…°"}.fa-bitbucket:before{content:"ï…±"}.fa-bitbucket-square:before{content:"ï…²"}.fa-tumblr:before{content:"ï…³"}.fa-tumblr-square:before{content:"ï…´"}.fa-long-arrow-down:before{content:"ï…µ"}.fa-long-arrow-up:before{content:"ï…¶"}.fa-long-arrow-left:before{content:"ï…·"}.fa-long-arrow-right:before{content:"ï…¸"}.fa-apple:before{content:"ï…¹"}.fa-windows:before{content:"ï…º"}.fa-android:before{content:"ï…»"}.fa-linux:before{content:"ï…¼"}.fa-dribbble:before{content:"ï…½"}.fa-skype:before{content:"ï…¾"}.fa-foursquare:before{content:""}.fa-trello:before{content:"ï†"}.fa-female:before{content:""}.fa-male:before{content:""}.fa-gittip:before,.fa-gratipay:before{content:""}.fa-sun-o:before{content:""}.fa-moon-o:before{content:""}.fa-archive:before{content:""}.fa-bug:before{content:""}.fa-vk:before{content:""}.fa-weibo:before{content:""}.fa-renren:before{content:""}.fa-pagelines:before{content:""}.fa-stack-exchange:before{content:"ï†"}.fa-arrow-circle-o-right:before{content:""}.fa-arrow-circle-o-left:before{content:"ï†"}.fa-caret-square-o-left:before,.fa-toggle-left:before{content:""}.fa-dot-circle-o:before{content:""}.fa-wheelchair:before{content:""}.fa-vimeo-square:before{content:""}.fa-try:before,.fa-turkish-lira:before{content:""}.fa-plus-square-o:before{content:""}.fa-space-shuttle:before{content:""}.fa-slack:before{content:""}.fa-envelope-square:before{content:""}.fa-wordpress:before{content:""}.fa-openid:before{content:""}.fa-bank:before,.fa-institution:before,.fa-university:before{content:""}.fa-graduation-cap:before,.fa-mortar-board:before{content:"ï†"}.fa-yahoo:before{content:""}.fa-google:before{content:"ï† "}.fa-reddit:before{content:""}.fa-reddit-square:before{content:""}.fa-stumbleupon-circle:before{content:""}.fa-stumbleupon:before{content:""}.fa-delicious:before{content:""}.fa-digg:before{content:""}.fa-pied-piper:before{content:""}.fa-pied-piper-alt:before{content:""}.fa-drupal:before{content:""}.fa-joomla:before{content:""}.fa-language:before{content:""}.fa-fax:before{content:""}.fa-building:before{content:"ï†"}.fa-child:before{content:""}.fa-paw:before{content:""}.fa-spoon:before{content:""}.fa-cube:before{content:""}.fa-cubes:before{content:""}.fa-behance:before{content:""}.fa-behance-square:before{content:""}.fa-steam:before{content:""}.fa-steam-square:before{content:""}.fa-recycle:before{content:""}.fa-automobile:before,.fa-car:before{content:""}.fa-cab:before,.fa-taxi:before{content:""}.fa-tree:before{content:""}.fa-spotify:before{content:""}.fa-deviantart:before{content:""}.fa-soundcloud:before{content:""}.fa-database:before{content:""}.fa-file-pdf-o:before{content:"ï‡"}.fa-file-word-o:before{content:""}.fa-file-excel-o:before{content:""}.fa-file-powerpoint-o:before{content:""}.fa-file-image-o:before,.fa-file-photo-o:before,.fa-file-picture-o:before{content:""}.fa-file-archive-o:before,.fa-file-zip-o:before{content:""}.fa-file-audio-o:before,.fa-file-sound-o:before{content:""}.fa-file-movie-o:before,.fa-file-video-o:before{content:""}.fa-file-code-o:before{content:""}.fa-vine:before{content:""}.fa-codepen:before{content:""}.fa-jsfiddle:before{content:""}.fa-life-bouy:before,.fa-life-buoy:before,.fa-life-ring:before,.fa-life-saver:before,.fa-support:before{content:"ï‡"}.fa-circle-o-notch:before{content:""}.fa-ra:before,.fa-rebel:before{content:"ï‡"}.fa-empire:before,.fa-ge:before{content:""}.fa-git-square:before{content:""}.fa-git:before{content:""}.fa-hacker-news:before,.fa-y-combinator-square:before,.fa-yc-square:before{content:""}.fa-tencent-weibo:before{content:""}.fa-qq:before{content:""}.fa-wechat:before,.fa-weixin:before{content:""}.fa-paper-plane:before,.fa-send:before{content:""}.fa-paper-plane-o:before,.fa-send-o:before{content:""}.fa-history:before{content:""}.fa-circle-thin:before{content:""}.fa-header:before{content:""}.fa-paragraph:before{content:"ï‡"}.fa-sliders:before{content:""}.fa-share-alt:before{content:"ï‡ "}.fa-share-alt-square:before{content:""}.fa-bomb:before{content:""}.fa-futbol-o:before,.fa-soccer-ball-o:before{content:""}.fa-tty:before{content:""}.fa-binoculars:before{content:""}.fa-plug:before{content:""}.fa-slideshare:before{content:""}.fa-twitch:before{content:""}.fa-yelp:before{content:""}.fa-newspaper-o:before{content:""}.fa-wifi:before{content:""}.fa-calculator:before{content:""}.fa-paypal:before{content:"ï‡"}.fa-google-wallet:before{content:""}.fa-cc-visa:before{content:""}.fa-cc-mastercard:before{content:""}.fa-cc-discover:before{content:""}.fa-cc-amex:before{content:""}.fa-cc-paypal:before{content:""}.fa-cc-stripe:before{content:""}.fa-bell-slash:before{content:""}.fa-bell-slash-o:before{content:""}.fa-trash:before{content:""}.fa-copyright:before{content:""}.fa-at:before{content:""}.fa-eyedropper:before{content:""}.fa-paint-brush:before{content:""}.fa-birthday-cake:before{content:""}.fa-area-chart:before{content:""}.fa-pie-chart:before{content:""}.fa-line-chart:before{content:"ïˆ"}.fa-lastfm:before{content:""}.fa-lastfm-square:before{content:""}.fa-toggle-off:before{content:""}.fa-toggle-on:before{content:""}.fa-bicycle:before{content:""}.fa-bus:before{content:""}.fa-ioxhost:before{content:""}.fa-angellist:before{content:""}.fa-cc:before{content:""}.fa-ils:before,.fa-shekel:before,.fa-sheqel:before{content:""}.fa-meanpath:before{content:""}.fa-buysellads:before{content:"ïˆ"}.fa-connectdevelop:before{content:""}.fa-dashcube:before{content:"ïˆ"}.fa-forumbee:before{content:""}.fa-leanpub:before{content:""}.fa-sellsy:before{content:""}.fa-shirtsinbulk:before{content:""}.fa-simplybuilt:before{content:""}.fa-skyatlas:before{content:""}.fa-cart-plus:before{content:""}.fa-cart-arrow-down:before{content:""}.fa-diamond:before{content:""}.fa-ship:before{content:""}.fa-user-secret:before{content:""}.fa-motorcycle:before{content:""}.fa-street-view:before{content:"ïˆ"}.fa-heartbeat:before{content:""}.fa-venus:before{content:""}.fa-mars:before{content:""}.fa-mercury:before{content:""}.fa-intersex:before,.fa-transgender:before{content:""}.fa-transgender-alt:before{content:""}.fa-venus-double:before{content:""}.fa-mars-double:before{content:""}.fa-venus-mars:before{content:""}.fa-mars-stroke:before{content:""}.fa-mars-stroke-v:before{content:""}.fa-mars-stroke-h:before{content:""}.fa-neuter:before{content:""}.fa-genderless:before{content:"ïˆ"}.fa-facebook-official:before{content:""}.fa-pinterest-p:before{content:""}.fa-whatsapp:before{content:""}.fa-server:before{content:""}.fa-user-plus:before{content:""}.fa-user-times:before{content:""}.fa-bed:before,.fa-hotel:before{content:""}.fa-viacoin:before{content:""}.fa-train:before{content:""}.fa-subway:before{content:""}.fa-medium:before{content:""}.fa-y-combinator:before,.fa-yc:before{content:""}.fa-optin-monster:before{content:""}.fa-opencart:before{content:""}.fa-expeditedssl:before{content:""}.fa-battery-4:before,.fa-battery-full:before{content:""}.fa-battery-3:before,.fa-battery-three-quarters:before{content:"ï‰"}.fa-battery-2:before,.fa-battery-half:before{content:""}.fa-battery-1:before,.fa-battery-quarter:before{content:""}.fa-battery-0:before,.fa-battery-empty:before{content:""}.fa-mouse-pointer:before{content:""}.fa-i-cursor:before{content:""}.fa-object-group:before{content:""}.fa-object-ungroup:before{content:""}.fa-sticky-note:before{content:""}.fa-sticky-note-o:before{content:""}.fa-cc-jcb:before{content:""}.fa-cc-diners-club:before{content:""}.fa-clone:before{content:"ï‰"}.fa-balance-scale:before{content:""}.fa-hourglass-o:before{content:"ï‰"}.fa-hourglass-1:before,.fa-hourglass-start:before{content:""}.fa-hourglass-2:before,.fa-hourglass-half:before{content:""}.fa-hourglass-3:before,.fa-hourglass-end:before{content:""}.fa-hourglass:before{content:""}.fa-hand-grab-o:before,.fa-hand-rock-o:before{content:""}.fa-hand-paper-o:before,.fa-hand-stop-o:before{content:""}.fa-hand-scissors-o:before{content:""}.fa-hand-lizard-o:before{content:""}.fa-hand-spock-o:before{content:""}.fa-hand-pointer-o:before{content:""}.fa-hand-peace-o:before{content:""}.fa-trademark:before{content:""}.fa-registered:before{content:"ï‰"}.fa-creative-commons:before{content:""}.fa-gg:before{content:"ï‰ "}.fa-gg-circle:before{content:""}.fa-tripadvisor:before{content:""}.fa-odnoklassniki:before{content:""}.fa-odnoklassniki-square:before{content:""}.fa-get-pocket:before{content:""}.fa-wikipedia-w:before{content:""}.fa-safari:before{content:""}.fa-chrome:before{content:""}.fa-firefox:before{content:""}.fa-opera:before{content:""}.fa-internet-explorer:before{content:""}.fa-television:before,.fa-tv:before{content:""}.fa-contao:before{content:"ï‰"}.fa-500px:before{content:""}.fa-amazon:before{content:""}.fa-calendar-plus-o:before{content:""}.fa-calendar-minus-o:before{content:""}.fa-calendar-times-o:before{content:""}.fa-calendar-check-o:before{content:""}.fa-industry:before{content:""}.fa-map-pin:before{content:""}.fa-map-signs:before{content:""}.fa-map-o:before{content:""}.fa-map:before{content:""}.fa-commenting:before{content:""}.fa-commenting-o:before{content:""}.fa-houzz:before{content:""}.fa-vimeo:before{content:""}.fa-black-tie:before{content:""}.fa-fonticons:before{content:""}.fa-reddit-alien:before{content:"ïŠ"}.fa-edge:before{content:""}.fa-credit-card-alt:before{content:""}.fa-codiepie:before{content:""}.fa-modx:before{content:""}.fa-fort-awesome:before{content:""}.fa-usb:before{content:""}.fa-product-hunt:before{content:""}.fa-mixcloud:before{content:""}.fa-scribd:before{content:""}.fa-pause-circle:before{content:""}.fa-pause-circle-o:before{content:""}.fa-stop-circle:before{content:"ïŠ"}.fa-stop-circle-o:before{content:""}.fa-shopping-bag:before{content:"ïŠ"}.fa-shopping-basket:before{content:""}.fa-hashtag:before{content:""}.fa-bluetooth:before{content:""}.fa-bluetooth-b:before{content:""}.fa-percent:before{content:""}code{font-size:.8em}code,div.sourceCode{background-color:#fafafa;border:1px solid #eee}div.sourceCode{line-height:1;margin-bottom:.625rem;overflow-x:auto}div.sourceCode pre{padding:.625rem}div.sourceCode code,div.sourceCode pre{border:none;background-color:transparent}div.sourceCode code{padding:0}table.sourceCode{width:100%}table.sourceCode tbody{border:none}table.sourceCode,table.sourceCode pre,td.lineNumbers,td.sourceCode,tr.sourceCode{margin:0;padding:0;border:0;vertical-align:baseline;border:none}td.lineNumbers{border-right:1px solid #aaa;text-align:right;color:#aaa;padding-right:5px;padding-left:5px;line-height:1.14}td.sourceCode{padding-left:.625rem}.sourceCode span.kw{color:#007020;font-weight:700}.sourceCode span.dt{color:#902000}.sourceCode span.bn,.sourceCode span.dv,.sourceCode span.fl{color:#40a070}.sourceCode span.ch,.sourceCode span.st{color:#4070a0}.sourceCode span.co{color:#60a0b0;font-style:italic}.sourceCode span.ot{color:#007020}.sourceCode span.al{color:red;font-weight:700}.sourceCode span.fu{color:#06287e}.sourceCode span.er{color:red;font-weight:700}h1.cardboard{font-family:adelle-sans;font-weight:400;transition:all .3s ease;float:left;font-weight:700;padding:0;line-height:3.75rem}@media screen and (max-width:39.9375em){h1.cardboard{line-height:1.5rem}}h1.cardboard span{transition:all .3s ease;position:relative;color:#fff;-webkit-box-decoration-break:clone;box-decoration-break:clone}h1.cardboard span.purple{color:#af517d}h1.cardboard span.yellow{color:#e6bd1a}h1.cardboard span.orange{color:#e87a2f}h1.cardboard span.red{color:#cb3535}h1.cardboard span.cyan{color:#51af9c}h1.cardboard span.green{color:#9caf51}h1.cardboard span.blue{color:#1490b0}a:active h1.cardboard,a:hover h1.cardboard span{color:#0a0a0a}div#header{padding-top:2.8125rem;padding-bottom:1.875rem;border-bottom:2px #cacaca}a#logo{display:inline-block}a#logo div{background-image:url(/images/header_logo_float.png);width:143px;height:59px}div#footer{margin-top:1.875rem;margin-bottom:1.875rem}div.info{color:#555;font-size:14px;font-style:italic;margin-bottom:1.25rem}div.post{margin-bottom:3.125rem}div.callout-quote{font-weight:700;font-style:italic;font-size:120%;max-width:25rem;margin:.625rem auto .9375rem}figcaption{font-style:italic;font-size:80%}figcaption:before{content:'fig. '}.wf-loading h1,.wf-loading p{visibility:hidden}.inline-block{display:inline-block}@media screen and (min-width:40em){.masonry{-webkit-column-count:3;-moz-column-count:3;column-count:3;-webkit-column-gap:.9375rem;-moz-column-gap:.9375rem;column-gap:.9375rem}.masonry .callout{margin-bottom:.9375rem;display:inline-block;width:100%}.text-left-medium{text-align:left}}figure{text-align:center} \ No newline at end of file + */@font-face{font-family:FontAwesome;src:url(/fonts/fontawesome-webfont.eot?v=4.5.0);src:url(/fonts/fontawesome-webfont.eot?#iefix&v=4.5.0) format("embedded-opentype"),url(/fonts/fontawesome-webfont.woff2?v=4.5.0) format("woff2"),url(/fonts/fontawesome-webfont.woff?v=4.5.0) format("woff"),url(/fonts/fontawesome-webfont.ttf?v=4.5.0) format("truetype"),url(/fonts/fontawesome-webfont.svg?v=4.5.0#fontawesomeregular) format("svg");font-weight:400;font-style:normal}.fa{display:inline-block;font:normal normal normal 14px/1 FontAwesome;font-size:inherit;text-rendering:auto;-webkit-font-smoothing:antialiased;-moz-osx-font-smoothing:grayscale}.fa-lg{font-size:1.33333em;line-height:.75em;vertical-align:-15%}.fa-2x{font-size:2em}.fa-3x{font-size:3em}.fa-4x{font-size:4em}.fa-5x{font-size:5em}.fa-fw{width:1.28571em;text-align:center}.fa-ul{padding-left:0;margin-left:2.14286em;list-style-type:none}.fa-ul>li{position:relative}.fa-li{position:absolute;left:-2.14286em;width:2.14286em;top:.14286em;text-align:center}.fa-li.fa-lg{left:-1.85714em}.fa-border{padding:.2em .25em .15em;border:.08em solid #eee;border-radius:.1em}.fa-pull-left{float:left}.fa-pull-right{float:right}.fa.fa-pull-left{margin-right:.3em}.fa.fa-pull-right{margin-left:.3em}.pull-right{float:right}.pull-left{float:left}.fa.pull-left{margin-right:.3em}.fa.pull-right{margin-left:.3em}.fa-spin{animation:a 2s infinite linear}.fa-pulse{animation:a 1s infinite steps(8)}@keyframes a{0%{transform:rotate(0deg)}to{transform:rotate(359deg)}}.fa-rotate-90{filter:progid:DXImageTransform.Microsoft.BasicImage(rotation=1);-ms-transform:rotate(90deg);transform:rotate(90deg)}.fa-rotate-180{filter:progid:DXImageTransform.Microsoft.BasicImage(rotation=2);-ms-transform:rotate(180deg);transform:rotate(180deg)}.fa-rotate-270{filter:progid:DXImageTransform.Microsoft.BasicImage(rotation=3);-ms-transform:rotate(270deg);transform:rotate(270deg)}.fa-flip-horizontal{filter:progid:DXImageTransform.Microsoft.BasicImage(rotation=0);-ms-transform:scaleX(-1);transform:scaleX(-1)}.fa-flip-vertical{filter:progid:DXImageTransform.Microsoft.BasicImage(rotation=2);-ms-transform:scaleY(-1);transform:scaleY(-1)}:root .fa-flip-horizontal,:root .fa-flip-vertical,:root .fa-rotate-90,:root .fa-rotate-180,:root .fa-rotate-270{-webkit-filter:none;filter:none}.fa-stack{position:relative;display:inline-block;width:2em;height:2em;line-height:2em;vertical-align:middle}.fa-stack-1x,.fa-stack-2x{position:absolute;left:0;width:100%;text-align:center}.fa-stack-1x{line-height:inherit}.fa-stack-2x{font-size:2em}.fa-inverse{color:#fff}.fa-glass:before{content:""}.fa-music:before{content:"ï€"}.fa-search:before{content:""}.fa-envelope-o:before{content:""}.fa-heart:before{content:""}.fa-star:before{content:""}.fa-star-o:before{content:""}.fa-user:before{content:""}.fa-film:before{content:""}.fa-th-large:before{content:""}.fa-th:before{content:""}.fa-th-list:before{content:""}.fa-check:before{content:""}.fa-close:before,.fa-remove:before,.fa-times:before{content:"ï€"}.fa-search-plus:before{content:""}.fa-search-minus:before{content:"ï€"}.fa-power-off:before{content:""}.fa-signal:before{content:""}.fa-cog:before,.fa-gear:before{content:""}.fa-trash-o:before{content:""}.fa-home:before{content:""}.fa-file-o:before{content:""}.fa-clock-o:before{content:""}.fa-road:before{content:""}.fa-download:before{content:""}.fa-arrow-circle-o-down:before{content:""}.fa-arrow-circle-o-up:before{content:""}.fa-inbox:before{content:""}.fa-play-circle-o:before{content:"ï€"}.fa-repeat:before,.fa-rotate-right:before{content:""}.fa-refresh:before{content:""}.fa-list-alt:before{content:""}.fa-lock:before{content:""}.fa-flag:before{content:""}.fa-headphones:before{content:""}.fa-volume-off:before{content:""}.fa-volume-down:before{content:""}.fa-volume-up:before{content:""}.fa-qrcode:before{content:""}.fa-barcode:before{content:""}.fa-tag:before{content:""}.fa-tags:before{content:""}.fa-book:before{content:"ï€"}.fa-bookmark:before{content:""}.fa-print:before{content:""}.fa-camera:before{content:""}.fa-font:before{content:""}.fa-bold:before{content:""}.fa-italic:before{content:""}.fa-text-height:before{content:""}.fa-text-width:before{content:""}.fa-align-left:before{content:""}.fa-align-center:before{content:""}.fa-align-right:before{content:""}.fa-align-justify:before{content:""}.fa-list:before{content:""}.fa-dedent:before,.fa-outdent:before{content:""}.fa-indent:before{content:""}.fa-video-camera:before{content:""}.fa-image:before,.fa-photo:before,.fa-picture-o:before{content:""}.fa-pencil:before{content:"ï€"}.fa-map-marker:before{content:"ï"}.fa-adjust:before{content:"ï‚"}.fa-tint:before{content:"ïƒ"}.fa-edit:before,.fa-pencil-square-o:before{content:"ï„"}.fa-share-square-o:before{content:"ï…"}.fa-check-square-o:before{content:"ï†"}.fa-arrows:before{content:"ï‡"}.fa-step-backward:before{content:"ïˆ"}.fa-fast-backward:before{content:"ï‰"}.fa-backward:before{content:"ïŠ"}.fa-play:before{content:"ï‹"}.fa-pause:before{content:"ïŒ"}.fa-stop:before{content:"ï"}.fa-forward:before{content:"ïŽ"}.fa-fast-forward:before{content:"ï"}.fa-step-forward:before{content:"ï‘"}.fa-eject:before{content:"ï’"}.fa-chevron-left:before{content:"ï“"}.fa-chevron-right:before{content:"ï”"}.fa-plus-circle:before{content:"ï•"}.fa-minus-circle:before{content:"ï–"}.fa-times-circle:before{content:"ï—"}.fa-check-circle:before{content:"ï˜"}.fa-question-circle:before{content:"ï™"}.fa-info-circle:before{content:"ïš"}.fa-crosshairs:before{content:"ï›"}.fa-times-circle-o:before{content:"ïœ"}.fa-check-circle-o:before{content:"ï"}.fa-ban:before{content:"ïž"}.fa-arrow-left:before{content:"ï "}.fa-arrow-right:before{content:"ï¡"}.fa-arrow-up:before{content:"ï¢"}.fa-arrow-down:before{content:"ï£"}.fa-mail-forward:before,.fa-share:before{content:"ï¤"}.fa-expand:before{content:"ï¥"}.fa-compress:before{content:"ï¦"}.fa-plus:before{content:"ï§"}.fa-minus:before{content:"ï¨"}.fa-asterisk:before{content:"ï©"}.fa-exclamation-circle:before{content:"ïª"}.fa-gift:before{content:"ï«"}.fa-leaf:before{content:"ï¬"}.fa-fire:before{content:"ï"}.fa-eye:before{content:"ï®"}.fa-eye-slash:before{content:"ï°"}.fa-exclamation-triangle:before,.fa-warning:before{content:"ï±"}.fa-plane:before{content:"ï²"}.fa-calendar:before{content:"ï³"}.fa-random:before{content:"ï´"}.fa-comment:before{content:"ïµ"}.fa-magnet:before{content:"ï¶"}.fa-chevron-up:before{content:"ï·"}.fa-chevron-down:before{content:"ï¸"}.fa-retweet:before{content:"ï¹"}.fa-shopping-cart:before{content:"ïº"}.fa-folder:before{content:"ï»"}.fa-folder-open:before{content:"ï¼"}.fa-arrows-v:before{content:"ï½"}.fa-arrows-h:before{content:"ï¾"}.fa-bar-chart-o:before,.fa-bar-chart:before{content:"ï‚€"}.fa-twitter-square:before{content:"ï‚"}.fa-facebook-square:before{content:"ï‚‚"}.fa-camera-retro:before{content:""}.fa-key:before{content:"ï‚„"}.fa-cogs:before,.fa-gears:before{content:"ï‚…"}.fa-comments:before{content:""}.fa-thumbs-o-up:before{content:""}.fa-thumbs-o-down:before{content:""}.fa-star-half:before{content:""}.fa-heart-o:before{content:"ï‚Š"}.fa-sign-out:before{content:"ï‚‹"}.fa-linkedin-square:before{content:"ï‚Œ"}.fa-thumb-tack:before{content:"ï‚"}.fa-external-link:before{content:"ï‚Ž"}.fa-sign-in:before{content:"ï‚"}.fa-trophy:before{content:"ï‚‘"}.fa-github-square:before{content:"ï‚’"}.fa-upload:before{content:"ï‚“"}.fa-lemon-o:before{content:"ï‚”"}.fa-phone:before{content:"ï‚•"}.fa-square-o:before{content:"ï‚–"}.fa-bookmark-o:before{content:"ï‚—"}.fa-phone-square:before{content:""}.fa-twitter:before{content:"ï‚™"}.fa-facebook-f:before,.fa-facebook:before{content:"ï‚š"}.fa-github:before{content:"ï‚›"}.fa-unlock:before{content:"ï‚œ"}.fa-credit-card:before{content:"ï‚"}.fa-feed:before,.fa-rss:before{content:"ï‚ž"}.fa-hdd-o:before{content:"ï‚ "}.fa-bullhorn:before{content:"ï‚¡"}.fa-bell:before{content:""}.fa-certificate:before{content:"ï‚£"}.fa-hand-o-right:before{content:""}.fa-hand-o-left:before{content:"ï‚¥"}.fa-hand-o-up:before{content:""}.fa-hand-o-down:before{content:""}.fa-arrow-circle-left:before{content:""}.fa-arrow-circle-right:before{content:"ï‚©"}.fa-arrow-circle-up:before{content:""}.fa-arrow-circle-down:before{content:"ï‚«"}.fa-globe:before{content:""}.fa-wrench:before{content:"ï‚"}.fa-tasks:before{content:"ï‚®"}.fa-filter:before{content:"ï‚°"}.fa-briefcase:before{content:""}.fa-arrows-alt:before{content:""}.fa-group:before,.fa-users:before{content:""}.fa-chain:before,.fa-link:before{content:"ïƒ"}.fa-cloud:before{content:""}.fa-flask:before{content:""}.fa-cut:before,.fa-scissors:before{content:""}.fa-copy:before,.fa-files-o:before{content:""}.fa-paperclip:before{content:""}.fa-floppy-o:before,.fa-save:before{content:""}.fa-square:before{content:""}.fa-bars:before,.fa-navicon:before,.fa-reorder:before{content:""}.fa-list-ul:before{content:""}.fa-list-ol:before{content:""}.fa-strikethrough:before{content:""}.fa-underline:before{content:"ïƒ"}.fa-table:before{content:""}.fa-magic:before{content:"ïƒ"}.fa-truck:before{content:""}.fa-pinterest:before{content:""}.fa-pinterest-square:before{content:""}.fa-google-plus-square:before{content:""}.fa-google-plus:before{content:""}.fa-money:before{content:""}.fa-caret-down:before{content:""}.fa-caret-up:before{content:""}.fa-caret-left:before{content:""}.fa-caret-right:before{content:""}.fa-columns:before{content:""}.fa-sort:before,.fa-unsorted:before{content:""}.fa-sort-desc:before,.fa-sort-down:before{content:"ïƒ"}.fa-sort-asc:before,.fa-sort-up:before{content:""}.fa-envelope:before{content:"ïƒ "}.fa-linkedin:before{content:""}.fa-rotate-left:before,.fa-undo:before{content:""}.fa-gavel:before,.fa-legal:before{content:""}.fa-dashboard:before,.fa-tachometer:before{content:""}.fa-comment-o:before{content:""}.fa-comments-o:before{content:""}.fa-bolt:before,.fa-flash:before{content:""}.fa-sitemap:before{content:""}.fa-umbrella:before{content:""}.fa-clipboard:before,.fa-paste:before{content:""}.fa-lightbulb-o:before{content:""}.fa-exchange:before{content:""}.fa-cloud-download:before{content:"ïƒ"}.fa-cloud-upload:before{content:""}.fa-user-md:before{content:""}.fa-stethoscope:before{content:""}.fa-suitcase:before{content:""}.fa-bell-o:before{content:"ï‚¢"}.fa-coffee:before{content:""}.fa-cutlery:before{content:""}.fa-file-text-o:before{content:""}.fa-building-o:before{content:""}.fa-hospital-o:before{content:""}.fa-ambulance:before{content:""}.fa-medkit:before{content:""}.fa-fighter-jet:before{content:""}.fa-beer:before{content:""}.fa-h-square:before{content:""}.fa-plus-square:before{content:""}.fa-angle-double-left:before{content:"ï„€"}.fa-angle-double-right:before{content:"ï„"}.fa-angle-double-up:before{content:"ï„‚"}.fa-angle-double-down:before{content:""}.fa-angle-left:before{content:"ï„„"}.fa-angle-right:before{content:"ï„…"}.fa-angle-up:before{content:""}.fa-angle-down:before{content:""}.fa-desktop:before{content:""}.fa-laptop:before{content:""}.fa-tablet:before{content:"ï„Š"}.fa-mobile-phone:before,.fa-mobile:before{content:"ï„‹"}.fa-circle-o:before{content:"ï„Œ"}.fa-quote-left:before{content:"ï„"}.fa-quote-right:before{content:"ï„Ž"}.fa-spinner:before{content:"ï„"}.fa-circle:before{content:"ï„‘"}.fa-mail-reply:before,.fa-reply:before{content:"ï„’"}.fa-github-alt:before{content:"ï„“"}.fa-folder-o:before{content:"ï„”"}.fa-folder-open-o:before{content:"ï„•"}.fa-smile-o:before{content:""}.fa-frown-o:before{content:"ï„™"}.fa-meh-o:before{content:"ï„š"}.fa-gamepad:before{content:"ï„›"}.fa-keyboard-o:before{content:"ï„œ"}.fa-flag-o:before{content:"ï„"}.fa-flag-checkered:before{content:"ï„ž"}.fa-terminal:before{content:"ï„ "}.fa-code:before{content:"ï„¡"}.fa-mail-reply-all:before,.fa-reply-all:before{content:"ï„¢"}.fa-star-half-empty:before,.fa-star-half-full:before,.fa-star-half-o:before{content:"ï„£"}.fa-location-arrow:before{content:""}.fa-crop:before{content:"ï„¥"}.fa-code-fork:before{content:""}.fa-chain-broken:before,.fa-unlink:before{content:""}.fa-question:before{content:""}.fa-info:before{content:"ï„©"}.fa-exclamation:before{content:""}.fa-superscript:before{content:"ï„«"}.fa-subscript:before{content:""}.fa-eraser:before{content:"ï„"}.fa-puzzle-piece:before{content:"ï„®"}.fa-microphone:before{content:"ï„°"}.fa-microphone-slash:before{content:""}.fa-shield:before{content:""}.fa-calendar-o:before{content:""}.fa-fire-extinguisher:before{content:"ï„´"}.fa-rocket:before{content:""}.fa-maxcdn:before{content:""}.fa-chevron-circle-left:before{content:"ï„·"}.fa-chevron-circle-right:before{content:""}.fa-chevron-circle-up:before{content:""}.fa-chevron-circle-down:before{content:""}.fa-html5:before{content:"ï„»"}.fa-css3:before{content:""}.fa-anchor:before{content:""}.fa-unlock-alt:before{content:""}.fa-bullseye:before{content:"ï…€"}.fa-ellipsis-h:before{content:"ï…"}.fa-ellipsis-v:before{content:"ï…‚"}.fa-rss-square:before{content:"ï…ƒ"}.fa-play-circle:before{content:"ï…„"}.fa-ticket:before{content:"ï……"}.fa-minus-square:before{content:"ï…†"}.fa-minus-square-o:before{content:"ï…‡"}.fa-level-up:before{content:"ï…ˆ"}.fa-level-down:before{content:"ï…‰"}.fa-check-square:before{content:"ï…Š"}.fa-pencil-square:before{content:"ï…‹"}.fa-external-link-square:before{content:"ï…Œ"}.fa-share-square:before{content:"ï…"}.fa-compass:before{content:"ï…Ž"}.fa-caret-square-o-down:before,.fa-toggle-down:before{content:"ï…"}.fa-caret-square-o-up:before,.fa-toggle-up:before{content:"ï…‘"}.fa-caret-square-o-right:before,.fa-toggle-right:before{content:"ï…’"}.fa-eur:before,.fa-euro:before{content:"ï…“"}.fa-gbp:before{content:"ï…”"}.fa-dollar:before,.fa-usd:before{content:"ï…•"}.fa-inr:before,.fa-rupee:before{content:"ï…–"}.fa-cny:before,.fa-jpy:before,.fa-rmb:before,.fa-yen:before{content:"ï…—"}.fa-rouble:before,.fa-rub:before,.fa-ruble:before{content:"ï…˜"}.fa-krw:before,.fa-won:before{content:"ï…™"}.fa-bitcoin:before,.fa-btc:before{content:"ï…š"}.fa-file:before{content:"ï…›"}.fa-file-text:before{content:"ï…œ"}.fa-sort-alpha-asc:before{content:"ï…"}.fa-sort-alpha-desc:before{content:"ï…ž"}.fa-sort-amount-asc:before{content:"ï… "}.fa-sort-amount-desc:before{content:"ï…¡"}.fa-sort-numeric-asc:before{content:"ï…¢"}.fa-sort-numeric-desc:before{content:"ï…£"}.fa-thumbs-up:before{content:"ï…¤"}.fa-thumbs-down:before{content:"ï…¥"}.fa-youtube-square:before{content:"ï…¦"}.fa-youtube:before{content:"ï…§"}.fa-xing:before{content:"ï…¨"}.fa-xing-square:before{content:"ï…©"}.fa-youtube-play:before{content:"ï…ª"}.fa-dropbox:before{content:"ï…«"}.fa-stack-overflow:before{content:"ï…¬"}.fa-instagram:before{content:"ï…"}.fa-flickr:before{content:"ï…®"}.fa-adn:before{content:"ï…°"}.fa-bitbucket:before{content:"ï…±"}.fa-bitbucket-square:before{content:"ï…²"}.fa-tumblr:before{content:"ï…³"}.fa-tumblr-square:before{content:"ï…´"}.fa-long-arrow-down:before{content:"ï…µ"}.fa-long-arrow-up:before{content:"ï…¶"}.fa-long-arrow-left:before{content:"ï…·"}.fa-long-arrow-right:before{content:"ï…¸"}.fa-apple:before{content:"ï…¹"}.fa-windows:before{content:"ï…º"}.fa-android:before{content:"ï…»"}.fa-linux:before{content:"ï…¼"}.fa-dribbble:before{content:"ï…½"}.fa-skype:before{content:"ï…¾"}.fa-foursquare:before{content:""}.fa-trello:before{content:"ï†"}.fa-female:before{content:""}.fa-male:before{content:""}.fa-gittip:before,.fa-gratipay:before{content:""}.fa-sun-o:before{content:""}.fa-moon-o:before{content:""}.fa-archive:before{content:""}.fa-bug:before{content:""}.fa-vk:before{content:""}.fa-weibo:before{content:""}.fa-renren:before{content:""}.fa-pagelines:before{content:""}.fa-stack-exchange:before{content:"ï†"}.fa-arrow-circle-o-right:before{content:""}.fa-arrow-circle-o-left:before{content:"ï†"}.fa-caret-square-o-left:before,.fa-toggle-left:before{content:""}.fa-dot-circle-o:before{content:""}.fa-wheelchair:before{content:""}.fa-vimeo-square:before{content:""}.fa-try:before,.fa-turkish-lira:before{content:""}.fa-plus-square-o:before{content:""}.fa-space-shuttle:before{content:""}.fa-slack:before{content:""}.fa-envelope-square:before{content:""}.fa-wordpress:before{content:""}.fa-openid:before{content:""}.fa-bank:before,.fa-institution:before,.fa-university:before{content:""}.fa-graduation-cap:before,.fa-mortar-board:before{content:"ï†"}.fa-yahoo:before{content:""}.fa-google:before{content:"ï† "}.fa-reddit:before{content:""}.fa-reddit-square:before{content:""}.fa-stumbleupon-circle:before{content:""}.fa-stumbleupon:before{content:""}.fa-delicious:before{content:""}.fa-digg:before{content:""}.fa-pied-piper:before{content:""}.fa-pied-piper-alt:before{content:""}.fa-drupal:before{content:""}.fa-joomla:before{content:""}.fa-language:before{content:""}.fa-fax:before{content:""}.fa-building:before{content:"ï†"}.fa-child:before{content:""}.fa-paw:before{content:""}.fa-spoon:before{content:""}.fa-cube:before{content:""}.fa-cubes:before{content:""}.fa-behance:before{content:""}.fa-behance-square:before{content:""}.fa-steam:before{content:""}.fa-steam-square:before{content:""}.fa-recycle:before{content:""}.fa-automobile:before,.fa-car:before{content:""}.fa-cab:before,.fa-taxi:before{content:""}.fa-tree:before{content:""}.fa-spotify:before{content:""}.fa-deviantart:before{content:""}.fa-soundcloud:before{content:""}.fa-database:before{content:""}.fa-file-pdf-o:before{content:"ï‡"}.fa-file-word-o:before{content:""}.fa-file-excel-o:before{content:""}.fa-file-powerpoint-o:before{content:""}.fa-file-image-o:before,.fa-file-photo-o:before,.fa-file-picture-o:before{content:""}.fa-file-archive-o:before,.fa-file-zip-o:before{content:""}.fa-file-audio-o:before,.fa-file-sound-o:before{content:""}.fa-file-movie-o:before,.fa-file-video-o:before{content:""}.fa-file-code-o:before{content:""}.fa-vine:before{content:""}.fa-codepen:before{content:""}.fa-jsfiddle:before{content:""}.fa-life-bouy:before,.fa-life-buoy:before,.fa-life-ring:before,.fa-life-saver:before,.fa-support:before{content:"ï‡"}.fa-circle-o-notch:before{content:""}.fa-ra:before,.fa-rebel:before{content:"ï‡"}.fa-empire:before,.fa-ge:before{content:""}.fa-git-square:before{content:""}.fa-git:before{content:""}.fa-hacker-news:before,.fa-y-combinator-square:before,.fa-yc-square:before{content:""}.fa-tencent-weibo:before{content:""}.fa-qq:before{content:""}.fa-wechat:before,.fa-weixin:before{content:""}.fa-paper-plane:before,.fa-send:before{content:""}.fa-paper-plane-o:before,.fa-send-o:before{content:""}.fa-history:before{content:""}.fa-circle-thin:before{content:""}.fa-header:before{content:""}.fa-paragraph:before{content:"ï‡"}.fa-sliders:before{content:""}.fa-share-alt:before{content:"ï‡ "}.fa-share-alt-square:before{content:""}.fa-bomb:before{content:""}.fa-futbol-o:before,.fa-soccer-ball-o:before{content:""}.fa-tty:before{content:""}.fa-binoculars:before{content:""}.fa-plug:before{content:""}.fa-slideshare:before{content:""}.fa-twitch:before{content:""}.fa-yelp:before{content:""}.fa-newspaper-o:before{content:""}.fa-wifi:before{content:""}.fa-calculator:before{content:""}.fa-paypal:before{content:"ï‡"}.fa-google-wallet:before{content:""}.fa-cc-visa:before{content:""}.fa-cc-mastercard:before{content:""}.fa-cc-discover:before{content:""}.fa-cc-amex:before{content:""}.fa-cc-paypal:before{content:""}.fa-cc-stripe:before{content:""}.fa-bell-slash:before{content:""}.fa-bell-slash-o:before{content:""}.fa-trash:before{content:""}.fa-copyright:before{content:""}.fa-at:before{content:""}.fa-eyedropper:before{content:""}.fa-paint-brush:before{content:""}.fa-birthday-cake:before{content:""}.fa-area-chart:before{content:""}.fa-pie-chart:before{content:""}.fa-line-chart:before{content:"ïˆ"}.fa-lastfm:before{content:""}.fa-lastfm-square:before{content:""}.fa-toggle-off:before{content:""}.fa-toggle-on:before{content:""}.fa-bicycle:before{content:""}.fa-bus:before{content:""}.fa-ioxhost:before{content:""}.fa-angellist:before{content:""}.fa-cc:before{content:""}.fa-ils:before,.fa-shekel:before,.fa-sheqel:before{content:""}.fa-meanpath:before{content:""}.fa-buysellads:before{content:"ïˆ"}.fa-connectdevelop:before{content:""}.fa-dashcube:before{content:"ïˆ"}.fa-forumbee:before{content:""}.fa-leanpub:before{content:""}.fa-sellsy:before{content:""}.fa-shirtsinbulk:before{content:""}.fa-simplybuilt:before{content:""}.fa-skyatlas:before{content:""}.fa-cart-plus:before{content:""}.fa-cart-arrow-down:before{content:""}.fa-diamond:before{content:""}.fa-ship:before{content:""}.fa-user-secret:before{content:""}.fa-motorcycle:before{content:""}.fa-street-view:before{content:"ïˆ"}.fa-heartbeat:before{content:""}.fa-venus:before{content:""}.fa-mars:before{content:""}.fa-mercury:before{content:""}.fa-intersex:before,.fa-transgender:before{content:""}.fa-transgender-alt:before{content:""}.fa-venus-double:before{content:""}.fa-mars-double:before{content:""}.fa-venus-mars:before{content:""}.fa-mars-stroke:before{content:""}.fa-mars-stroke-v:before{content:""}.fa-mars-stroke-h:before{content:""}.fa-neuter:before{content:""}.fa-genderless:before{content:"ïˆ"}.fa-facebook-official:before{content:""}.fa-pinterest-p:before{content:""}.fa-whatsapp:before{content:""}.fa-server:before{content:""}.fa-user-plus:before{content:""}.fa-user-times:before{content:""}.fa-bed:before,.fa-hotel:before{content:""}.fa-viacoin:before{content:""}.fa-train:before{content:""}.fa-subway:before{content:""}.fa-medium:before{content:""}.fa-y-combinator:before,.fa-yc:before{content:""}.fa-optin-monster:before{content:""}.fa-opencart:before{content:""}.fa-expeditedssl:before{content:""}.fa-battery-4:before,.fa-battery-full:before{content:""}.fa-battery-3:before,.fa-battery-three-quarters:before{content:"ï‰"}.fa-battery-2:before,.fa-battery-half:before{content:""}.fa-battery-1:before,.fa-battery-quarter:before{content:""}.fa-battery-0:before,.fa-battery-empty:before{content:""}.fa-mouse-pointer:before{content:""}.fa-i-cursor:before{content:""}.fa-object-group:before{content:""}.fa-object-ungroup:before{content:""}.fa-sticky-note:before{content:""}.fa-sticky-note-o:before{content:""}.fa-cc-jcb:before{content:""}.fa-cc-diners-club:before{content:""}.fa-clone:before{content:"ï‰"}.fa-balance-scale:before{content:""}.fa-hourglass-o:before{content:"ï‰"}.fa-hourglass-1:before,.fa-hourglass-start:before{content:""}.fa-hourglass-2:before,.fa-hourglass-half:before{content:""}.fa-hourglass-3:before,.fa-hourglass-end:before{content:""}.fa-hourglass:before{content:""}.fa-hand-grab-o:before,.fa-hand-rock-o:before{content:""}.fa-hand-paper-o:before,.fa-hand-stop-o:before{content:""}.fa-hand-scissors-o:before{content:""}.fa-hand-lizard-o:before{content:""}.fa-hand-spock-o:before{content:""}.fa-hand-pointer-o:before{content:""}.fa-hand-peace-o:before{content:""}.fa-trademark:before{content:""}.fa-registered:before{content:"ï‰"}.fa-creative-commons:before{content:""}.fa-gg:before{content:"ï‰ "}.fa-gg-circle:before{content:""}.fa-tripadvisor:before{content:""}.fa-odnoklassniki:before{content:""}.fa-odnoklassniki-square:before{content:""}.fa-get-pocket:before{content:""}.fa-wikipedia-w:before{content:""}.fa-safari:before{content:""}.fa-chrome:before{content:""}.fa-firefox:before{content:""}.fa-opera:before{content:""}.fa-internet-explorer:before{content:""}.fa-television:before,.fa-tv:before{content:""}.fa-contao:before{content:"ï‰"}.fa-500px:before{content:""}.fa-amazon:before{content:""}.fa-calendar-plus-o:before{content:""}.fa-calendar-minus-o:before{content:""}.fa-calendar-times-o:before{content:""}.fa-calendar-check-o:before{content:""}.fa-industry:before{content:""}.fa-map-pin:before{content:""}.fa-map-signs:before{content:""}.fa-map-o:before{content:""}.fa-map:before{content:""}.fa-commenting:before{content:""}.fa-commenting-o:before{content:""}.fa-houzz:before{content:""}.fa-vimeo:before{content:""}.fa-black-tie:before{content:""}.fa-fonticons:before{content:""}.fa-reddit-alien:before{content:"ïŠ"}.fa-edge:before{content:""}.fa-credit-card-alt:before{content:""}.fa-codiepie:before{content:""}.fa-modx:before{content:""}.fa-fort-awesome:before{content:""}.fa-usb:before{content:""}.fa-product-hunt:before{content:""}.fa-mixcloud:before{content:""}.fa-scribd:before{content:""}.fa-pause-circle:before{content:""}.fa-pause-circle-o:before{content:""}.fa-stop-circle:before{content:"ïŠ"}.fa-stop-circle-o:before{content:""}.fa-shopping-bag:before{content:"ïŠ"}.fa-shopping-basket:before{content:""}.fa-hashtag:before{content:""}.fa-bluetooth:before{content:""}.fa-bluetooth-b:before{content:""}.fa-percent:before{content:""}code{font-size:.8em}code,div.sourceCode{background-color:#fafafa;border:1px solid #eee}div.sourceCode{line-height:1;margin-bottom:.625rem;overflow-x:auto}div.sourceCode pre{padding:.625rem}div.sourceCode code,div.sourceCode pre{border:none;background-color:transparent}div.sourceCode code{padding:0}table.sourceCode{width:100%}table.sourceCode tbody{border:none}table.sourceCode,table.sourceCode pre,td.lineNumbers,td.sourceCode,tr.sourceCode{margin:0;padding:0;border:0;vertical-align:baseline;border:none}td.lineNumbers{border-right:1px solid #aaa;text-align:right;color:#aaa;padding-right:5px;padding-left:5px;line-height:1.14}td.sourceCode{padding-left:.625rem}.sourceCode span.kw{color:#007020;font-weight:700}.sourceCode span.dt{color:#902000}.sourceCode span.bn,.sourceCode span.dv,.sourceCode span.fl{color:#40a070}.sourceCode span.ch,.sourceCode span.st{color:#4070a0}.sourceCode span.co{color:#60a0b0;font-style:italic}.sourceCode span.ot{color:#007020}.sourceCode span.al{color:red;font-weight:700}.sourceCode span.fu{color:#06287e}.sourceCode span.er{color:red;font-weight:700}h1.cardboard{font-family:adelle-sans;font-weight:400;transition:all .3s ease;float:left;font-weight:700;padding:0;line-height:3.75rem}@media screen and (min-width:0em) and (max-width:39.9375em){h1.cardboard{line-height:1.5rem}}h1.cardboard span{transition:all .3s ease;position:relative;color:#fff;-webkit-box-decoration-break:clone;box-decoration-break:clone}h1.cardboard span.purple{color:#af517d}h1.cardboard span.yellow{color:#e6bd1a}h1.cardboard span.orange{color:#e87a2f}h1.cardboard span.red{color:#cb3535}h1.cardboard span.cyan{color:#51af9c}h1.cardboard span.green{color:#9caf51}h1.cardboard span.blue{color:#1490b0}a:active h1.cardboard,a:hover h1.cardboard span{color:#0a0a0a}div#header{padding-top:2.8125rem;padding-bottom:1.875rem;border-bottom:2px #cacaca}a#logo{display:inline-block}a#logo div{background-image:url(/images/header_logo_float.png);width:143px;height:59px}div#footer{margin-top:1.875rem;margin-bottom:1.875rem}div.info{color:#555;font-size:14px;font-style:italic;margin-bottom:1.25rem}div.post{margin-bottom:3.125rem}div.callout-quote{font-weight:700;font-style:italic;font-size:120%;max-width:25rem;margin:.625rem auto .9375rem}figcaption{font-style:italic;font-size:80%}figcaption:before{content:'fig. '}.wf-loading h1,.wf-loading p{visibility:hidden}.inline-block{display:inline-block}@media screen and (min-width:40em){.masonry{-moz-column-count:3;column-count:3;-moz-column-gap:.9375rem;column-gap:.9375rem}.masonry .callout{margin-bottom:.9375rem;display:inline-block;width:100%}.text-left-medium{text-align:left}}figure{text-align:center}.markdown-icon{width:30px;margin-right:5px;vertical-align:sub} \ No newline at end of file diff --git a/images/markdown-mark.svg b/images/markdown-mark.svg new file mode 100644 index 0000000000000000000000000000000000000000..f3ed113f4b9ffb152a24ed8201d788646237f4ee --- /dev/null +++ b/images/markdown-mark.svg @@ -0,0 +1 @@ +<svg xmlns="http://www.w3.org/2000/svg" width="208" height="128" viewBox="0 0 208 128"><rect width="198" height="118" x="5" y="5" ry="10" stroke="#000" stroke-width="10" fill="none"/><path d="M30 98v-68h20l20 25 20-25h20v68h-20v-39l-20 25-20-25v39zM155 98l-30-33h20v-35h20v35h20z"/></svg> \ No newline at end of file diff --git a/posts/2014-01-20-linux-setup-gnome-3.md b/posts/2014-01-20-linux-setup-gnome-3.md index 91f794ac1f36b06254d1c007a3a4f0c0d51f05f9..d3f182370712050740f562db750e7df69a77c1b1 100644 --- a/posts/2014-01-20-linux-setup-gnome-3.md +++ b/posts/2014-01-20-linux-setup-gnome-3.md @@ -1,5 +1,5 @@ --- -title: Linux setup: Gnome 3 +title: 'Linux setup: Gnome 3' tags: linux, gnome, fedora uuid: 97473bd1-82a8-412a-8863-68ca30a5ef6e legacy: linux-setup-gnome-3 diff --git a/posts/2014-03-08-php-is-not-dead.md b/posts/2014-03-08-php-is-not-dead.md index 4a29ebfa5ae56f3709f4e93fda64378ce6b9fc32..39bff5e843d08795c0dc21e19eef0991e1bada08 100644 --- a/posts/2014-03-08-php-is-not-dead.md +++ b/posts/2014-03-08-php-is-not-dead.md @@ -1,5 +1,5 @@ --- -title: Using Laravel: PHP is not dead +title: 'Using Laravel: PHP is not dead' tags: php, laravel uuid: 9b92d244-281c-401c-8c72-3e9a67e976c3 legacy: using-laravel-php-is-not-dead diff --git a/posts/2014-06-07-ensurejs.md b/posts/2014-06-07-ensurejs.md index 42161d77672352abe13ceef24bfa0dbcedccc99d..0937ea0daeb82a11de7ade9c188e2df4c917ec63 100644 --- a/posts/2014-06-07-ensurejs.md +++ b/posts/2014-06-07-ensurejs.md @@ -1,5 +1,5 @@ --- -title: Ensure.js: Simple type-checking on JavaScript +title: 'Ensure.js: Simple type-checking on JavaScript' tags: ensure, javascript uuid: 3dc96fbd-5409-4d5b-926b-b1daa3ed3809 legacy: ensurejs-simple-type-checking-on-javascript diff --git a/posts/2014-08-12-ensure-04-records.md b/posts/2014-08-12-ensure-04-records.md index e5e892b35c5c988ea04ff593f5d72f19a59c470c..f7f9118b5ed270727d141112ffa45fc7105ebc45 100644 --- a/posts/2014-08-12-ensure-04-records.md +++ b/posts/2014-08-12-ensure-04-records.md @@ -1,5 +1,5 @@ --- -title: Ensure.js 0.4: Record Types and better testing +title: 'Ensure.js 0.4: Record Types and better testing' tags: type-checking, ensure, nodejs, javascript uuid: e1b251c3-10cd-41d1-9d64-faa70d407e9b legacy: ensurejs-04-record-types-and-better-testing diff --git a/posts/2014-10-27-custom-laravel-logs.md b/posts/2014-10-27-custom-laravel-logs.md index 103b8a7e07f659f9d22ebdbbd1cf9f7886695de2..49753930b7b986df9110808e20cdf08b2e5cb780 100644 --- a/posts/2014-10-27-custom-laravel-logs.md +++ b/posts/2014-10-27-custom-laravel-logs.md @@ -1,5 +1,5 @@ --- -title: Laravel 5: Custom Logs +title: 'Laravel 5: Custom Logs' tags: laravel, laravel5, logs, php uuid: f9095ab9-008f-44fd-aa54-b148dcd007e0 legacy: laravel-5-custom-logs diff --git a/posts/2014-11-08-ensurejs-documentation-shields.md b/posts/2014-11-08-ensurejs-documentation-shields.md index a439cd2755019211f94eb91f92d57a8bf38ecd9f..f2a7f10dcc1185aa0072448f5ce75774c017db86 100644 --- a/posts/2014-11-08-ensurejs-documentation-shields.md +++ b/posts/2014-11-08-ensurejs-documentation-shields.md @@ -1,5 +1,5 @@ --- -title: Ensure 0.5.0: Documentation and shields! +title: 'Ensure 0.5.0: Documentation and shields!' tags: ensure, nodejs uuid: a4d02358-7410-46ed-be8a-b99730a0e45d legacy: ensure-050-documentation-and-shields diff --git a/posts/2015-05-10-heapster-deis.md b/posts/2015-05-10-heapster-deis.md index f1778a70f597d8dc2beca44cefce3d85f63c2d7c..d751745fe22bc573e54d0ee02f88a4289b8b5b33 100644 --- a/posts/2015-05-10-heapster-deis.md +++ b/posts/2015-05-10-heapster-deis.md @@ -1,5 +1,5 @@ --- -title: Heapster and Deis: So hip! +title: 'Heapster and Deis: So hip!' tags: docker, heapster, coreos, influxdb uuid: 09e80619-b671-47ec-b419-a57813d55ff2 legacy: heapster-and-deis-so-hip diff --git a/scss/_headers.scss b/scss/_headers.scss index f726c47638780d03c2c936db503d04ad5911b6e0..4450108ddc5984d69a188eda95f84cf4edfc5e10 100644 --- a/scss/_headers.scss +++ b/scss/_headers.scss @@ -10,7 +10,7 @@ h1 { padding: rem-calc(0); line-height: rem-calc(60); - @include breakpoint(small down) { + @include breakpoint(small only) { line-height: 1.5rem; } diff --git a/scss/app.scss b/scss/app.scss index 8eca4af028f955a5f79f2398cc2552ae184980e1..a15af870e59a32c6b864b1e11fed4004c08d60cb 100644 --- a/scss/app.scss +++ b/scss/app.scss @@ -128,3 +128,9 @@ figcaption { figure { text-align: center; } + +.markdown-icon { + width: 30px; + margin-right: 5px; + vertical-align: sub; +} diff --git a/stack.yaml b/stack.yaml index 2028a4bc1943b06524caed80c3c20fab526f22bd..8fc031ed3448cb937b130b8743a1e44232b9788e 100644 --- a/stack.yaml +++ b/stack.yaml @@ -1,14 +1,14 @@ # For more information, see: https://github.com/commercialhaskell/stack/blob/release/doc/yaml_configuration.md # Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2) -resolver: lts-5.11 +resolver: lts-6.7 # Local packages, usually specified by relative directory name packages: - '.' - location: - git: https://phabricator.chromabits.com/diffusion/HAKS/hakyll-serve.git - commit: e4bbdcb2124fc0f44d4a5a8e9dea0fbcdb612267 + git: https://phabricator.chromabits.com/diffusion/KWAI/kawaii.git + commit: 50bf3ff2edeeb8a68b585fee19d255af377e37b3 # Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3) extra-deps: [] diff --git a/templates/full-post.html b/templates/full-post.html index 983922a5ca5133b33989549d3a5d2b81497f6c2c..54058b07af3740b0d19111b794b6d40c28ba2d60 100644 --- a/templates/full-post.html +++ b/templates/full-post.html @@ -1,3 +1,9 @@ $body$ +<div class="callout"> + <img src="/images/markdown-mark.svg" class="markdown-icon"/> + This post is also available in Markdown: + <a href="/$identifier$">View source</a> +</div> + $partial("templates/disqus.html")$