Skip to content

Instantly share code, notes, and snippets.

@soenkehahn
Created August 4, 2019 16:57
Show Gist options
  • Save soenkehahn/748b4907ac2e92d478ac4ba3f32e85bc to your computer and use it in GitHub Desktop.
Save soenkehahn/748b4907ac2e92d478ac4ba3f32e85bc to your computer and use it in GitHub Desktop.
#!/usr/bin/env stack
{-
stack script
--resolver lts-13.29 --install-ghc
--package base
--package shake
--package hspec
--package getopt-generics
-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE ScopedTypeVariables #-}
import Development.Shake
import Test.Hspec
import Data.Foldable
import WithCli
import Data.Maybe
import System.Environment
main :: IO ()
main = do
withArgs [] $ hspec spec
withCli run
run :: Maybe Int -> Maybe Int -> IO ()
run (fromMaybe 1 -> from :: Int) (fromMaybe 2182 -> to :: Int) = do
forM_ [from .. to] $ \ n -> do
unit $ cmd "wget" (mkUrl n)
mkUrl :: Int -> String
mkUrl n =
"https://www.gunnerkrigg.com/comics/" ++
formattedN ++
".jpg"
where
formattedN =
replicate (8 - length (show n)) '0' ++ show n
spec :: Spec
spec = do
describe "mkUrl" $ do
it "returns the correctly formatted url" $ do
mkUrl 1 `shouldBe`
"https://www.gunnerkrigg.com/comics/00000001.jpg"
it "works for higher numbers" $ do
mkUrl 10 `shouldBe`
"https://www.gunnerkrigg.com/comics/00000010.jpg"
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment