{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ExtendedDefaultRules #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# 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 ixset
-- : dep lucid
-- : dep protolude
-- : 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 uuid
-- : dep vector
-- : 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.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 Control.Exception as Exception
import Crypto.JOSE.JWK (JWK)
import Data.Acid (makeAcidic)
import qualified Data.Acid 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.String as String
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Encoding
import qualified Data.Time.Clock as Clock
import qualified Data.Time.Format as Time
import Data.Vector (Vector)
import qualified Data.Vector 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 Network.Wai.Middleware.RequestLogger (logStdout)
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.Envy as Envy
import System.FilePath ((<.>), (</>))
import qualified System.Process as Process
import qualified Web.FormUrlEncoded

-- * persistent data

-- this must go first because of template haskell splicing

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

instance Aeson.ToJSON UserEmail

instance Aeson.FromJSON UserEmail

instance Auth.ToJWT UserEmail

instance Auth.FromJWT UserEmail

$(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)

-- | 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
  }
  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 <| \u -> [userEmail u],
        ixFun <| \u -> [userGitHubId u]
      ]

-- | The database.
newtype Keep = Keep {users :: IxSet User}
  deriving (Data, Typeable)

instance Semigroup Keep where
  a <> b = Keep <| users a <> users b

instance Monoid Keep where
  mempty = Keep <| mempty []

$(deriveSafeCopy 0 'base ''Keep)

newUser :: User -> Acid.Update Keep User
newUser u = do
  keep <- get
  put <| keep {users = IxSet.insert u (users keep)}
  return u

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

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

$(makeAcidic ''Keep ['newUser, 'updateUser, 'getUserByEmail])

upsertGitHubUser :: Acid.AcidState Keep -> ByteString -> GitHub.User -> IO User
upsertGitHubUser keep tok ghUser = case GitHub.userEmail ghUser of
  -- Nothing -> throwError err502 { errBody = "No user email" }
  Nothing -> panic "No user email"
  Just email ->
    Acid.query keep (GetUserByEmail <| UserEmail email) >>= \case
      Just user ->
        -- need to refresh the token
        Acid.update keep <| UpdateUser user {userGitHubToken = Encoding.decodeUtf8 tok}
      Nothing ->
        Acid.update keep
          <| NewUser
            User
              { userEmail = UserEmail email,
                userGitHubId = GitHubId <. GitHub.untagId <| GitHub.userId ghUser,
                userGitHubToken = Encoding.decodeUtf8 tok
              }

-- * main and test

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

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

Usage:
  devalloc
  devalloc test
|]

move :: Cli.Arguments -> IO ()
move _ = Exception.bracket startup shutdown run
  where
    startup = do
      cfg <- Envy.decodeWithDefaults Envy.defConfig
      oAuthArgs <- Envy.decodeWithDefaults Envy.defConfig
      kp <- Acid.openLocalStateFrom (keep cfg) mempty :: IO (Acid.AcidState Keep)
      jwk <- Auth.generateKey
      putText "@"
      putText "devalloc"
      putText <| "area: " <> (show <| area cfg)
      putText <| "port: " <> (show <| port cfg)
      putText <| "depo: " <> (Text.pack <| depo cfg)
      putText <| "keep: " <> (Text.pack <| keep cfg)
      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)
      return (cfg, app, kp)
    shutdown :: (Config, Application, Acid.AcidState Keep) -> IO ()
    shutdown (_, _, kp) = Acid.closeAcidState kp
    run :: (Config, Wai.Application, Acid.AcidState Keep) -> IO ()
    run (cfg, app, _) = Warp.run (port cfg) (logStdout app)

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_analyzeGitHub,
      test_calculateScore
    ]

-- * 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 UserHome)),
    account ::
      path
        :- Auth.Auth '[Auth.Cookie] User
        :> "account"
        :> Get '[Lucid.HTML] (HtmlApp UserHome),
    selectRepo ::
      path
        :- Auth.Auth '[Auth.Cookie] User
        :> "select-repo"
        :> Get '[Lucid.HTML] (HtmlApp SelectRepo),
    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)

