{-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE NoImplicitPrelude #-} {-# OPTIONS_GHC -fno-warn-orphans #-} -- Developer allocation -- -- : out devalloc -- : dep clay -- dep cmark -- sys cmark -- : dep envy -- : dep github -- : dep lucid -- : dep protolude -- : dep req -- : dep servant -- : dep servant-lucid -- : dep servant-server -- : dep uuid -- : dep vector -- : dep warp module Biz.Devalloc ( main, ) where import Alpha import Biz.App (CSS (..), HtmlApp (..)) import qualified Biz.Look import qualified Clay import qualified Control.Exception as Exception import qualified Data.Aeson as Aeson import qualified Data.ByteString.Lazy as LBS import qualified Data.Text as Text import qualified Data.Text.Encoding as Encoding 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 Network.Wai.Application.Static (defaultWebAppSettings) import qualified Network.Wai.Handler.Warp as Warp import Network.Wai.Middleware.RequestLogger (logStdout) import Servant import Servant.HTML.Lucid import qualified System.Envy as Envy import qualified Web.FormUrlEncoded main :: IO () main = Exception.bracket startup shutdown run where startup = do cfg <- Envy.decodeWithDefaults Envy.defConfig oAuthArgs <- Envy.decodeWithDefaults Envy.defConfig putText "@" putText "devalloc" putText <| "port: " <> (show <| port cfg) return (cfg, serve (Proxy @AllPaths) <| paths cfg oAuthArgs) shutdown :: (Config, Application) -> IO () shutdown _ = pure () run :: (Config, Wai.Application) -> IO () run (cfg, app) = Warp.run (port cfg) (logStdout app) data Config = Config { port :: Warp.Port, assets :: FilePath } deriving (Generic, Show) instance Envy.DefConfig Config where defConfig = Config { port = 8005, assets = "_/bild/dev/static/devalloc.js" } 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 -- | 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.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 ] -- * paths and pages type AllPaths = Get '[HTML] (HtmlApp Page) :<|> "auth" :> "github" :> "callback" :> QueryParam "code" Text :> Get '[HTML] (HtmlApp Page) :<|> ShowAnalysis :<|> ("static" :> Raw) :<|> "css" :> "main.css" :> Get '[CSS] Text allPaths :: Proxy AllPaths allPaths = Proxy :: Proxy AllPaths type ShowAnalysis = "analysis" :> QueryParam "id" Int :> Get '[HTML] (HtmlApp Analysis) paths :: Config -> OAuthArgs -> Server AllPaths paths Config {assets} oAuthArgs = page (Home oAuthArgs) :<|> auth oAuthArgs :<|> analyze :<|> static :<|> look where page = pure . HtmlApp analyze Nothing = panic "could not analyze this repo" analyze (Just id) = pure . HtmlApp <| Analysis {targetRepo = GitHub.mkId (Proxy :: Proxy GitHub.Repo) id} static = serveDirectoryWith <| defaultWebAppSettings assets look = return . toStrict . Clay.render <| do Biz.Look.fuckingStyle "body" Clay.? Biz.Look.fontStack -- | Create an href attribute to a path in 'AllPaths'. linkTo :: (HasLink path, IsElem path AllPaths) => -- | Proxy to the path Proxy path -> -- | Return value @x@ is to be used like @Lucid.a_ [ x ] ...@ MkLink path Lucid.Attribute linkTo = Lucid.safeHref_ "/" allPaths data Page = Home OAuthArgs | GitHubRepos (Vector GitHub.Repo) instance Lucid.ToHtml Page where toHtmlRaw = Lucid.toHtml toHtml page = Lucid.toHtml <| case page of Home authArgs -> pitch authArgs GitHubRepos repos -> do Lucid.h1_ "Select a repo to analyze" selectRepo repos data OAuthResponse = OAuthResponse { access_token :: Text, scope :: Text, token_type :: Text } deriving (Generic, Aeson.FromJSON) auth :: OAuthArgs -> Maybe Text -> Handler (HtmlApp Page) auth _ Nothing = panic "no code from github api" auth OAuthArgs {..} (Just code) = liftIO <| getAccessToken >>= getRepos >>= \case Left err -> panic <| show err Right repos -> pure <| HtmlApp <| GitHubRepos repos where getRepos oAuthToken = GitHub.github (GitHub.OAuth <| Encoding.encodeUtf8 oAuthToken) (GitHub.currentUserReposR GitHub.RepoPublicityAll GitHub.FetchAll) getAccessToken = Req.runReq Req.defaultHttpConfig <| accessTokenRequest >>= Req.responseBody /> access_token /> return 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 data Analysis = Analysis { targetRepo :: GitHub.Id GitHub.Repo } instance Lucid.ToHtml Analysis where toHtmlRaw = Lucid.toHtml toHtml = Lucid.toHtml . render where render :: Analysis -> Lucid.Html () render analysis = Lucid.div_ <| do Lucid.h1_ "Analysis Results" Lucid.p_ (Lucid.toHtml <| Text.pack <| show <| targetRepo analysis) -- * parts encodeParams :: [(Text, Text)] -> Text encodeParams = Encoding.decodeUtf8 . LBS.toStrict . Web.FormUrlEncoded.urlEncodeParams selectRepo :: Vector GitHub.Repo -> Lucid.Html () selectRepo = Lucid.ul_ . mapM_ render . Vector.toList where render :: GitHub.Repo -> Lucid.Html () render repo = Lucid.li_ . Lucid.a_ [ linkTo (Proxy :: Proxy ShowAnalysis) (Just <| GitHub.untagId <| GitHub.repoId repo) ] . Lucid.toHtml . GitHub.untagName <| GitHub.repoName repo loginButton :: OAuthArgs -> Lucid.Html () loginButton OAuthArgs {..} = Lucid.a_ [ Lucid.href_ <| "https://github.com/login/oauth/authorize?" <> encodeParams [ ("client_id", githubClientId), ("state", githubState) -- ("redirect_uri", "https://devalloc.io") ] ] "Get Started with GitHub" pitch :: OAuthArgs -> Lucid.Html () pitch oAuthArgs = Lucid.div_ <| do Lucid.h1_ "Devalloc" Lucid.p_ "Devalloc analyzes your codebase trends, finds patterns \ \ in how your developers work, and protects against tech debt." Lucid.p_ "Just hook it up to your CI system - it will warn you when it finds a problem." loginButton oAuthArgs Lucid.h2_ "Identify blackholes in your codebase" Lucid.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." loginButton oAuthArgs Lucid.h2_ "Protect against lost knowledge" Lucid.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." loginButton oAuthArgs Lucid.h2_ "Don't just measure code coverage - also know your dev coverage" Lucid.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?" Lucid.p_ "(Paid only)" loginButton oAuthArgs Lucid.h2_ "See how your teams *actually* organize themselves with cluster analysis" Lucid.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." Lucid.p_ "(Paid only)" loginButton oAuthArgs