{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE ExtendedDefaultRules #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

-- Developer allocation
--
-- : out devalloc
-- : dep acid-state
-- : dep clay
-- : dep cmark
-- : sys cmark
-- : dep cmark-lucid
-- : dep docopt
-- : dep envy
-- : dep github
-- : dep http-api-data
-- : dep ixset
-- : dep lucid
-- : dep protolude
-- : dep rainbow
-- : dep req
-- : dep safecopy
-- : dep servant
-- : dep servant-auth
-- : dep servant-auth-server
-- : dep servant-lucid
-- : dep servant-server
-- : dep tasty
-- : dep tasty-hunit
-- : dep tasty-quickcheck
-- : dep uuid
-- : dep vector
-- : dep vector-algorithms
-- : dep warp
module Biz.Devalloc
  ( main,
    test,
  )
where

import Alpha hiding (rem, (<.>))
import Biz.App (CSS (..), HtmlApp (..))
import qualified Biz.Cli as Cli
import qualified Biz.Id as Id
import qualified Biz.Log as Log
import qualified Biz.Look
import Biz.Test ((@=?), (@?!=), (@?=))
import qualified Biz.Test as Test
import qualified CMark as Cmark
import qualified CMark.Lucid as Cmark
import Clay (em, pct, px, rem, sec, (?))
import qualified Clay
import qualified Clay.Font
import qualified Clay.Render as Clay
import qualified Control.Concurrent.Async as Async
import qualified Control.Exception as Exception
import Control.Monad ((>=>))
import Crypto.JOSE.JWK (JWK)
import Data.Acid (makeAcidic)
import qualified Data.Acid as Acid
import qualified Data.Acid.Advanced as Acid
import qualified Data.Acid.Local as Acid
import qualified Data.Aeson as Aeson
import qualified Data.ByteString.Lazy as LBS
import Data.Data (Data, Typeable)
import Data.IxSet (Indexable (..), IxSet, ixFun, ixSet, (&&&), (@=))
import qualified Data.IxSet as IxSet
import qualified Data.List as List
import Data.SafeCopy (base, deriveSafeCopy)
import qualified Data.SafeCopy as SafeCopy
import qualified Data.Set as Set
import qualified Data.String as String
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Encoding
import qualified Data.Time.Calendar as Time
import qualified Data.Time.Clock as Time
import qualified Data.Time.Format as Time
import Data.Vector (Vector)
import qualified Data.Vector as Vector
-- import qualified Data.Vector.Algorithms.Intro as Vector
import qualified GitHub
import qualified Lucid
import qualified Lucid.Base as Lucid
import qualified Lucid.Servant as Lucid
import Network.HTTP.Req ((/:), (=:))
import qualified Network.HTTP.Req as Req
import qualified Network.Wai as Wai
import qualified Network.Wai.Handler.Warp as Warp
import Servant
import Servant.API.Generic (ToServantApi, genericApi, toServant, (:-))
import qualified Servant.Auth as Auth
import qualified Servant.Auth.Server as Auth
import qualified Servant.HTML.Lucid as Lucid
import Servant.Server.Generic (AsServer)
import qualified System.Directory as Directory
import qualified System.Environment as Env
import qualified System.Envy as Envy
import System.FilePath ((<.>), (</>))
import qualified System.Process as Process
import qualified Web.FormUrlEncoded as Web

-- * persistent data

-- This must go first because of template haskell splicing.
--
-- When changing a persisted type `T`, first copy the type `T == T0`, then make
-- the `SafeCopy.Migrate T` class compile, then make changes to `T`. If you
-- don't, there will be a runtime exception when you try to start the new
-- service. I'm not sure how to guard against this, except maybe run a test
-- deployment by copying a database backup locally, or something.

newtype UserEmail = UserEmail {unUserEmail :: Maybe Text}
  deriving (Eq, Ord, Data, Typeable, Generic, Show)

instance Aeson.ToJSON UserEmail

instance Aeson.FromJSON UserEmail

instance Auth.ToJWT UserEmail

instance Auth.FromJWT UserEmail

instance Lucid.ToHtml UserEmail where
  toHtmlRaw = Lucid.toHtml
  toHtml (UserEmail (Just email)) = Lucid.toHtml email
  toHtml (UserEmail Nothing) = mempty

$(deriveSafeCopy 0 'base ''UserEmail)

-- | In 'GitHub.Data.Definitions' this is '(Id User)', but I don't want the
-- extra complexity of 'Id', so just store the underlying Int
newtype GitHubId = GitHubId {unGitHubId :: Int}
  deriving (Eq, Ord, Data, Typeable, Generic, Show)

instance Aeson.ToJSON GitHubId

instance Aeson.FromJSON GitHubId

instance Auth.ToJWT GitHubId

instance Auth.FromJWT GitHubId

$(deriveSafeCopy 0 'base ''GitHubId)

data Subscription = Free | Invoice
  deriving (Eq, Data, Typeable, Ord, Generic, Show)

instance Web.FromForm Subscription where
  fromForm f = case Web.parseUnique "user-subscription" f of
    Right "Free" -> Right Free
    Right "Invoice" -> Right Invoice
    Right x -> Left <| "could not parse form value: " <> x
    Left x -> Left <| "could not parse form value: " <> x

instance Aeson.ToJSON Subscription

instance Aeson.FromJSON Subscription

instance Auth.ToJWT Subscription

instance Auth.FromJWT Subscription

$(deriveSafeCopy 0 'base ''Subscription)

-- | The main representation of a user.
data User = User
  { userEmail :: UserEmail,
    userGitHubId :: GitHubId,
    -- | So we can make GitHub API calls on their behalf.
    userGitHubToken :: Text,
    userSubscription :: Subscription,
    userId :: Id.Id User
  }
  deriving (Eq, Data, Typeable, Ord, Generic, Show)

instance Aeson.ToJSON User

instance Aeson.FromJSON User

instance Auth.ToJWT User

instance Auth.FromJWT User

$(deriveSafeCopy 0 'base ''User)

instance Indexable User where
  empty =
    ixSet
      [ ixFun <| \User {..} -> [userEmail],
        ixFun <| \User {..} -> [userGitHubId],
        ixFun <| \User {..} -> [userSubscription]
      ]

newtype Commit = Sha Text
  deriving (Eq, Data, Typeable, Ord, Generic, Show)

instance Lucid.ToHtml Commit where
  toHtmlRaw = Lucid.toHtml
  toHtml (Sha txt) = Lucid.toHtml txt

$(deriveSafeCopy 0 'base ''Commit)

newtype URL = URL Text
  deriving (Eq, Data, Typeable, Ord, Generic, Show)

instance Lucid.ToHtml URL where
  toHtmlRaw = Lucid.toHtml
  toHtml (URL txt) = Lucid.toHtml txt

$(deriveSafeCopy 0 'base ''URL)

data Visibility = Public | Private
  deriving (Eq, Ord, Generic, Show, Data, Typeable)

$(deriveSafeCopy 0 'base ''Visibility)

data Analysis0 = Analysis0
  { analysisId :: Id.Id Analysis0,
    url :: URL,
    bareRepo :: FilePath,
    blackholes :: [Text],
    liabilities :: [Text],
    stale :: [(FilePath, Int)],
    score :: Integer,
    totalFiles :: Integer,
    activeAuthors :: [Text],
    commit :: Commit,
    askedBy :: Id.Id User
  }
  deriving (Eq, Ord, Generic, Show, Data, Typeable)

$(deriveSafeCopy 0 'base ''Analysis0)

-- | The result of analyzing a git repo.
data Analysis = Analysis
  { -- | Monotonic incrementing integer id
    analysisId :: Id.Id Analysis,
    -- | Canonical URL for the repo. I wish this was structured data instead of
    -- just Text.
    url :: URL,
    -- | Where the repo is stored on the local disk.
    bareRepo :: FilePath,
    -- | If the repo is OSS or not
    repoVisibility :: Visibility,
    -- | A path with no active contributors
    blackholes :: [Text],
    -- | A path with < 3 active contributors
    liabilities :: [Text],
    -- | Files that have not been touched in 6 months
    stale :: [(FilePath, Int)],
    -- | Total score for the repo
    score :: Integer,
    -- | Total number of files
    totalFiles :: Integer,
    -- | List of all the active users we care about
    activeAuthors :: [Text],
    -- | Which commit this analysis was run against.
    commit :: Commit,
    -- | Who asked for this analysis
    askedBy :: Id.Id User
  }
  deriving (Eq, Ord, Generic, Show, Data, Typeable)

instance SafeCopy.Migrate Analysis where
  type MigrateFrom Analysis = Analysis0
  migrate Analysis0 {..} =
    Analysis
      { analysisId = Id.mk (Proxy :: Proxy Analysis) <| Id.untag analysisId,
        repoVisibility = Public,
        ..
      }

$(deriveSafeCopy 0 'base ''Id.Id)
$(deriveSafeCopy 0 'base ''Analysis)

instance Indexable Analysis where
  empty =
    ixSet
      [ ixFun <| \Analysis {..} -> [analysisId],
        ixFun <| \Analysis {..} -> [askedBy],
        ixFun <| \Analysis {..} -> [url],
        ixFun <| \Analysis {..} -> [commit]
      ]

-- | The database.
data Keep = Keep
  { users :: IxSet User,
    nextUserId :: Id.Id User,
    analyses :: IxSet Analysis,
    nextAnalysisId :: Id.Id Analysis
  }
  deriving (Data, Typeable)

$(deriveSafeCopy 0 'base ''Keep)

createUser :: User -> Acid.Update Keep User
createUser u = do
  keep <- get
  let newUser = u {userId = nextUserId keep}
  put
    <| keep
      { users = IxSet.insert newUser (users keep),
        nextUserId = succ <| nextUserId keep
      }
  pure newUser

updateUser :: User -> Acid.Update Keep User
updateUser u@User {..} = do
  keep <- get
  put <| keep {users = IxSet.updateIx userGitHubId u (users keep)}
  pure u

getUserByEmail :: UserEmail -> Acid.Query Keep (Maybe User)
getUserByEmail email = do
  Keep {..} <- ask
  pure <| IxSet.getOne <| users @= email

getUserByGitHubId :: GitHubId -> Acid.Query Keep (Maybe User)
getUserByGitHubId id = do
  Keep {..} <- ask
  pure <| IxSet.getOne <| users @= id

getUsers :: Acid.Query Keep [User]
getUsers = do
  Keep {..} <- ask
  pure <| IxSet.toList users

createAnalysis :: Analysis -> Acid.Update Keep Analysis
createAnalysis a = do
  keep@Keep {..} <- get
  let newAnalysis = a {analysisId = nextAnalysisId} :: Analysis
  put
    <| keep
      { analyses = IxSet.insert newAnalysis analyses,
        nextAnalysisId = succ nextAnalysisId
      }
  pure newAnalysis

getAnalysisById :: Id.Id Analysis -> Acid.Query Keep (Maybe Analysis)
getAnalysisById id = do
  Keep {..} <- ask
  pure <| IxSet.getOne <| analyses @= id

getAllAnalyses :: Acid.Query Keep [Analysis]
getAllAnalyses = do
  Keep {..} <- ask
  pure <| IxSet.toList analyses

getAnalysesByAsker :: User -> Acid.Query Keep [Analysis]
getAnalysesByAsker user = do
  Keep {..} <- ask
  pure <| IxSet.toList <| analyses @= userId user

getAnalysisByUrlAndCommit :: URL -> Commit -> Acid.Query Keep (Maybe Analysis)
getAnalysisByUrlAndCommit url sha = do
  Keep {..} <- ask
  pure <| IxSet.getOne <| analyses @= url &&& analyses @= sha

$( makeAcidic
     ''Keep
     [ 'createUser,
       'updateUser,
       'getUsers,
       'getUserByEmail,
       'getUserByGitHubId,
       'createAnalysis,
       'getAnalysisById,
       'getAllAnalyses,
       'getAnalysesByAsker,
       'getAnalysisByUrlAndCommit
     ]
 )

upsertGitHubUser ::
  Acid.AcidState Keep ->
  ByteString ->
  GitHub.User ->
  IO (Either Text User)
upsertGitHubUser keep tok ghUser =
  ghUser
    |> GitHub.userId
    |> GitHub.untagId
    |> GitHubId
    |> GetUserByGitHubId
    |> Acid.query keep
    +> \case
      Just user ->
        -- if we already know this user, we need to refresh the token
        UpdateUser user {userGitHubToken = Encoding.decodeUtf8 tok}
          |> Acid.update keep
      Nothing ->
        CreateUser
          User
            { userEmail = UserEmail <| GitHub.userEmail ghUser,
              userGitHubId = GitHubId <. GitHub.untagId <| GitHub.userId ghUser,
              userGitHubToken = Encoding.decodeUtf8 tok,
              userSubscription = Free,
              userId = mempty
            }
          |> Acid.update keep
    /> Right

test_upsertGitHubUser :: IO (Config, Application, Acid.AcidState Keep) -> Test.Tree
test_upsertGitHubUser load =
  Test.group
    "upsertUser"
    [ Test.unit "userId is not mempty" <| do
        (_, _, k) <- load
        Right User {..} <- upsertGitHubUser k "token" ghUser
        userId @?!= mempty,
      Test.unit "creates user when email is empty" <| do
        (_, _, k) <- load
        Right User {..} <- upsertGitHubUser k "token" ghUser {GitHub.userEmail = Nothing}
        userEmail @?!= UserEmail Nothing
    ]
  where
    ghUser =
      GitHub.User
        { GitHub.userId = GitHub.mkId (Proxy :: Proxy GitHub.User) 123,
          GitHub.userEmail = Just "user@example.com",
          GitHub.userLogin = "example",
          GitHub.userName = Nothing,
          GitHub.userType = GitHub.OwnerUser,
          GitHub.userCreatedAt =
            Time.UTCTime (Time.ModifiedJulianDay 1) (Time.secondsToDiffTime 100),
          GitHub.userPublicGists = 123,
          GitHub.userAvatarUrl = GitHub.URL "http://example.com",
          GitHub.userFollowers = 0,
          GitHub.userFollowing = 0,
          GitHub.userHireable = Nothing,
          GitHub.userBlog = Nothing,
          GitHub.userBio = Nothing,
          GitHub.userPublicRepos = 0,
          GitHub.userLocation = Nothing,
          GitHub.userCompany = Nothing,
          GitHub.userUrl = GitHub.URL "http://example.com",
          GitHub.userHtmlUrl = GitHub.URL "http://example.com"
        }

init :: Keep
init =
  Keep
    { nextAnalysisId = Id.mk (Proxy :: Proxy Analysis) 1,
      nextUserId = Id.mk (Proxy :: Proxy User) 1,
      users = IxSet.empty,
      analyses = IxSet.empty
    }

-- * main and test

main :: IO ()
main = Cli.main <| Cli.Plan help move test tidy

help :: Cli.Docopt
help =
  [Cli.docopt|
devalloc

Usage:
  devalloc [--quiet]
  devalloc test
|]

move :: Cli.Arguments -> IO ()
move args =
  Exception.bracket
    (startup <| args `Cli.has` Cli.longOption "quiet")
    shutdown
    run

startup :: Bool -> IO (Config, Application, Acid.AcidState Keep)
startup quiet = do
  cfg <- Envy.decodeWithDefaults Envy.defConfig
  oAuthArgs <- Envy.decodeWithDefaults Envy.defConfig
  kp <- Acid.openLocalStateFrom (keep cfg) init :: IO (Acid.AcidState Keep)
  jwk <- Auth.generateKey
  unless quiet <| do
    Log.info ["@", "devalloc"] >> Log.br
    Log.info ["area", show <| area cfg] >> Log.br
    Log.info ["port", show <| port cfg] >> Log.br
    Log.info ["depo", Text.pack <| depo cfg] >> Log.br
    Log.info ["keep", Text.pack <| keep cfg] >> Log.br
  let jwtCfg = Auth.defaultJWTSettings jwk
  let cooks = case area cfg of
        Test -> testCookieSettings
        Live -> liveCookieSettings
  let ctx = cooks :. jwtCfg :. EmptyContext
  let app = serveWithContext paths ctx (toServant <| htmlApp cooks kp cfg jwk oAuthArgs)
  pure (cfg, app, kp)

shutdown :: (Config, Application, Acid.AcidState Keep) -> IO ()
shutdown (_, _, kp) = Acid.createCheckpointAndClose kp

tidy :: Config -> IO ()
tidy Config {..} = Directory.removeDirectoryRecursive keep

run :: (Config, Wai.Application, Acid.AcidState Keep) -> IO ()
run (cfg, app, _) = Warp.run (port cfg) (logMiddleware app)

logMiddleware :: Wai.Middleware
logMiddleware app req sendResponse =
  app req <| \res ->
    Log.info
      [ str <| Wai.requestMethod req,
        show <| Wai.remoteHost req,
        str <| Wai.rawPathInfo req
      ]
      >> Log.br
      >> sendResponse res

liveCookieSettings :: Auth.CookieSettings
liveCookieSettings =
  Auth.defaultCookieSettings
    { Auth.cookieIsSecure = Auth.Secure,
      -- TODO: fix this, add js snippet
      Auth.cookieXsrfSetting = Nothing
    }

testCookieSettings :: Auth.CookieSettings
testCookieSettings =
  Auth.defaultCookieSettings
    { Auth.cookieIsSecure = Auth.NotSecure,
      Auth.cookieXsrfSetting = Nothing
    }

test :: Test.Tree
test =
  Test.group
    "Biz.Devalloc"
    [ test_calculateScore,
      Test.with
        (startup True)
        (\t@(c, _, _) -> shutdown t >> tidy c)
        test_upsertGitHubUser,
      Test.with
        (startup True)
        (\t@(c, _, _) -> shutdown t >> tidy c)
        test_analyzeGitHub
    ]

-- * app configurations

data Area = Test | Live
  deriving (Generic, Show)

instance Envy.Var Area where
  toVar = show
  fromVar "Test" = Just Test
  fromVar "Live" = Just Live
  fromVar _ = Just Test

data Config = Config
  { port :: Warp.Port,
    -- | The repo depo! Depository of repositories!
    depo :: FilePath,
    keep :: FilePath,
    area :: Area
  }
  deriving (Generic, Show)

instance Envy.DefConfig Config where
  defConfig =
    Config
      { port = 8005,
        depo = "_/var/devalloc/depo",
        keep = "_/var/devalloc/keep",
        area = Test
      }

instance Envy.FromEnv Config

-- | These are arguments that a 3rd-party OAuth provider needs in order for us
-- to authenticate a user.
data OAuthArgs = OAuthArgs
  { githubClientSecret :: Text,
    githubClientId :: Text,
    githubState :: Text
  }
  deriving (Generic, Show)

instance Envy.DefConfig OAuthArgs where
  defConfig =
    OAuthArgs
      { githubClientSecret = mempty,
        githubClientId = mempty,
        githubState = mempty
      }

instance Envy.FromEnv OAuthArgs

-- * paths and pages

-- | Wraps pages in default HTML
instance Lucid.ToHtml a => Lucid.ToHtml (HtmlApp a) where
  toHtmlRaw = Lucid.toHtml
  toHtml (HtmlApp x) =
    Lucid.doctypehtml_ <| do
      Lucid.head_ <| do
        Lucid.title_ "Devalloc.io :: Know your codebase, know your team."
        Lucid.meta_
          [ Lucid.name_ "description",
            Lucid.content_ "Know your codebase, know your team."
          ]
        Lucid.meta_
          [ Lucid.name_ "viewport",
            Lucid.content_ "width=device-width, initial-scale=1"
          ]
        Lucid.meta_ [Lucid.charset_ "utf-8"]
        jsRef "//unpkg.com/turbolinks@5.2.0/dist/turbolinks.js"
        cssRef "/css/main.css"
      Lucid.body_ (Lucid.toHtml x)
    where
      jsRef _href =
        Lucid.with
          (Lucid.script_ mempty)
          [ Lucid.makeAttribute "src" _href,
            Lucid.makeAttribute "async" mempty,
            Lucid.makeAttribute "defer" mempty
          ]
      cssRef _href =
        Lucid.with
          (Lucid.link_ mempty)
          [ Lucid.rel_ "stylesheet",
            Lucid.type_ "text/css",
            Lucid.href_ _href
          ]

-- | All of the routes in the app.
data Paths path = Paths
  { home ::
      path
        :- Get '[Lucid.HTML] (HtmlApp Home),
    login ::
      path
        :- "login"
        :> Verb 'GET 301 '[Lucid.HTML] (Headers '[Header "Location" Text] NoContent),
    githubAuth ::
      path
        :- "auth"
        :> "github"
        :> "callback"
        :> QueryParam "code" Text
        :> Get '[Lucid.HTML] (SetCookies (HtmlApp UserAccount)),
    getAccount ::
      path
        :- Auth.Auth '[Auth.Cookie] User
        :> "account"
        :> Get '[Lucid.HTML] (HtmlApp UserAccount),
    postAccount ::
      path
        :- Auth.Auth '[Auth.Cookie] User
        :> "account"
        :> ReqBody '[FormUrlEncoded] Subscription
        :> Post '[Lucid.HTML] (HtmlApp UserAccount),
    selectRepo ::
      path
        :- Auth.Auth '[Auth.Cookie] User
        :> "select-repo"
        :> Get '[Lucid.HTML] (HtmlApp SelectRepo),
    getAnalyses ::
      path
        :- Auth.Auth '[Auth.Cookie] User
        :> "analysis"
        :> Get '[Lucid.HTML] (HtmlApp Analyses),
    getAnalysis ::
      path
        :- Auth.Auth '[Auth.Cookie] User
        :> "analysis"
        :> Capture "analysisId" (Id.Id Analysis)
        :> Get '[Lucid.HTML] (HtmlApp AnalysisDisplay),
    githubAnalysis ::
      path
        :- Auth.Auth '[Auth.Cookie] User
        :> "analysis"
        :> "github"
        :> Capture "user" Text
        :> Capture "repo" Text
        :> Get '[Lucid.HTML] (HtmlApp AnalysisDisplay),
    css ::
      path
        :- "css"
        :> "main.css"
        :> Get '[CSS] Text
  }
  deriving (Generic)

type SetCookies ret =
  (Headers '[Header "Set-Cookie" Auth.SetCookie, Header "Set-Cookie" Auth.SetCookie] ret)

paths :: Proxy (ToServantApi Paths)
paths = genericApi (Proxy :: Proxy Paths)

guardAuth ::
  MonadError ServerError m =>
  Auth.AuthResult a ->
  m a
guardAuth = \case
  Auth.NoSuchUser -> throwError err401 {errBody = "No such user"}
  Auth.BadPassword -> throwError err401 {errBody = "Bad password"}
  Auth.Indefinite -> throwError err401 {errBody = "Incorrect authentication method"}
  Auth.Authenticated user -> pure user

requiredScopes :: Set Text
requiredScopes = Set.fromList ["repo"]

guardScope :: Text -> Handler ()
guardScope =
  Text.split (== ',')
    .> Set.fromList
    .> Set.isSubsetOf requiredScopes
    .> ( \ok ->
           unless ok
             <| throwError err503 {errBody = "Scopes are not correct"}
       )

-- | Main HTML handlers for all paths.
htmlApp ::
  Auth.CookieSettings ->
  Acid.AcidState Keep ->
  Config ->
  JWK ->
  OAuthArgs ->
  Paths AsServer
htmlApp cooks kp cfg jwk oAuthArgs =
  Paths
    { home =
        pure <. HtmlApp <| Home oAuthArgs,
      login =
        pure <| addHeader (githubLoginUrl oAuthArgs) NoContent,
      githubAuth = \case
        Nothing -> throwError err503 {errBody = "Bad response from GitHub API"}
        Just code -> do
          OAuthResponse {..} <- githubOauth oAuthArgs code |> liftIO
          guardScope scope
          let token = Encoding.encodeUtf8 access_token
          let warn :: Text -> Handler a
              warn msg =
                Log.warn [msg]
                  >> Log.br
                  |> liftIO
                  >> throwError err502 {errBody = str msg}
          user <-
            GitHub.userInfoCurrentR
              |> GitHub.github (GitHub.OAuth token)
              |> liftIO
              +> either (show .> warn) pure
              +> upsertGitHubUser kp token
              .> liftIO
              +> either warn pure
          Auth.acceptLogin cooks (Auth.defaultJWTSettings jwk) user
            |> liftIO
            +> \case
              Nothing -> throwError err502 {errBody = "login didn't work"}
              -- I think this should redirect to instead of rendering UserAccount
              Just applyCookies ->
                UserAccount user
                  |> HtmlApp
                  |> applyCookies
                  |> pure,
      getAccount =
        guardAuth >=> UserAccount .> HtmlApp .> pure,
      postAccount = \a subscription ->
        guardAuth a
          +> \user ->
            UpdateUser user {userSubscription = subscription}
              |> Acid.update' kp
              +> UserAccount
              .> HtmlApp
              .> pure,
      selectRepo =
        guardAuth
          >=> \user@User {..} ->
            GitHub.github
              (GitHub.OAuth <| Encoding.encodeUtf8 userGitHubToken)
              (GitHub.currentUserReposR GitHub.RepoPublicityAll GitHub.FetchAll)
              |> liftIO
              +> \case
                Left err -> throwError err502 {errBody = show err}
                Right repos -> pure <. HtmlApp <| SelectRepo user repos,
      getAnalyses =
        guardAuth
          >=> \user@User {..} ->
            GetAnalysesByAsker user
              |> Acid.query' kp
              +> Analyses user
              .> HtmlApp
              .> pure,
      getAnalysis = \a analysisId ->
        guardAuth a
          +> \user ->
            GetAnalysisById analysisId
              |> Acid.query' kp
              +> \case
                Nothing -> throwError err404
                Just analysis -> pure <| HtmlApp <| AnalysisDisplay user analysis,
      githubAnalysis = \a owner repo ->
        guardAuth a
          +> \user ->
            analyzeGitHub kp user (depo cfg) owner repo
              |> liftIO
              +> AnalysisDisplay user
              .> HtmlApp
              .> pure,
      css =
        pure <. toStrict <. Clay.render <| do
          let yellow = "#ffe000"
          let black = "#121212"
          Biz.Look.fuckingStyle

          Biz.Look.whenDark <| do
            "body" ? do
              Clay.backgroundColor black
            "a:link" <> "a:visited" ? do
              Clay.textDecorationColor Clay.white
              Clay.color Clay.white
            "a:hover" ? do
              Clay.textDecorationColor yellow
            "select" <> "button" <> "input" ? do
              Clay.backgroundColor black
              Clay.color Clay.white

          Biz.Look.whenLight <| do
            "body" ? do
              Clay.color black
            "a:link" <> "a:visited" ? do
              Clay.textDecorationColor black
              Clay.color black
            "a:hover" ? do
              Clay.textDecorationColor yellow
            "select" <> "button" <> "input" ? do
              Clay.backgroundColor Clay.white
              Clay.color black

          "body" ? Biz.Look.fontStack
          "header" ? do
            Clay.maxWidth (pct 100)
          "footer" ? do
            Clay.fontStyle Clay.italic
            Clay.fontSize (rem 0.8)
            Clay.marginTop (em 6)
            Clay.marginBottom (em 6)
          "a" ? do
            Clay.transition "all" (sec 0.2) Clay.ease 0
            Clay.transitionProperties
              [ "text-decoration-color",
                "text-decoration-thickness",
                "text-decoration-width"
              ]
            Clay.textDecoration Clay.underline
            Biz.Look.textDecorationThickness (em 0.1)
            Biz.Look.textDecorationWidth (em 0.1)
          "a:hover" ? do
            Clay.textDecorationColor yellow
            Clay.textDecoration Clay.underline
            Biz.Look.textDecorationThickness (em 0.2)
            Biz.Look.textDecorationWidth (em 0.2)

          "select" <> "button" <> "input" ? do
            Biz.Look.paddingAll (em 0.5)
            Biz.Look.marginX (em 0.5)
            Clay.borderColor yellow
            Clay.borderStyle Clay.solid

          "label" ? do
            Clay.display Clay.inlineBlock
            Clay.width (px 100)

          "nav" ? do
            Clay.display Clay.flex
            Clay.justifyContent Clay.spaceBetween
            "a" ? do
              Clay.padding (em 1) (em 1) (em 1) (em 1)
              Clay.display Clay.block
            "ul" ? do
              Clay.display Clay.flex
              Clay.justifyContent Clay.flexEnd
              Clay.listStyleType Clay.none
              Clay.margin (Clay.px 0) 0 0 0
              "li" ? do
                Clay.padding 0 (px 5) 0 (px 5)

          "#home" ? do
            Clay.textAlign Clay.center
            "h1" ? do
              Clay.fontSize (Clay.rem 3)
            "h1" <> "h2" ? do
              Clay.textAlign Clay.center
            "section" ? do
              Clay.padding (rem 3) 0 (rem 3) 0
            "a#try-button" <> "a#try-button:visited" ? do
              Clay.transition "all" (sec 0.2) Clay.ease 0
              Clay.transitionProperties
                ["color", "background-color", "border-color"]
              Clay.padding (em 0.5) (em 1) (em 0.5) (em 1)
              Clay.display Clay.flex
              Clay.flexDirection Clay.column
              Clay.margin (em 3) Clay.auto 0 Clay.auto
              Clay.width (px 250)
              Clay.borderWidth (px 1)
              Clay.borderStyle Clay.solid
              Clay.borderColor black
              Clay.backgroundColor yellow
              Clay.color black
              Clay.textDecoration Clay.none
              Clay.justifyContent Clay.center
              Clay.alignItems Clay.center
              Clay.fontWeight Clay.bold
              "small" ? do
                Clay.fontSize (px 10)
            "a#try-button:hover" ? do
              Clay.borderColor yellow
              Clay.color yellow
              Clay.backgroundColor black

          "#selectRepo" ? do
            "ul" ? do
              Clay.listStyleType Clay.none
              Clay.margin (px 0) 0 0 0
              Clay.padding (px 0) 0 0 0
              "li" ? do
                Clay.borderBottomWidth (px 1)
                Clay.borderBottomColor "#999"
                Clay.borderBottomStyle Clay.solid
                Clay.padding (em 1.5) 0 (em 1.5) 0
    }

-- | The front page pitch. Eventually I'd like to load the content from markdown
-- files or some other store of data so I can A/B test.
newtype Home = Home OAuthArgs

instance Lucid.ToHtml Home where
  toHtmlRaw = Lucid.toHtml
  toHtml (Home oAuthArgs) = do
    header Nothing
    Lucid.main_ [Lucid.id_ "home"] <| do
      section <| do
        h1 "Know your codebase."
        h1 "Know your team."
        p "Devalloc analyzes your codebase trends, finds patterns in how your developers work, and protects against tech debt."
        p "Just hook it up to your CI system - Devalloc warns you when it finds a problem."
        Lucid.toHtml <| tryButton oAuthArgs
      section <| do
        h2 "Identify blackholes in your codebase"
        p
          "What if none of your active employees have touched some part of the codebase? \
          \ This happens too often with legacy code, and then it turns into a huge source of tech debt. \
          \ Devalloc finds these \"blackholes\" and warns you about them so you can be proactive in eliminating tech debt."
      section <| do
        h2 "Find developer hot spots"
        p
          "Which pieces of code get continually rewritten, taking up valuable dev time? \
          \ Find these module hot spots before they become a costly time-sink."
      section <| do
        h2 "Protect against lost knowledge"
        p "Not everyone can know every part of a codebase. By finding pieces of code that only 1 or 2 people have touched, devalloc identifes siloed knowledge. This allows you to protect against the risk of this knowledge leaving the company if an employee leaves."
      section <| do
        h2 "Don't just measure code coverage - also know your dev coverage"
        p "No matter how smart your employees are, if you are under- or over-utilizing your developers then you will never get optimal performance from your team."
        p "Know how your devs work best: which ones have depth of knowledge, and which ones have breadth?"
      section <| do
        h2 "See how your teams *actually* organize themselves with cluster analysis"
        p "Does your team feel splintered or not cohesive? Which developers work best together? Devalloc analyzes the collaboration patterns between devs and helps you form optimal pairings and teams based on shared code and mindspace."
      section <| do
        h1 <| "Ready to get going?"
        Lucid.toHtml <| tryButton oAuthArgs
    footer
    where
      section = Lucid.section_
      markdown = Cmark.renderNode [] <. Cmark.commonmarkToNode []
      p = Lucid.p_ <. markdown
      h1 = Lucid.h1_
      h2 = Lucid.h2_ <. markdown

data Analyses = Analyses User [Analysis]

instance Lucid.ToHtml Analyses where
  toHtmlRaw = Lucid.toHtml
  toHtml (Analyses user@User {..} analyses) = do
    header <| Just user
    Lucid.main_ <| do
      Lucid.section_ <| do
        Lucid.h2_ "Your Analyses"
        Lucid.p_
          <| Lucid.a_
            [Lucid.linkHref_ "/" <| fieldLink selectRepo]
            "Analyze one of your repos"
        Lucid.div_ <| do
          forM_ analyses <| \Analysis {..} ->
            Lucid.a_
              [ href analysisId,
                style <| Biz.Look.marginAll (em 1)
                  <> Clay.textDecoration Clay.none
              ]
              <| do
                Lucid.div_ <| Lucid.toHtml url
                Lucid.div_ [style <| Clay.fontSizeCustom Clay.Font.small]
                  <| Lucid.toHtml commit
    footer
    where
      href aid = Lucid.linkHref_ "/" <| fieldLink getAnalysis aid

newtype UserAccount = UserAccount User

instance Lucid.ToHtml Subscription where
  toHtmlRaw = Lucid.toHtml
  toHtml Free = "Free"
  toHtml Invoice = "Invoice me"

linkAction_ :: ToHttpApiData a => Text -> a -> Lucid.Attribute
linkAction_ baseUrl = Lucid.action_ <. (baseUrl <>) <. Servant.toUrlPiece

instance Lucid.ToHtml UserAccount where
  toHtmlRaw = Lucid.toHtml
  toHtml (UserAccount user@User {..}) = do
    header <| Just user
    Lucid.main_ <| do
      Lucid.h1_ "Welcome!"
      Lucid.section_ <| do
        Lucid.h2_ "Subscription"
        let action = linkAction_ "/" <| fieldLink postAccount
        Lucid.form_ [action, Lucid.method_ "post"] <| do
          let name = "user-subscription"
          Lucid.label_ [Lucid.for_ name] "Your plan:"
          Lucid.select_ [Lucid.name_ name] <| do
            Lucid.option_
              (Lucid.value_ "Free" : isSelected Free)
              <| Lucid.toHtml Free
            Lucid.option_
              (Lucid.value_ "Invoice" : isSelected Invoice)
              <| Lucid.toHtml Invoice
          Lucid.input_ [Lucid.type_ "submit", Lucid.value_ "Save"]
        when (userSubscription == Invoice) <| do
          Lucid.p_ "Thanks! You will receive an invoice by email every month."
    footer
    where
      isSelected sel =
        if userSubscription == sel
          then [Lucid.selected_ <| tshow sel]
          else mempty

style :: Clay.Css -> Lucid.Attribute
style = Lucid.style_ <. toStrict <. Clay.renderWith Clay.htmlInline []

-- | A type for parsing JSON auth responses, used in 'githubOauth' below.
-- Should be moved to Biz.Auth with others.
data OAuthResponse = OAuthResponse
  { access_token :: Text,
    scope :: Text,
    token_type :: Text
  }
  deriving (Generic, Aeson.FromJSON)

-- | POST to GitHub's OAuth service and get the user's oAuth token.
githubOauth ::
  OAuthArgs ->
  Text ->
  -- | This should be GitHub.Token but GitHub.Auth doesn't export Token.
  IO OAuthResponse
githubOauth OAuthArgs {..} code =
  accessTokenRequest
    /> Req.responseBody
    |> Req.runReq Req.defaultHttpConfig
  where
    accessTokenRequest :: Req.Req (Req.JsonResponse OAuthResponse)
    accessTokenRequest =
      Req.req
        Req.POST
        (Req.https "github.com" /: "login" /: "oauth" /: "access_token")
        Req.NoReqBody
        Req.jsonResponse
        <| "client_id" =: githubClientId
        <> "client_secret" =: githubClientSecret
        <> "code" =: code
        <> "state" =: githubState

-- GitHub OAuth endpoint. For what the parameters mean, see:
-- https://docs.github.com/en/developers/apps/authorizing-oauth-apps
githubLoginUrl :: OAuthArgs -> Text
githubLoginUrl OAuthArgs {..} =
  "https://github.com/login/oauth/authorize?"
    <> encodeParams
      [ ("client_id", githubClientId),
        ("state", githubState),
        ("scope", Text.intercalate " " <| Set.toList requiredScopes)
      ]

-- | This view presents a list of repos to select for analysis.
data SelectRepo = SelectRepo User (Vector GitHub.Repo)

instance Lucid.ToHtml SelectRepo where
  toHtmlRaw = Lucid.toHtml
  toHtml (SelectRepo user repos) = do
    header <| Just user
    Lucid.main_ [Lucid.id_ "selectRepo"] <| do
      Lucid.h2_ "Select a repo to analyze"
      Lucid.ul_ <| Lucid.toHtml <| traverse_ displayRepo (Vector.toList repos)
    footer
    where
      displayRepo :: GitHub.Repo -> Lucid.Html ()
      displayRepo repo =
        Lucid.li_ <| do
          Lucid.a_
            [ Lucid.linkHref_ "/"
                <| fieldLink
                  githubAnalysis
                  (GitHub.untagName <| GitHub.simpleOwnerLogin <| GitHub.repoOwner repo)
                  (GitHub.untagName <| GitHub.repoName repo)
            ]
            <. Lucid.h3_
            <. Lucid.toHtml
            <. GitHub.untagName
            <| GitHub.repoName repo
          maybe mempty (Lucid.p_ <. Lucid.toHtml) (GitHub.repoDescription repo)

-- * parts

-- | Utility for turning a list of tuples into a URL querystring.
encodeParams :: [(Text, Text)] -> Text
encodeParams =
  Encoding.decodeUtf8
    <. LBS.toStrict
    <. Web.urlEncodeParams

-- | Login button for GitHub.
tryButton :: OAuthArgs -> Lucid.Html ()
tryButton oAuthArgs =
  Lucid.a_
    [Lucid.id_ "try-button", Lucid.href_ <| githubLoginUrl oAuthArgs]
    <| do
      "Give it a try with GitHub"
      Lucid.small_ "Free for a limited time, then $99 per month"

-- | Universal header
header :: Monad m => Maybe User -> Lucid.HtmlT m ()
header muser =
  Lucid.header_ <| do
    Lucid.nav_ <| do
      a "Devalloc" <| fieldLink home
      case muser of
        Nothing ->
          Lucid.ul_ <| do
            li "Login" <| fieldLink login
        Just _ ->
          Lucid.ul_ <| do
            li "Analyses" <| fieldLink getAnalyses
            li "Account" <| fieldLink getAccount
  where
    a txt href =
      Lucid.a_ [Lucid.linkHref_ "/" href] txt
    li txt href = Lucid.li_ <| a txt href

-- | Universal footer
footer :: Monad m => Lucid.HtmlT m ()
footer =
  Lucid.footer_ <| do
    Lucid.p_ <| Lucid.i_ "Copyright ©2020-2021 Devalloc.io"

-- * analysis

-- | I need more information than just 'Analysis' has to render a full, useful
-- web page, hence this type.
data AnalysisDisplay = AnalysisDisplay User Analysis

instance Lucid.ToHtml AnalysisDisplay where
  toHtmlRaw = Lucid.toHtml
  toHtml (AnalysisDisplay user anal) = do
    header <| Just user
    Lucid.main_ <| Lucid.toHtml anal
    footer

instance Lucid.ToHtml Analysis where
  toHtmlRaw = Lucid.toHtml
  toHtml = render .> Lucid.toHtml
    where
      render :: Analysis -> Lucid.Html ()
      render Analysis {..} = do
        Lucid.h1_ "Analysis Results"
        Lucid.h3_ "Total score:"
        Lucid.p_ <| Lucid.toHtml <| Text.pack <| show score
        Lucid.h3_ "Active authors:"
        Lucid.ul_ <| forM_ activeAuthors <| \author -> do
          Lucid.li_ <| Lucid.toHtml author
        Lucid.h3_ <| Lucid.toHtml <| "Total files: " <> tshow totalFiles
        Lucid.h3_ <| Lucid.toHtml <| "Found " <> slen blackholes <> " blackholes:"
        Lucid.ul_ <| do
          traverse_ (Lucid.toHtml .> Lucid.li_) blackholes
        Lucid.h3_ <| Lucid.toHtml <| "Found " <> slen liabilities <> " liabilities:"
        Lucid.ul_ <| do
          traverse_ (Lucid.toHtml .> Lucid.li_) liabilities
        Lucid.h3_ <| Lucid.toHtml <| "Found " <> slen stale <> " stale files:"
        Lucid.ul_ <| do
          forM_ stale <| \(path, days) ->
            Lucid.li_ <| Lucid.toHtml <| path <> " (" <> show days <> " days)"
      slen = tshow <. length

-- | Run a full analysis on a git repo
analyze :: Acid.AcidState Keep -> Id.Id User -> [Text] -> URL -> FilePath -> Bool -> IO Analysis
analyze keep askedBy activeAuthors url bareRepo repoPrivate = do
  commit <- Sha </ Text.strip </ Text.pack </ git ["log", "-n1", "--format=%H"]
  Acid.query keep (GetAnalysisByUrlAndCommit url commit) +> \case
    Just analysis -> pure analysis
    Nothing -> do
      tree <-
        git
          [ "ls-tree",
            "--full-tree",
            "--name-only",
            "-r", -- recurse into subtrees
            "HEAD"
          ]
          /> String.lines
      authors <- traverse (authorsFor bareRepo) tree :: IO [[(Text, Text, Text)]]
      let authorMap =
            zipWith
              ( \path authors_ ->
                  (path, authors_)
              )
              tree
              authors ::
              [(FilePath, [(Text, Text, Text)])]
      stalenessMap <- traverse (lastTouched bareRepo) tree
      let blackholes =
            [ Text.pack path
              | (path, authors_) <- authorMap,
                null (map third authors_ `List.intersect` activeAuthors)
            ]
      let liabilities =
            [ Text.pack path
              | (path, authors_) <- authorMap,
                length (map third authors_ `List.intersect` activeAuthors) < 3
            ]
      let numBlackholes = realToFrac <| length blackholes
      let numLiabilities = realToFrac <| length liabilities
      let numTotal = realToFrac <| length tree
      Analysis
        { analysisId = mempty,
          stale =
            [ (path, days)
              | (path, Just days) <- stalenessMap,
                days > 180
            ],
          score = calculateScore numTotal numBlackholes numLiabilities,
          totalFiles = toInteger <| length tree,
          repoVisibility = repoPrivate ?: (Private, Public),
          ..
        }
        |> CreateAnalysis
        |> Acid.update keep
  where
    third :: (a, b, c) -> c
    third (_, _, a) = a
    git args = Process.readProcess "git" (["--git-dir", bareRepo] ++ args) ""

-- | Does the aggregate score calculation given number of files found to be
-- blackholes, liabilities, etc.
calculateScore :: Double -> Double -> Double -> Integer
calculateScore 0 _ _ = 0
calculateScore a 0 0 | a > 0 = 100
calculateScore a b c | a < 0 || b < 0 || c < 0 = 0
calculateScore numTotal numBlackholes numLiabilities =
  max 0 <. round
    <| maxScore
    * (weightedBlackholes + weightedLiabilities + numGood)
    / numTotal
  where
    weightedBlackholes = numBlackholes * (5 / 10)
    weightedLiabilities = numLiabilities * (7 / 10)
    numGood = numTotal - numBlackholes - numLiabilities
    maxScore = 100.0

test_calculateScore :: Test.Tree
test_calculateScore =
  Test.group
    "calculateScore"
    [ Test.unit "perfect score" <| 100 @=? calculateScore 100 0 0,
      Test.unit "all blackholes" <| 50 @=? calculateScore 100 100 0,
      Test.unit "all liabilities" <| 70 @=? calculateScore 100 0 100,
      Test.prop "never > 100" <| \t b l -> calculateScore t b l <= 100,
      Test.prop "never < 0" <| \t b l -> calculateScore t b l >= 0
    ]

lastTouched :: FilePath -> FilePath -> IO (FilePath, Maybe Int)
lastTouched bareRepo path = do
  now <- Time.getCurrentTime
  timestamp <-
    Process.readProcess
      "git"
      [ "--git-dir",
        bareRepo,
        "log",
        "-n1",
        "--pretty=%aI",
        "--",
        path
      ]
      ""
      /> filter (/= '\n')
      /> Time.parseTimeM True Time.defaultTimeLocale "%Y-%m-%dT%H:%M:%S%z"
  pure (path, calculateAge now </ timestamp)
  where
    calculateAge now n = round <| Time.diffUTCTime now n / Time.nominalDay

-- | Given a git dir and a path inside the git repo, pure a list of tuples
-- with number of commits and author.
authorsFor ::
  FilePath ->
  FilePath ->
  -- | returns (number of commits, author name, author email)
  IO [(Text, Text, Text)]
authorsFor gitDir path =
  Process.readProcess
    "git"
    [ "--git-dir",
      gitDir,
      "shortlog",
      "--numbered",
      "--summary",
      "--email",
      "HEAD",
      "--",
      path
    ]
    ""
    /> Text.pack
    /> Text.lines
    /> map (Text.break (== '\t'))
    /> map
      ( \(commits, author) ->
          ( Text.strip commits,
            Text.strip <| Text.takeWhile (/= '<') author,
            Text.strip <| Text.dropAround (`elem` ['<', '>']) <| Text.dropWhile (/= '<') author
          )
      )

-- | Clones a repo from GitHub and does the analysis.
analyzeGitHub ::
  Acid.AcidState Keep ->
  -- | The User asking for the analysis, we auth as them
  User ->
  -- | The repo depo
  FilePath ->
  -- | GitHub owner
  Text ->
  -- | GitHub repo
  Text ->
  IO Analysis
analyzeGitHub keep User {..} depo o r = do
  activeAuthors <-
    getPeople
      /> Vector.map (GitHub.simpleUserLogin .> GitHub.userInfoForR)
      /> Vector.toList
      +> Async.mapConcurrently (GitHub.github ghAuth)
      /> map (either (const Nothing) GitHub.userEmail)
      /> catMaybes
  GitHub.github ghAuth (GitHub.repositoryR ghOwner ghRepo) +> \case
    Left err -> throwIO <| toException err
    Right repo -> do
      let GitHub.URL url = GitHub.repoHtmlUrl repo
      bareRepo <- fetchBareRepo depo <. GitHub.getUrl <| GitHub.repoHtmlUrl repo
      analyze keep userId activeAuthors (URL url) bareRepo (GitHub.repoPrivate repo)
  where
    ghAuth = GitHub.OAuth <| Encoding.encodeUtf8 userGitHubToken
    ghOwner = GitHub.mkName (Proxy :: Proxy GitHub.Owner) o
    ghRepo = GitHub.mkName (Proxy :: Proxy GitHub.Repo) r

    getPeople :: IO (Vector GitHub.SimpleUser)
    getPeople =
      Async.runConcurrently <| (Vector.++)
        </ Concurrently getCollaborators
        <*> Concurrently getTopContributors

    getCollaborators :: IO (Vector GitHub.SimpleUser)
    getCollaborators =
      GitHub.collaboratorsOnR ghOwner ghRepo GitHub.FetchAll
        |> GitHub.github ghAuth
        /> either mempty identity

    getTopContributors :: IO (Vector GitHub.SimpleUser)
    getTopContributors =
      -- 'False' means don't include anonymous contributors
      GitHub.contributorsR ghOwner ghRepo False GitHub.FetchAll
        |> GitHub.github ghAuth
        /> either mempty identity
        -- TODO: return top 10%; I can't figure out how to use this />
        -- Vector.sortBy
        --   ( \case
        --       GitHub.KnownContributor n _ _ _ _ _ -> n
        --       GitHub.AnonymousContributor n _ -> n
        --   )
        /> Vector.take 10
        /> Vector.mapMaybe GitHub.contributorToSimpleUser

test_analyzeGitHub :: IO (Config, Application, Acid.AcidState Keep) -> Test.Tree
test_analyzeGitHub load =
  Test.group
    "analyzeGitHub"
    [ Test.unit "can analyze a public repo (octocat/hello-world)" <| do
        (c, _, k) <- load
        -- get a token with 'repo' scope from GitHub and set in .envrc.local
        -- https://docs.github.com/en/github/authenticating-to-github/creating-a-personal-access-token
        tok <-
          Env.lookupEnv "GITHUB_USER_TOKEN"
            /> maybe (panic "need GITHUB_USER_TOKEN") Text.pack
        let user =
              User
                { userEmail = UserEmail <| Just "user@example.com",
                  userGitHubId = GitHubId 0,
                  userGitHubToken = tok,
                  userSubscription = Free,
                  userId = mempty
                }
        Analysis {..} <- analyzeGitHub k user (depo c) "octocat" "hello-world"
        url @?= URL "https://github.com/octocat/Hello-World"
        bareRepo @?= depo c <> "/github.com/octocat/Hello-World.git"
        length activeAuthors @?= 2
        activeAuthors @?= ["hire@spacegho.st", "octocat@github.com"]
        blackholes @?= ["README"]
        liabilities @?= ["README"]
        fst </ headMay stale @?= Just "README"
        score @?= 20
        totalFiles @?= 1
        commit @?= Sha "7fd1a60b01f91b314f59955a4e4d4e80d8edf11d"
    ]

-- | Clone the repo to @<Config.depo>/<url>@. If repo already exists, just do a
-- @git fetch@. pures the full path to the local repo.
fetchBareRepo :: FilePath -> Text -> IO FilePath
fetchBareRepo depo url =
  Directory.doesPathExist worktree
    +> fetchOrClone
    >> pure worktree
  where
    fetchOrClone True =
      Process.callProcess "git" ["--git-dir", worktree, "fetch", "--quiet", "origin"]
    fetchOrClone False =
      Process.callProcess "git" ["clone", "--quiet", "--bare", "--", Text.unpack url, worktree]
    removeScheme :: Text -> FilePath
    removeScheme u = Text.unpack <. Text.dropWhile (== '/') <. snd <| Text.breakOn "//" u
    worktree = depo </> removeScheme url <.> "git"