-- | 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 =
        auth kp cooks jwk oAuthArgs,
      account = \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 <| HtmlApp <| UserHome user,
      selectRepo = \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 -> do
          erepos <-
            liftIO
              <| GitHub.github
                (GitHub.OAuth <. Encoding.encodeUtf8 <| userGitHubToken user)
                (GitHub.currentUserReposR GitHub.RepoPublicityAll GitHub.FetchAll)
          case erepos of
            Left err -> throwError err502 {errBody = show err}
            Right repos -> pure <. HtmlApp <| SelectRepo user repos,
      githubAnalysis = \case
        Auth.NoSuchUser -> panic "No such user"
        Auth.BadPassword -> panic "Bad password"
        Auth.Indefinite -> panic "Incorrect authentication method"
        Auth.Authenticated user -> \owner repo ->
          liftIO
            <| analyzeGitHub
              (GitHub.OAuth <. Encoding.encodeUtf8 <| userGitHubToken user)
              cfg
              owner
              repo
            >>= AnalysisDisplay user
            .> HtmlApp
            .> pure,
      css =
        return <. toStrict <. Clay.render <| do
          let yellow = "#ffe000"
          let black = "#1d2d35" -- really a dark blue
          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

          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

          "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)
          "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" -- TODO: more subtle gradient?
                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 "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."
        Lucid.ul_ <| do
          Lucid.li_ "Find developer hot spots in your code: which pieces of code get continually rewritten, taking up valuable dev time?"
          Lucid.li_ "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

newtype UserHome = UserHome User

instance Lucid.ToHtml UserHome where
  toHtmlRaw = Lucid.toHtml
  toHtml (UserHome user) = do
    header <| Just user
    Lucid.main_ <| do
      Lucid.h1_ <. Lucid.toHtml <| "Welcome, " <> email <> "!"
      Lucid.p_
        <| Lucid.a_
          [Lucid.linkHref_ "/" <| fieldLink selectRepo]
          "Analyze one of your repos"
    footer
    where
      UserEmail email = userEmail user

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

-- | Login a user by authenticating with GitHub.
auth ::
  Acid.AcidState Keep ->
  Auth.CookieSettings ->
  JWK ->
  OAuthArgs ->
  Maybe Text ->
  Handler (SetCookies (HtmlApp UserHome))
auth _ _ _ _ Nothing = panic "no code from github api"
auth keep cooks jwt oAuthArgs (Just code) = do
  token <- liftIO <| getAccessToken oAuthArgs code
  eghUser <- liftIO <| (GitHub.github (GitHub.OAuth token) GitHub.userInfoCurrentR :: IO (Either GitHub.Error GitHub.User))
  ghUser <- case eghUser of
    Left err -> throwError err502 {errBody = show err}
    Right user -> return user
  user <- liftIO <| upsertGitHubUser keep token ghUser
  mApplyCookies <- liftIO <| Auth.acceptLogin cooks (Auth.defaultJWTSettings jwt) user
  case mApplyCookies of
    Nothing -> panic "login didn't work"
    Just applyCookies -> return <. applyCookies <. HtmlApp <| UserHome user

-- | POST to GitHub's oAuth service and return the user's oAuth token.
-- TODO: I can also get access scope etc from this response
getAccessToken ::
  OAuthArgs ->
  Text ->
  -- | This should be GitHub.Token but GitHub.Auth doesn't export Token.
  IO ByteString
getAccessToken OAuthArgs {..} code =
  accessTokenRequest
    >>= Req.responseBody
    /> access_token
    /> Encoding.encodeUtf8
    /> return
    |> Req.runReq Req.defaultHttpConfig
  where
    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

githubLoginUrl :: OAuthArgs -> Text
githubLoginUrl OAuthArgs {..} =
  "https://github.com/login/oauth/authorize?"
    <> encodeParams
      [ ("client_id", githubClientId),
        ("state", githubState)
      ]

-- | 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 <| mapM_ 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.FormUrlEncoded.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"

-- | 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
            li "Pricing" <| fieldLink home
        Just _ ->
          Lucid.ul_ <. li "My Account" <| fieldLink account
  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

