diff --git a/index.html b/index.html
index a285c8605d89cd9579302ec125ffeaaed19684fa..1d8947b04448b7cb355e9898d5dce9cf4efebc2d 100644
--- a/index.html
+++ b/index.html
@@ -1,4 +1,5 @@
 ---
+title: Blog
 ---
 
 $posts$
diff --git a/site.hs b/site.hs
index 80b1745b773c54bc661d24ee7e0747e7f387167f..b2f0938c72d71e83f71ff80e66c9296279ee7a8c 100644
--- a/site.hs
+++ b/site.hs
@@ -1,11 +1,12 @@
 --------------------------------------------------------------------------------
 {-# LANGUAGE OverloadedStrings #-}
+import Control.Applicative
 import Control.Monad (liftM)
 import Control.Monad.IO.Class
 import qualified Data.Map as M
 import Data.Maybe (fromMaybe)
 import Data.Monoid (mappend)
-import Data.List (intersperse)
+import Data.List (intersperse, isSuffixOf)
 import Data.List.Split (splitOn)
 import Hakyll
 import Text.Highlighting.Kate.Styles (haddock)
@@ -73,12 +74,14 @@ main = hakyllWith hakyllConf $ do
     compile $ pandocHtml5Compiler
       >>= loadAndApplyTemplate "templates/default.html" siteCtx
       >>= relativizeUrls
+      >>= deIndexUrls
 
   create ["about.html"] $ do
     route $ indexify `composeRoutes` setExtension "html"
     compile $ pandocHtml5Compiler
       >>= loadAndApplyTemplate "templates/default.html" siteCtx
       >>= relativizeUrls
+      >>= deIndexUrls
 
   matchMetadata "posts/*" (M.member "legacy") $ version "legacy" $ do
     route $ legacyRoute `composeRoutes` setExtension "html"
@@ -94,6 +97,7 @@ main = hakyllWith hakyllConf $ do
         >>= loadAndApplyTemplate "templates/full-post.html" ctx
         >>= loadAndApplyTemplate "templates/default.html" ctx
         >>= relativizeUrls
+        >>= deIndexUrls
 
   match "posts/*" $ do
     route $ directorizeDate `composeRoutes` setExtension "html"
@@ -110,6 +114,7 @@ main = hakyllWith hakyllConf $ do
         >>= loadAndApplyTemplate "templates/full-post.html" ctx
         >>= loadAndApplyTemplate "templates/default.html" ctx
         >>= relativizeUrls
+        >>= deIndexUrls
 
   match "drafts/*" $ do
     route $ setExtension "html"
@@ -121,6 +126,7 @@ main = hakyllWith hakyllConf $ do
         >>= loadAndApplyTemplate "templates/full-post.html" ctx
         >>= loadAndApplyTemplate "templates/default.html" ctx
         >>= relativizeUrls
+        >>= deIndexUrls
 
   match "projects/*" $ do
     route $ indexify `composeRoutes` setExtension "html"
@@ -136,6 +142,7 @@ main = hakyllWith hakyllConf $ do
       saveSnapshot "content" full
         >>= loadAndApplyTemplate "templates/default.html" siteCtx
         >>= relativizeUrls
+        >>= deIndexUrls
 
   create ["archive.html"] $ do
     route indexify
@@ -151,6 +158,7 @@ main = hakyllWith hakyllConf $ do
         >>= loadAndApplyTemplate "templates/archive.html" archiveCtx
         >>= loadAndApplyTemplate "templates/default.html" archiveCtx
         >>= relativizeUrls
+        >>= deIndexUrls
 
   create ["projects.html"] $ do
     route indexify
@@ -166,6 +174,7 @@ main = hakyllWith hakyllConf $ do
         >>= loadAndApplyTemplate "templates/projects.html" archiveCtx
         >>= loadAndApplyTemplate "templates/default.html" archiveCtx
         >>= relativizeUrls
+        >>= deIndexUrls
 
   pag <- buildPaginateWith grouper ("posts/*" .&&. hasNoVersion) makeId
 
@@ -185,6 +194,7 @@ main = hakyllWith hakyllConf $ do
         >>= applyTemplate body (ctx `mappend` bodyField "posts")
         >>= loadAndApplyTemplate "templates/default.html" ctx
         >>= relativizeUrls
+        >>= deIndexUrls
 
     paginateRules pag $ \pageNum pattern -> do
       route idRoute
@@ -205,12 +215,14 @@ main = hakyllWith hakyllConf $ do
           >>= loadAndApplyTemplate "templates/default.html"
             (ctx `mappend` bodyField "posts")
           >>= relativizeUrls
+          >>= deIndexUrls
 
     match "templates/*" $ compile templateCompiler
 
 --------------------------------------------------------------------------------
 siteCtx :: Context String
 siteCtx =
+  deIndexedUrlField "url" `mappend`
   constField "root" (siteRoot siteConf) `mappend`
   constField "gaId" (siteGaId siteConf) `mappend`
   defaultContext
@@ -251,6 +263,18 @@ grouper ids = (liftM (paginateEvery 3) . sortRecentFirst) ids
 makeId :: PageNumber -> Identifier
 makeId pageNum = fromFilePath $ "page/" ++ show pageNum ++ "/index.html"
 
+stripIndex :: String -> String
+stripIndex url = if "index.html" `isSuffixOf` url
+    && elem (head url) ("/." :: String)
+  then take (length url - 10) url else url
+
+deIndexUrls :: Item String -> Compiler (Item String)
+deIndexUrls item = return $ fmap (withUrls stripIndex) item
+
+deIndexedUrlField :: String -> Context a
+deIndexedUrlField key = field key
+  $ fmap (stripIndex . maybe empty toUrl) . getRoute . itemIdentifier
+
 dropMore :: Item String -> Item String
 dropMore = fmap (unlines . takeWhile (/= "<!--more-->") . lines)
 
diff --git a/templates/default.html b/templates/default.html
index 2008c256b347a3df11e63f0aab0d4655bc564a20..92ec66689214bc55d99dc990bba0e27300ea463c 100644
--- a/templates/default.html
+++ b/templates/default.html
@@ -13,8 +13,21 @@
 
         <script src="https://use.typekit.net/voy2fek.js"></script>
         <script>try{Typekit.load({ async: true });}catch(e){}</script>
+
+        <meta property="fb:admins" content="etcinit"/>
     </head>
     <body>
+      <div id="fb-root"></div>
+      <script>
+      (function(d, s, id) {
+      var js, fjs = d.getElementsByTagName(s)[0];
+      if (d.getElementById(id)) return;
+      js = d.createElement(s); js.id = id;
+      js.src = "//connect.facebook.net/en_US/sdk.js#xfbml=1&version=v2.5&appId=332765426823646";
+      fjs.parentNode.insertBefore(js, fjs);
+      }(document, 'script', 'facebook-jssdk'));
+      </script>
+
         <div id="header" class="row align-middle">
           <div class="columns medium-6">
             <a href="/" id="logo"><div></div></a>
diff --git a/templates/disqus.html b/templates/disqus.html
index 793007c8fcbd471386b356fe9da3cea7725fc54d..5b162404fa5ac79b3bd31991d30dd2a8aabbe5b9 100644
--- a/templates/disqus.html
+++ b/templates/disqus.html
@@ -1,22 +1,11 @@
-<div id="disqus_thread"></div>
-<script>
-var disqus_config = function () {
-  this.page.url = '$url$';
-  this.page.identifier = '$uuid$';
-};
+<div class="fb-like"
+  data-href="https://chromabits.com$url$"
+  data-layout="standard" data-action="like" data-show-faces="true"
+  data-share="true">
+</div>
 
-(function() {
-var d = document, s = d.createElement('script');
-
-s.src = '//openwalls.disqus.com/embed.js';
-
-s.setAttribute('data-timestamp', +new Date());
-(d.head || d.body).appendChild(s);
-})();
-</script>
-<noscript>
-  Please enable JavaScript to view the
-  <a href="https://disqus.com/?ref_noscript" rel="nofollow">
-    comments powered by Disqus.
-  </a>
-</noscript>
+<div class="fb-comments"
+  data-href="https://chromabits.com$url$"
+  data-width="100%"
+  data-numposts="5">
+</div>
diff --git a/templates/projects.html b/templates/projects.html
index c6938d2e12c04e1b6abde32432ac6e9240fd3c95..022c741ede8b2ecc65502a67fc2a8caa85b3dff6 100644
--- a/templates/projects.html
+++ b/templates/projects.html
@@ -22,7 +22,7 @@
 </p>
 
 <div class="button-group">
-  <a class="button" href="//phabricator.chromabits.com">
+  <a class="button" href="http://phabricator.chromabits.com">
     <i class="fa fa-cog"></i>&nbsp;
     Phabricator
   </a>