mirror of https://github.com/voidlizard/hbs2
added pandoc / sort of compiles
This commit is contained in:
parent
ddd6dc7d7f
commit
e857f73bdc
|
@ -63,14 +63,17 @@ runApp chan mode = do
|
||||||
setLogging @ERROR (toStderr . logPrefix "[error] ")
|
setLogging @ERROR (toStderr . logPrefix "[error] ")
|
||||||
setLogging @NOTICE (toStderr . logPrefix "[debug] ")
|
setLogging @NOTICE (toStderr . logPrefix "[debug] ")
|
||||||
|
|
||||||
|
|
||||||
case mode of
|
case mode of
|
||||||
RunIndex a -> runWithOracleEnv chan $ runOracleIndex a
|
RunIndex a -> runWithOracleEnv chan $ runOracleIndex a
|
||||||
RunPipe{} -> runWithOracleEnv chan $ runPipe
|
RunPipe{} -> shutUp >> (runWithOracleEnv chan $ runPipe)
|
||||||
RunDump pks -> runDump pks
|
RunDump pks -> runDump pks
|
||||||
RunUpdate -> runWithOracleEnv chan $ updateState
|
RunUpdate -> runWithOracleEnv chan $ updateState
|
||||||
|
|
||||||
`finally` do
|
`finally` do
|
||||||
|
shutUp
|
||||||
|
|
||||||
|
where
|
||||||
|
shutUp = do
|
||||||
setLoggingOff @DEBUG
|
setLoggingOff @DEBUG
|
||||||
setLoggingOff @WARN
|
setLoggingOff @WARN
|
||||||
setLoggingOff @ERROR
|
setLoggingOff @ERROR
|
||||||
|
|
|
@ -0,0 +1,32 @@
|
||||||
|
module HBS2.Git.Oracle.Html where
|
||||||
|
|
||||||
|
import HBS2.Git.Oracle.Prelude
|
||||||
|
import HBS2.Git.Oracle.State
|
||||||
|
|
||||||
|
import Data.HashMap.Strict (HashMap)
|
||||||
|
|
||||||
|
import Lucid (Html,HtmlT,toHtml,renderBS)
|
||||||
|
import Lucid.Html5 hiding (for_)
|
||||||
|
|
||||||
|
import Data.Text (Text)
|
||||||
|
import Data.Text qualified as Text
|
||||||
|
import Data.ByteString.Lazy
|
||||||
|
import Control.Monad.Identity
|
||||||
|
|
||||||
|
renderEntries :: Monad m => HashMap Text Text -> [(HashVal, Text, Text)] -> m ByteString
|
||||||
|
renderEntries _ items = pure $ renderBS do
|
||||||
|
doctypehtml_ do
|
||||||
|
head_ mempty do
|
||||||
|
meta_ [charset_ "utf-8"]
|
||||||
|
|
||||||
|
body_ mempty do
|
||||||
|
for_ items $ \(h,n,b) -> do
|
||||||
|
div_ do
|
||||||
|
|
||||||
|
when ( Text.length n > 2) do
|
||||||
|
h3_ [class_ "repo-name"] (toHtml (show $ pretty n))
|
||||||
|
span_ [class_ "repo-reference"] (toHtml (show $ pretty h))
|
||||||
|
|
||||||
|
-- td_ (toHtml (show $ pretty n))
|
||||||
|
-- td_ (toHtml (show $ pretty b))
|
||||||
|
|
|
@ -7,6 +7,7 @@ import HBS2.Git.Oracle.Prelude
|
||||||
import HBS2.Git.Oracle.App
|
import HBS2.Git.Oracle.App
|
||||||
import HBS2.Git.Oracle.Facts
|
import HBS2.Git.Oracle.Facts
|
||||||
import HBS2.Git.Oracle.State
|
import HBS2.Git.Oracle.State
|
||||||
|
import HBS2.Git.Oracle.Html
|
||||||
|
|
||||||
import HBS2.Actors.Peer
|
import HBS2.Actors.Peer
|
||||||
|
|
||||||
|
@ -35,12 +36,13 @@ import Control.Monad.Trans.Maybe
|
||||||
import Data.Coerce
|
import Data.Coerce
|
||||||
import Data.Ord
|
import Data.Ord
|
||||||
import Data.Text qualified as Text
|
import Data.Text qualified as Text
|
||||||
|
import Data.List qualified as List
|
||||||
import Data.HashMap.Strict qualified as HM
|
import Data.HashMap.Strict qualified as HM
|
||||||
import Data.ByteString.Lazy qualified as LBS
|
import Data.ByteString.Lazy qualified as LBS
|
||||||
import System.Process.Typed
|
import System.Process.Typed
|
||||||
import Text.InterpolatedString.Perl6 (qc)
|
import Text.InterpolatedString.Perl6 (qc)
|
||||||
import System.Environment (getProgName, getArgs)
|
import System.Environment (getProgName, getArgs)
|
||||||
|
import System.Environment
|
||||||
import System.Posix.Signals
|
import System.Posix.Signals
|
||||||
|
|
||||||
import System.Exit
|
import System.Exit
|
||||||
|
@ -151,6 +153,9 @@ runDump :: forall m . MonadUnliftIO m
|
||||||
runDump pks = do
|
runDump pks = do
|
||||||
self <- liftIO getProgName
|
self <- liftIO getProgName
|
||||||
|
|
||||||
|
env <- liftIO getEnvironment
|
||||||
|
<&> fmap (over _1 Text.pack . over _2 Text.pack)
|
||||||
|
|
||||||
let cmd = proc self ["pipe", "-r", show (pretty (AsBase58 pks))]
|
let cmd = proc self ["pipe", "-r", show (pretty (AsBase58 pks))]
|
||||||
& setStdin createPipe
|
& setStdin createPipe
|
||||||
& setStdout createPipe
|
& setStdout createPipe
|
||||||
|
@ -158,39 +163,27 @@ runDump pks = do
|
||||||
flip runContT pure do
|
flip runContT pure do
|
||||||
|
|
||||||
p <- ContT $ withProcessWait cmd
|
p <- ContT $ withProcessWait cmd
|
||||||
-- p <- lift $ startProcess cmd
|
|
||||||
|
|
||||||
let ssin = getStdin p
|
let ssin = getStdin p
|
||||||
let sout = getStdout p
|
let sout = getStdout p
|
||||||
client <- newMessagingPipe (sout,ssin) -- ,sout)
|
client <- newMessagingPipe (sout,ssin) -- ,sout)
|
||||||
|
|
||||||
mess <- ContT $ bracket (async $ runMessagingPipe client) cancel
|
void $ ContT $ withAsync $ runMessagingPipe client
|
||||||
|
|
||||||
caller <- makeServiceCaller @BrowserPluginAPI @PIPE (localPeer client)
|
caller <- makeServiceCaller @BrowserPluginAPI @PIPE (localPeer client)
|
||||||
|
|
||||||
broker <- ContT $ bracket (async $ liftIO $ runReaderT (runServiceClient caller) client) cancel
|
void $ ContT $ withAsync $ liftIO $ runReaderT (runServiceClient caller) client
|
||||||
|
|
||||||
wtf <- callService @RpcChannelQuery caller ()
|
wtf <- callService @RpcChannelQuery caller env
|
||||||
>>= orThrowUser "can't query rpc"
|
>>= orThrowUser "can't query rpc"
|
||||||
|
|
||||||
r <- ContT $ maybe1 wtf (pure ())
|
r <- ContT $ maybe1 wtf (pure ())
|
||||||
|
|
||||||
let val = Aeson.decode @Value r
|
|
||||||
|
|
||||||
liftIO $ LBS.putStr (A.encodePretty val)
|
|
||||||
|
|
||||||
hClose ssin
|
hClose ssin
|
||||||
hClose sout
|
|
||||||
|
|
||||||
waitExitCode p
|
liftIO $ LBS.putStr r >> hFlush stdout
|
||||||
|
|
||||||
debug "CLIENT: WTF?"
|
void $ waitExitCode p
|
||||||
|
|
||||||
-- stopProcess p
|
|
||||||
-- error "MOTHERFUCKER!"
|
|
||||||
-- void $ callService @RpcChannelQuery caller ()
|
|
||||||
-- >>= orThrowUser "can't query rpc"
|
|
||||||
-- liftIO $ exitSuccess
|
|
||||||
|
|
||||||
data RpcChannelQuery
|
data RpcChannelQuery
|
||||||
|
|
||||||
|
@ -198,7 +191,7 @@ data RpcChannelQuery
|
||||||
type BrowserPluginAPI = '[ RpcChannelQuery ]
|
type BrowserPluginAPI = '[ RpcChannelQuery ]
|
||||||
|
|
||||||
-- API endpoint definition
|
-- API endpoint definition
|
||||||
type instance Input RpcChannelQuery = ()
|
type instance Input RpcChannelQuery = [(Text,Text)]
|
||||||
type instance Output RpcChannelQuery = Maybe ByteString
|
type instance Output RpcChannelQuery = Maybe ByteString
|
||||||
|
|
||||||
class HasOracleEnv m where
|
class HasOracleEnv m where
|
||||||
|
@ -206,13 +199,23 @@ class HasOracleEnv m where
|
||||||
|
|
||||||
-- API handler
|
-- API handler
|
||||||
instance (MonadUnliftIO m, HasOracleEnv m) => HandleMethod m RpcChannelQuery where
|
instance (MonadUnliftIO m, HasOracleEnv m) => HandleMethod m RpcChannelQuery where
|
||||||
handleMethod _ = do
|
handleMethod args' = do
|
||||||
env <- getOracleEnv
|
env <- getOracleEnv
|
||||||
-- let chan = _refchanId env
|
|
||||||
-- let rchanAPI = _refchanAPI env
|
|
||||||
-- let sto = _storage env
|
|
||||||
|
|
||||||
|
let args = HM.fromList args'
|
||||||
|
|
||||||
|
case HM.lookup "METHOD" args of
|
||||||
|
Just "debug" -> listEnv args
|
||||||
|
Just "list-entries" -> listEntries args
|
||||||
|
Nothing -> listEntries args
|
||||||
|
_ -> pure mempty
|
||||||
|
|
||||||
|
where
|
||||||
|
listEnv args = do
|
||||||
|
pure $ Just $ A.encodePretty args
|
||||||
|
|
||||||
|
listEntries args = do
|
||||||
|
env <- getOracleEnv
|
||||||
withOracleEnv env do
|
withOracleEnv env do
|
||||||
items <- withState $ select_ @_ @(HashVal, Text, Text) [qc|
|
items <- withState $ select_ @_ @(HashVal, Text, Text) [qc|
|
||||||
|
|
||||||
|
@ -232,12 +235,21 @@ instance (MonadUnliftIO m, HasOracleEnv m) => HandleMethod m RpcChannelQuery whe
|
||||||
|
|
||||||
|]
|
|]
|
||||||
|
|
||||||
|
case HM.lookup "OUTPUT" args of
|
||||||
|
Just "html" -> formatHtml args items
|
||||||
|
Just "json" -> formatJson items
|
||||||
|
_ -> formatJson items
|
||||||
|
|
||||||
|
formatJson items = do
|
||||||
let root = object [ "rows" .= items
|
let root = object [ "rows" .= items
|
||||||
, "desc" .= [ "entity", "name", "brief" ]
|
, "desc" .= [ "entity", "name", "brief" ]
|
||||||
]
|
]
|
||||||
|
|
||||||
pure $ Just $ A.encodePretty root
|
pure $ Just $ A.encodePretty root
|
||||||
|
|
||||||
|
formatHtml args items = do
|
||||||
|
renderEntries args items <&> Just
|
||||||
|
|
||||||
-- Codec for protocol
|
-- Codec for protocol
|
||||||
instance HasProtocol PIPE (ServiceProto BrowserPluginAPI PIPE) where
|
instance HasProtocol PIPE (ServiceProto BrowserPluginAPI PIPE) where
|
||||||
type instance ProtocolId (ServiceProto BrowserPluginAPI PIPE) = 0xDEADF00D123
|
type instance ProtocolId (ServiceProto BrowserPluginAPI PIPE) = 0xDEADF00D123
|
||||||
|
@ -270,7 +282,9 @@ runPipe = do
|
||||||
|
|
||||||
void $ ContT $ bracket (async $ runMessagingPipe server) cancel
|
void $ ContT $ bracket (async $ runMessagingPipe server) cancel
|
||||||
|
|
||||||
void $ ContT $ withAsync $ forever do
|
void $ ContT $ withAsync $ do
|
||||||
|
pause @'Seconds 10
|
||||||
|
forever do
|
||||||
debug $ yellow "updateState"
|
debug $ yellow "updateState"
|
||||||
updateState
|
updateState
|
||||||
pause @'Seconds 60
|
pause @'Seconds 60
|
||||||
|
@ -282,12 +296,10 @@ runPipe = do
|
||||||
]
|
]
|
||||||
|
|
||||||
fix \next -> do
|
fix \next -> do
|
||||||
-- debug $ red "YAYAYAYA"
|
|
||||||
done1 <- hIsClosed stdin
|
done1 <- hIsClosed stdin
|
||||||
done2 <- hIsClosed stdout
|
done2 <- hIsClosed stdout
|
||||||
done3 <- hIsEOF stdin
|
done3 <- hIsEOF stdin
|
||||||
let done = done1 || done2 || done3
|
let done = done1 || done2 || done3
|
||||||
debug $ red "DONE:" <+> pretty done
|
|
||||||
unless done (pause @'Seconds 0.01 >> next)
|
unless done (pause @'Seconds 0.01 >> next)
|
||||||
|
|
||||||
updateState :: MonadUnliftIO m => Oracle m ()
|
updateState :: MonadUnliftIO m => Oracle m ()
|
||||||
|
|
|
@ -59,6 +59,7 @@ newtype GitRepoKey = GitRepoKey (LWWRefKey HBS2Basic)
|
||||||
|
|
||||||
newtype HashVal = HashVal HashRef
|
newtype HashVal = HashVal HashRef
|
||||||
deriving stock Generic
|
deriving stock Generic
|
||||||
|
deriving newtype (Pretty,Show)
|
||||||
|
|
||||||
instance ToJSON HashVal where
|
instance ToJSON HashVal where
|
||||||
toJSON (HashVal x) = toJSON (show $ pretty x)
|
toJSON (HashVal x) = toJSON (show $ pretty x)
|
||||||
|
|
|
@ -178,12 +178,16 @@ library hbs2-git-oracle-oracle-lib
|
||||||
HBS2.Git.Oracle.Run
|
HBS2.Git.Oracle.Run
|
||||||
HBS2.Git.Oracle.State
|
HBS2.Git.Oracle.State
|
||||||
HBS2.Git.Oracle.Facts
|
HBS2.Git.Oracle.Facts
|
||||||
|
HBS2.Git.Oracle.Html
|
||||||
|
|
||||||
DBPipe.SQLite.Types
|
DBPipe.SQLite.Types
|
||||||
DBPipe.SQLite.Generic
|
DBPipe.SQLite.Generic
|
||||||
|
|
||||||
build-depends: base, hbs2-git
|
build-depends: base, hbs2-git
|
||||||
, base16-bytestring
|
, base16-bytestring
|
||||||
, binary
|
, binary
|
||||||
|
, lucid
|
||||||
|
, pandoc == 3.1.12.3
|
||||||
, unix
|
, unix
|
||||||
-- FIXME: ASAP-remove
|
-- FIXME: ASAP-remove
|
||||||
, sqlite-simple
|
, sqlite-simple
|
||||||
|
|
Loading…
Reference in New Issue