-- | The result of analyzing a git repo.
data Analysis = Analysis
  { -- | Where the repo is stored on the local disk.
    bareRepo :: FilePath,
    -- | 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]
  }
  deriving (Show)

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_ <| Lucid.toHtml <| "Total files: " <> tshow totalFiles
        Lucid.h3_ <| Lucid.toHtml <| "Found " <> slen blackholes <> " blackholes:"
        Lucid.ul_ <| do
          mapM_ (Lucid.toHtml .> Lucid.li_) blackholes
        Lucid.h3_ <| Lucid.toHtml <| "Found " <> slen liabilities <> " liabilities:"
        Lucid.ul_ <| do
          mapM_ (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 = Text.pack <. show <. length
      tshow = Text.pack <. show

-- | Takes a list of active authors and a path to a bare git repo and runs a
-- regular analysis
analyze :: [Text] -> FilePath -> IO Analysis
analyze activeAuthors bareRepo = do
  tree <-
    Process.readProcess
      "git"
      [ "--git-dir",
        bareRepo,
        "ls-tree",
        "--full-tree",
        "--name-only",
        "-r", -- recurse into subtrees
        "HEAD"
      ]
      ""
      /> String.lines
  authors <- mapM (authorsFor bareRepo) tree :: IO [[(Text, Text, Text)]]
  let authorMap =
        zipWith
          ( \path authors_ ->
              (path, authors_)
          )
          tree
          authors ::
          [(FilePath, [(Text, Text, Text)])]
  stalenessMap <- mapM (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
  return
    Analysis
      { stale =
          [ (path, days)
            | (path, days) <- stalenessMap,
              days > 180
          ],
        score = calculateScore numTotal numBlackholes numLiabilities,
        totalFiles = toInteger <| length tree,
        ..
      }
  where
    third :: (a, b, c) -> c
    third (_, _, a) = a

calculateScore :: Double -> Double -> Double -> Integer
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
    ]

lastTouched :: FilePath -> FilePath -> IO (FilePath, Int)
lastTouched bareRepo path = do
  now <- Clock.getCurrentTime
  timestamp <-
    Process.readProcess
      "git"
      [ "--git-dir",
        bareRepo,
        "log",
        "-n1",
        "--pretty=%aI",
        "--",
        path
      ]
      ""
      /> filter (/= '\n')
      -- TODO: this fails if time is empty?
      /> Time.parseTimeOrError True Time.defaultTimeLocale "%Y-%m-%dT%H:%M:%S%z"
  let days = round <| Clock.diffUTCTime now timestamp / Clock.nominalDay
  return (path, days)

-- | Given a git dir and a path inside the git repo, return 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 =
  -- git shortlog writes to stderr for some reason, so we can't just use
  -- Process.readProcess
  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.
-- TODO: break this up into fetchGitHub and analyze functions.
analyzeGitHub ::
  GitHub.AuthMethod authMethod =>
  authMethod ->
  Config ->
  -- | GitHub owner
  Text ->
  -- | GitHub repo
  Text ->
  IO Analysis
analyzeGitHub githubAuth cfg o r = do
  -- I currently have no way of getting active users... getting a list of
  -- collaborators on a repo requires authentication for some reason.
  --
  -- If the owner is an organization, then we can just use org members, which is
  -- public too. And if the auth'ed user is a member of the org, then it returns
  -- all of the members, not just public ones, so that will work just fine.
  --
  -- In the meantime, what do? Maybe get the number of commits, and consider
  -- "active users" as the top 10% in terms of number of commits? Or ask for a
  -- list explicitly? If it is a personal repo, then I can assume that the owner
  -- is the only regular contributor, at least for now.
  --
  -- Right activeUsers <- GitHub.github () (GitHub.collaboratorsOnR ghOwner ghRepo GitHub.FetchAll)
  Right user <-
    GitHub.github
      githubAuth
      ( GitHub.userInfoForR
          <| GitHub.mkName (Proxy :: Proxy GitHub.User) o
      )
  -- assume the only active author is the owner, for now
  -- TODO: should be userEmail but that requires authentication?
  let activeAuthors = [require "user email" <| GitHub.userName user]
  eRepo <- GitHub.github githubAuth (GitHub.repositoryR ghOwner ghRepo)
  case eRepo of
    Left err -> throwIO <| toException err
    Right repo -> do
      bareRepo <- fetchBareRepo cfg <. GitHub.getUrl <| GitHub.repoHtmlUrl repo
      analyze activeAuthors bareRepo
  where
    ghOwner = GitHub.mkName (Proxy :: Proxy GitHub.Owner) o
    ghRepo = GitHub.mkName (Proxy :: Proxy GitHub.Repo) r

-- TODO: write this test
-- test_analyzeGitHub :: IO Analysis
-- test_analyzeGitHub = analyzeGitHub () Envy.defConfig "bsima" "bin"

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