Skip to content

Commit

Permalink
Make nix runable (#12)
Browse files Browse the repository at this point in the history
  • Loading branch information
srid authored Feb 3, 2025
1 parent 2574ec4 commit 24d10bd
Show file tree
Hide file tree
Showing 5 changed files with 33 additions and 6 deletions.
8 changes: 8 additions & 0 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -34,3 +34,11 @@ just run
# Or, if you need to start from empty database (useful if you have changed the acid-state types)
just resetdb run
```

## Beta Testing

```
nix run github:juspay/vira -- --host <interface-ip> --port 5005
```

This uses samples repos, but you can pass your own in the command line.
1 change: 1 addition & 0 deletions nix/modules/flake-parts/haskell.nix
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,7 @@
(root + /LICENSE)
(root + /README.md)
(root + /.stan.toml)
(root + /static)
];
});

Expand Down
13 changes: 12 additions & 1 deletion src/Vira/App/CLI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
module Vira.App.CLI where

import Data.Set qualified as Set
import Network.Wai.Handler.Warp (Port)
import OptEnvConf
import Prelude hiding (Reader, reader)

Expand All @@ -13,8 +14,10 @@ TODO: Use Severity from co-log
data Settings = Settings
{ logLevel :: String
-- ^ Minimum logging level
, port :: Int
, port :: Port
-- ^ The port to bind the HTTP server to
, host :: Text
-- ^ The host to bind the HTTP server to
, dbPath :: FilePath
-- ^ Path to the vira db
, repo :: RepoSettings
Expand Down Expand Up @@ -58,6 +61,14 @@ instance HasParser Settings where
, name "port"
, value 5005
]
host <-
setting
[ reader str
, metavar "HOST"
, help "Host"
, name "host"
, value "127.0.0.1"
]
dbPath <-
setting
[ reader str
Expand Down
14 changes: 9 additions & 5 deletions src/Vira/Toplevel.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ import Network.Wai.Middleware.Static (
(>->),
)
import OptEnvConf qualified
import Paths_vira (version)
import Paths_vira qualified
import Servant.API (Get, NamedRoutes, (:>))
import Servant.API.ContentTypes.Lucid (HTML)
import Servant.API.Generic (GenericMode (type (:-)))
Expand Down Expand Up @@ -78,7 +78,7 @@ runVira = do
Utf8.withUtf8 $ do
hSetBuffering stdout LineBuffering
hSetBuffering stderr LineBuffering
settings :: Settings <- OptEnvConf.runSettingsParser version "Nix CI & Cache for teams"
settings :: Settings <- OptEnvConf.runSettingsParser Paths_vira.version "Nix CI & Cache for teams"
appIO settings
where
-- Like `app` but in `IO`
Expand All @@ -93,12 +93,16 @@ runVira = do
-- Vira application for given `Settings`
app :: (HasCallStack) => Settings -> Eff AppStack ()
app settings = do
log Info $ "Launching vira at http://localhost:" <> show settings.port
log Info $ "Launching vira at http://" <> settings.host <> ":" <> show settings.port
log Debug $ "Settings: " <> show settings
let staticMiddleware = staticPolicy $ noDots >-> addBase "static"
staticDir <- liftIO Paths_vira.getDataDir
log Debug $ "Serving static files from: " <> show staticDir
let staticMiddleware = staticPolicy $ noDots >-> addBase staticDir
cfg <- ask
let servantApp = genericServe $ handlers cfg
liftIO $ Warp.run settings.port $ staticMiddleware servantApp
let host = fromString $ toString settings.host
let warpSettings = Warp.defaultSettings & Warp.setHost host & Warp.setPort settings.port
liftIO $ Warp.runSettings warpSettings $ staticMiddleware servantApp

-- | Convert a git repository URL to a `State.Repo` record.
repoFromUrl :: Text -> State.Repo
Expand Down
3 changes: 3 additions & 0 deletions vira.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,9 @@ extra-source-files:
LICENSE
README.md

data-dir: static
data-files: tailwind.css

flag ghcid
default: False
manual: True
Expand Down

0 comments on commit 24d10bd

Please sign in to comment.