How to get the current Firefox tab

Posted on November 28, 2020
Tags: haskell, emacs

Here is a cli solution using Haskell to get the current tab opened in Firefox, which I run from emacs.

Haskell

The single input argument is the path of the recovery.jsonlz4 file in Firefox’s profile folder, which is decompressed with the lz4-hs package and traversed using lenses from lens-aeson. Output is just the tab tile and url in two lines printed to stdout. The code can be found here.

{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Main where

import           Codec.Lz4
import           Control.Lens
import           Data.Aeson
import           Data.Aeson.Lens
import           Data.Bits                      ( shiftL )
import qualified Data.ByteString.Char8         as BC
import           Data.Char                      ( ord )
import           System.Environment
import           Data.Text.Lens

readLz4 :: FilePath -> IO BC.ByteString
readLz4 f = do
  contents <- BC.readFile f
  let bsc = BC.drop 8 contents
      sz  = lEBsToInt $ BC.take 4 bsc
  return $ decompressBlockSz (BC.drop 4 bsc) sz


readJsonLz4 :: FilePath -> IO Value
readJsonLz4 f = do
  bs <- readLz4 f
  return $ bs ^?! _JSON

-- https://stackoverflow.com/questions/26519579/how-do-i-convert-4-bytes-of-a-bytestring-to-an-int
-- 1.  Get the first 4 bytes of a ByteString
-- 2.  Calculate the amount to shift by
-- 3.  Fold over the ByteString, summing the result of shifting the current byte by the current offset
lEBsToInt :: BC.ByteString -> Int -- littleEndianByteStringToInt
lEBsToInt bs =
  let bsI = BC.take 4 bs
  in  fst $ BC.foldl
        (\(s, i) b ->
          let shiftBy = i * 8 in (s + (ord b `shiftL` shiftBy), i + 1)
        )
        (0, 0)
        bsI

getCurrentTab :: Value -> (String, String)
getCurrentTab v =
  let iwindow = v ^?! key "selectedWindow" . _Integer . to fromIntegral - 1
      window  = v ^?! key "windows" . nth iwindow
      itab    = window ^?! key "selected" . _Integer . to fromIntegral - 1
      tab     = window ^?! key "tabs" . nth itab
      ientry  = tab ^?! key "index" . _Integer . to fromIntegral - 1
  in  tab ^?! key "entries" . nth ientry . to
        (\o ->
          ( o ^?! key "title" . _String . unpacked
          , o ^?! key "url" . _String . unpacked
          )
        )

extractCurrentTab :: FilePath -> IO (String, String)
extractCurrentTab recoveryJson = do
  value <- readJsonLz4 recoveryJson
  return $ getCurrentTab value

currentFirefoxTab :: FilePath -> IO ()
currentFirefoxTab recoveryJson = do
  (title, url) <- extractCurrentTab recoveryJson
  putStrLn title
  putStrLn url


main :: IO ()
main = do
  [recoveryJson] <- getArgs
  currentFirefoxTab recoveryJson

Firefox

The path to firefox’s recovery.jsonlz4 file:

  • macos: "~/Library/Application Support/Firefox/Profiles/*.default-*/sessionstore-backups/recovery.jsonlz4"
  • linux: "~/.mozilla/firefox*/*.default/sessionstore-backups/recovery.jsonlz4"

Emacs

I wrote fftabs to be used in my doom emacs config to insert the tab in a buffer or open it in eww. Here are some elisp function to achieve this:

;; Use Firefox Tabs
(defvar mnd/ff-restore-file
  "/Users/mnd/Library/Application\\ Support/Firefox/Profiles/\
<FILLHERE>.default-<FILLHERE>/sessionstore-backups/recovery.jsonlz4")

(defun mnd/current-firefox-tab ()
  "Run fftabs haskell programm to get the current firefox tab."
  (s-split "\n"
           (shell-command-to-string
            (format "fftabs %s" mnd/ff-restore-file))
           'omit-nulls))

(defun mnd/current-firefox-tab-url ()
  "Insert the url of the current firefox tab."
  (interactive)
  (let* ((pair (mnd/current-firefox-tab))
         (url (cadr pair)))
    (insert url)))
(map! :leader "i w u" #'mnd/current-firefox-tab-url)

(defun mnd/current-firefox-tab-orglink ()
  "Get the current firefox tab in titled org-link format."
  (let* ((pair (mnd/current-firefox-tab))
         (title (car pair))
         (url (cadr pair))
         (orglink (format "[[%s][%s]]" url title)))
    (message "%s" orglink)
    orglink))

(defun mnd/current-firefox-tab-org-cliplink ()
  "Insert the current firefox tab in titled org-link format."
  (interactive)
  (insert (mnd/current-firefox-tab-orglink))
  (evil-jump-item))
(map! :leader "i w o" #'mnd/current-firefox-tab-org-cliplink)

(defun mnd/current-firefox-tab-eww ()
  "Open the current firefox tab in eww."
  (interactive)
  (let* ((pair (mnd/current-firefox-tab))
         (url (cadr pair)))
    (eww url)))
(map! :leader "o w" #'mnd/current-firefox-tab-eww)

References