2018-08-05 17:51:58 +02:00
|
|
|
#!/usr/bin/env nix-script
|
|
|
|
#!>haskell
|
|
|
|
#! haskell | shell-conduit temporary transformers raw-strings-qq
|
|
|
|
#! shell | curl
|
|
|
|
|
|
|
|
{-# LANGUAGE QuasiQuotes #-}
|
|
|
|
|
|
|
|
import Control.Monad
|
|
|
|
import Control.Monad.IO.Class (liftIO)
|
|
|
|
import Text.Printf (printf)
|
|
|
|
import Text.RawString.QQ (r)
|
|
|
|
import System.IO.Temp (withSystemTempDirectory)
|
|
|
|
import System.Directory (copyFile, createDirectoryIfMissing)
|
|
|
|
import System.FilePath
|
|
|
|
import Data.Conduit.Shell (Segment, run, shell, grep)
|
|
|
|
import Data.Conduit.Shell.Segments (strings)
|
|
|
|
|
|
|
|
type Url = String
|
|
|
|
type Sed = String
|
|
|
|
|
|
|
|
|
|
|
|
privoxy :: FilePath
|
|
|
|
privoxy = "/var/lib/privoxy"
|
|
|
|
|
|
|
|
|
|
|
|
urls :: [Url]
|
|
|
|
urls =
|
|
|
|
[ "https://easylist.to/easylist/easylist.txt"
|
|
|
|
, "https://easylist.to/easylist/easyprivacy.txt"
|
|
|
|
, "https://easylist.to/easylist/fanboy-annoyance.txt"
|
2019-05-07 01:27:07 +02:00
|
|
|
, "https://www.fanboy.co.nz/fanboy-cookiemonster.txt"
|
2018-08-05 17:51:58 +02:00
|
|
|
]
|
|
|
|
|
|
|
|
|
|
|
|
rules :: [Sed]
|
|
|
|
rules =
|
|
|
|
[ [r|/^!.*/d;1,1 d;/^@@.*/d;/\$.*/d;/#/d;s/\./\\./g;s/\?/\\?/g;s/\*/.*/g;s/(/\\(/g;s/)/\\)/g;s/\[/\\[/g;s/\]/\\]/g;s/\^/[\/\&:\?=_]/g;s/^||/\./g;s/^|/^/g;s/|$/\$/g;/|/d|]
|
|
|
|
, [r|/^#/!d;s/^##//g;s/^#\(.*\)\[.*\]\[.*\]*/s|<([a-zA-Z0-9]+)\\s+.*id=.?\1.*>.*<\/\\1>||g/g;s/^#\(.*\)/s|<([a-zA-Z0-9]+)\\s+.*id=.?\1.*>.*<\/\\1>||g/g;s/^\.\(.*\)/s|<([a-zA-Z0-9]+)\\s+.*class=.?\1.*>.*<\/\\1>||g/g;s/^a\[\(.*\)\]/s|<a.*\1.*>.*<\/a>||g/g;s/^\([a-zA-Z0-9]*\)\.\(.*\)\[.*\]\[.*\]*/s|<\1.*class=.?\2.*>.*<\/\1>||g/g;s/^\([a-zA-Z0-9]*\)#\(.*\):.*[\:[^:]]*[^:]*/s|<\1.*id=.?\2.*>.*<\/\1>||g/g;s/^\([a-zA-Z0-9]*\)#\(.*\)/s|<\1.*id=.?\2.*>.*<\/\1>||g/g;s/^\[\([a-zA-Z]*\).=\(.*\)\]/s|\1^=\2>||g/g;s/\^/[\/\&:\?=_]/g;s/\.\([a-zA-Z0-9]\)/\\.\1/g|]
|
|
|
|
, [r|/^@@.*/!d;s/^@@//g;/\$.*/d;/#/d;s/\./\\./g;s/\?/\\?/g;s/\*/.*/g;s/(/\\(/g;s/)/\\)/g;s/\[/\\[/g;s/\]/\\]/g;s/\^/[\/\&:\?=_]/g;s/^||/\./g;s/^|/^/g;s/|$/\$/g;/|/d|]
|
|
|
|
, [r|/^@@.*/!d;s/^@@//g;/\$.*image.*/!d;s/\$.*image.*//g;/#/d;s/\./\\./g;s/\?/\\?/g;s/\*/.*/g;s/(/\\(/g;s/)/\\)/g;s/\[/\\[/g;s/\]/\\]/g;s/\^/[\/\&:\?=_]/g;s/^||/\./g;s/^|/^/g;s/|$/\$/g;/|/d|]
|
|
|
|
]
|
|
|
|
|
|
|
|
main :: IO ()
|
|
|
|
main = withSystemTempDirectory "privoxy" (forM_ urls . generateConfig)
|
|
|
|
|
|
|
|
|
|
|
|
get :: Segment () -> IO String
|
|
|
|
get = fmap head . run . strings
|
|
|
|
|
|
|
|
|
|
|
|
notify :: String -> Segment () -> IO ()
|
|
|
|
notify msg action =
|
|
|
|
putStr (printf " %s..." msg) >> run action >> putStrLn " done"
|
|
|
|
|
|
|
|
|
|
|
|
generateConfig :: FilePath -> Url -> IO ()
|
|
|
|
generateConfig dir url = do
|
|
|
|
let list = takeBaseName url
|
|
|
|
file = dir </> list <.> "txt"
|
|
|
|
action = dir </> list <.> "action"
|
|
|
|
filter = dir </> list <.> "filter"
|
|
|
|
|
|
|
|
putStrLn ("generating config for " ++ list)
|
|
|
|
notify "downloading" $ shell (printf "CURL_CA_BUNDLE=/etc/ssl/certs/ca-bundle.crt curl -so %s %s" file url)
|
|
|
|
|
|
|
|
banner <- get (grep "-E" "^.*\\[Adblock.*\\].*$" file)
|
|
|
|
when (null banner) (fail "Not a valid adblock list")
|
|
|
|
notify "generating actionfile" $ do
|
|
|
|
shell (printf "echo -e '{ +block{%s} }' > %s" list action)
|
|
|
|
shell (printf "sed '%s' %s >> %s" (rules !! 0) file action)
|
|
|
|
|
|
|
|
notify "generating filterfile" $ do
|
|
|
|
shell (printf "echo 'FILTER: %s Tag filter of %s' > %s" list list filter)
|
|
|
|
shell (printf "sed '%s' %s >> %s" (rules !! 1) file filter)
|
|
|
|
|
|
|
|
notify "adding filterfile to actionfile" $ do
|
|
|
|
shell (printf "echo '{ +filter{%s} }' >> %s" list action)
|
|
|
|
shell (printf "echo '*' >> %s" action)
|
|
|
|
|
|
|
|
notify "generating and adding whitelist" $ do
|
|
|
|
shell (printf "echo '{ -block }' >> %s" action)
|
|
|
|
shell (printf "sed '%s' %s >> %s" (rules !! 2) file action)
|
|
|
|
|
|
|
|
notify "generating and adding image handler" $ do
|
|
|
|
shell (printf "echo '{ -block +handle-as-image }' >> %s" action)
|
|
|
|
shell (printf "sed '%s' %s >> %s" (rules !! 3) file action)
|
|
|
|
|
|
|
|
notify "copying files to destination" $ liftIO $ do
|
|
|
|
createDirectoryIfMissing True privoxy
|
|
|
|
copyFile action (replaceDirectory action privoxy)
|
|
|
|
copyFile filter (replaceDirectory filter privoxy)
|
|
|
|
|