mirror of https://github.com/voidlizard/hbs2
wip, init lwwref
This commit is contained in:
parent
187e9d2ba7
commit
2298295972
|
@ -24,6 +24,7 @@ import HBS2.Peer.RPC.Client.Unix
|
||||||
import HBS2.Net.Auth.Schema()
|
import HBS2.Net.Auth.Schema()
|
||||||
|
|
||||||
import System.Environment
|
import System.Environment
|
||||||
|
import System.IO qualified as IO
|
||||||
|
|
||||||
type RefLogId = PubKey 'Sign 'HBS2Basic
|
type RefLogId = PubKey 'Sign 'HBS2Basic
|
||||||
|
|
||||||
|
@ -35,7 +36,7 @@ setupLogger = do
|
||||||
-- setLogging @DEBUG $ toStderr . logPrefix "[debug] "
|
-- setLogging @DEBUG $ toStderr . logPrefix "[debug] "
|
||||||
setLogging @ERROR $ toStderr . logPrefix "[error] "
|
setLogging @ERROR $ toStderr . logPrefix "[error] "
|
||||||
setLogging @WARN $ toStderr . logPrefix "[warn] "
|
setLogging @WARN $ toStderr . logPrefix "[warn] "
|
||||||
setLogging @NOTICE $ toStdout . logPrefix ""
|
setLogging @NOTICE $ toStderr . logPrefix ""
|
||||||
pure ()
|
pure ()
|
||||||
|
|
||||||
flushLoggers :: MonadIO m => m ()
|
flushLoggers :: MonadIO m => m ()
|
||||||
|
@ -86,6 +87,7 @@ main = do
|
||||||
|
|
||||||
runHBS2Cli do
|
runHBS2Cli do
|
||||||
|
|
||||||
|
|
||||||
case cli of
|
case cli of
|
||||||
[ListVal [SymbolVal "stdin"]] -> do
|
[ListVal [SymbolVal "stdin"]] -> do
|
||||||
what <- liftIO getContents
|
what <- liftIO getContents
|
||||||
|
@ -94,7 +96,14 @@ main = do
|
||||||
recover $ run dict what >>= eatNil display
|
recover $ run dict what >>= eatNil display
|
||||||
|
|
||||||
[] -> do
|
[] -> do
|
||||||
void $ run dict [mkForm "help" []]
|
eof <- liftIO IO.isEOF
|
||||||
|
if eof then
|
||||||
|
void $ run dict [mkForm "help" []]
|
||||||
|
else do
|
||||||
|
what <- liftIO getContents
|
||||||
|
>>= either (error.show) pure . parseTop
|
||||||
|
|
||||||
|
recover $ run dict what >>= eatNil display
|
||||||
|
|
||||||
_ -> do
|
_ -> do
|
||||||
recover $ run dict cli >>= eatNil display
|
recover $ run dict cli >>= eatNil display
|
||||||
|
|
|
@ -33,7 +33,7 @@ keymanGetConfig = do
|
||||||
|
|
||||||
keymanUpdate :: MonadUnliftIO m => m ()
|
keymanUpdate :: MonadUnliftIO m => m ()
|
||||||
keymanUpdate = do
|
keymanUpdate = do
|
||||||
void $ runProcess (shell [qc|hbs2-keyman update|])
|
void $ runProcess (shell [qc|hbs2-keyman update|] & setStderr closed & setStdout closed)
|
||||||
|
|
||||||
keymanNewCredentials :: MonadUnliftIO m => Maybe String -> Int -> m (PubKey 'Sign 'HBS2Basic)
|
keymanNewCredentials :: MonadUnliftIO m => Maybe String -> Int -> m (PubKey 'Sign 'HBS2Basic)
|
||||||
keymanNewCredentials suff n = do
|
keymanNewCredentials suff n = do
|
||||||
|
@ -52,3 +52,4 @@ keymanNewCredentials suff n = do
|
||||||
keymanUpdate
|
keymanUpdate
|
||||||
|
|
||||||
pure psk
|
pure psk
|
||||||
|
|
||||||
|
|
|
@ -50,3 +50,4 @@ keymanEntries = do
|
||||||
pure $ mkStr fpath
|
pure $ mkStr fpath
|
||||||
|
|
||||||
_ -> throwIO (BadFormException @C nil)
|
_ -> throwIO (BadFormException @C nil)
|
||||||
|
|
||||||
|
|
|
@ -37,10 +37,10 @@ lwwRefEntries = do
|
||||||
$ returns "string" "lwwref public key"
|
$ returns "string" "lwwref public key"
|
||||||
$ entry $ bindMatch "hbs2:lwwref:create" $ \case
|
$ entry $ bindMatch "hbs2:lwwref:create" $ \case
|
||||||
[] -> do
|
[] -> do
|
||||||
reflog <- keymanNewCredentials (Just "lwwref") 0
|
key <- keymanNewCredentials (Just "lwwref") 0
|
||||||
api <- getClientAPI @PeerAPI @UNIX
|
api <- getClientAPI @PeerAPI @UNIX
|
||||||
void $ callService @RpcPollAdd api (reflog, "lwwref", 31)
|
void $ callService @RpcPollAdd api (key, "lwwref", 31)
|
||||||
pure $ mkStr (show $ pretty (AsBase58 reflog))
|
pure $ mkForm "pk" [mkStr (show $ pretty (AsBase58 key))]
|
||||||
|
|
||||||
_ -> throwIO (BadFormException @C nil)
|
_ -> throwIO (BadFormException @C nil)
|
||||||
|
|
||||||
|
|
|
@ -125,12 +125,14 @@ library
|
||||||
HBS2.Git3.Prelude
|
HBS2.Git3.Prelude
|
||||||
HBS2.Git3.Export
|
HBS2.Git3.Export
|
||||||
HBS2.Git3.Import
|
HBS2.Git3.Import
|
||||||
|
HBS2.Git3.Repo
|
||||||
HBS2.Git3.Run
|
HBS2.Git3.Run
|
||||||
HBS2.Git3.State.Types
|
HBS2.Git3.State.Types
|
||||||
HBS2.Git3.State.RefLog
|
HBS2.Git3.State.RefLog
|
||||||
HBS2.Git3.State.Index
|
HBS2.Git3.State.Index
|
||||||
HBS2.Git3.State.Segment
|
HBS2.Git3.State.Segment
|
||||||
HBS2.Git3.Config.Local
|
HBS2.Git3.Config.Local
|
||||||
|
HBS2.Git3.State.LWWBlock
|
||||||
HBS2.Git3.Git
|
HBS2.Git3.Git
|
||||||
HBS2.Git3.Git.Pack
|
HBS2.Git3.Git.Pack
|
||||||
|
|
||||||
|
|
|
@ -12,6 +12,8 @@ import Data.Config.Suckless.Script
|
||||||
|
|
||||||
import Data.Text.IO qualified as IO
|
import Data.Text.IO qualified as IO
|
||||||
|
|
||||||
|
{- HLINT ignore "Functor law"-}
|
||||||
|
|
||||||
getConfigPath :: MonadIO m => m FilePath
|
getConfigPath :: MonadIO m => m FilePath
|
||||||
getConfigPath = do
|
getConfigPath = do
|
||||||
|
|
||||||
|
@ -21,6 +23,17 @@ getConfigPath = do
|
||||||
>>= orThrowUser ".git not found"
|
>>= orThrowUser ".git not found"
|
||||||
<&> (</> name) . takeDirectory
|
<&> (</> name) . takeDirectory
|
||||||
|
|
||||||
|
|
||||||
|
getConfigRootFile :: MonadIO m => m FilePath
|
||||||
|
getConfigRootFile = do
|
||||||
|
|
||||||
|
let name = ".hbs2-git3"
|
||||||
|
|
||||||
|
findGitDir
|
||||||
|
>>= orThrowUser ".git not found"
|
||||||
|
<&> (</> name) . takeDirectory
|
||||||
|
<&> (</> "config")
|
||||||
|
|
||||||
readLocalConf :: MonadIO m => m [Syntax C]
|
readLocalConf :: MonadIO m => m [Syntax C]
|
||||||
readLocalConf = do
|
readLocalConf = do
|
||||||
|
|
||||||
|
|
|
@ -15,12 +15,14 @@ module HBS2.Git3.Prelude
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import HBS2.Prelude.Plated as Exported
|
import HBS2.Prelude.Plated as Exported
|
||||||
|
import HBS2.Defaults as Exported
|
||||||
import HBS2.OrDie as Exported
|
import HBS2.OrDie as Exported
|
||||||
import HBS2.Data.Types.Refs as Exported
|
import HBS2.Data.Types.Refs as Exported
|
||||||
import HBS2.Base58 as Exported
|
import HBS2.Base58 as Exported
|
||||||
import HBS2.Merkle as Exported
|
import HBS2.Merkle as Exported
|
||||||
import HBS2.Misc.PrettyStuff as Exported
|
import HBS2.Misc.PrettyStuff as Exported
|
||||||
import HBS2.Net.Auth.Credentials
|
import HBS2.Net.Auth.Credentials
|
||||||
|
import HBS2.Peer.Proto.LWWRef as Exported
|
||||||
import HBS2.Peer.Proto.RefLog as Exported
|
import HBS2.Peer.Proto.RefLog as Exported
|
||||||
import HBS2.Peer.RPC.API.RefLog as Exported
|
import HBS2.Peer.RPC.API.RefLog as Exported
|
||||||
import HBS2.Peer.RPC.API.Peer as Exported
|
import HBS2.Peer.RPC.API.Peer as Exported
|
||||||
|
@ -30,6 +32,7 @@ import HBS2.Peer.RPC.Client hiding (encode,decode)
|
||||||
import HBS2.Peer.RPC.Client.Unix hiding (encode,decode)
|
import HBS2.Peer.RPC.Client.Unix hiding (encode,decode)
|
||||||
import HBS2.Peer.RPC.Client.StorageClient
|
import HBS2.Peer.RPC.Client.StorageClient
|
||||||
import HBS2.Peer.CLI.Detect
|
import HBS2.Peer.CLI.Detect
|
||||||
|
import HBS2.Data.Types.SignedBox as Exported
|
||||||
import HBS2.Storage as Exported
|
import HBS2.Storage as Exported
|
||||||
import HBS2.Storage.Operations.Class as Exported
|
import HBS2.Storage.Operations.Class as Exported
|
||||||
import HBS2.System.Logger.Simple.ANSI as Exported
|
import HBS2.System.Logger.Simple.ANSI as Exported
|
||||||
|
@ -117,7 +120,9 @@ data Git3Env =
|
||||||
, peerStorage :: AnyStorage
|
, peerStorage :: AnyStorage
|
||||||
, peerAPI :: ServiceCaller PeerAPI UNIX
|
, peerAPI :: ServiceCaller PeerAPI UNIX
|
||||||
, reflogAPI :: ServiceCaller RefLogAPI UNIX
|
, reflogAPI :: ServiceCaller RefLogAPI UNIX
|
||||||
|
, lwwAPI :: ServiceCaller LWWRefAPI UNIX
|
||||||
, gitRefLog :: TVar (Maybe GitRemoteKey)
|
, gitRefLog :: TVar (Maybe GitRemoteKey)
|
||||||
|
, gitRepoKey :: TVar (Maybe GitRepoKey)
|
||||||
, gitPackedSegmentSize :: TVar Int
|
, gitPackedSegmentSize :: TVar Int
|
||||||
, gitCompressionLevel :: TVar Int
|
, gitCompressionLevel :: TVar Int
|
||||||
, gitIndexBlockSize :: TVar Natural
|
, gitIndexBlockSize :: TVar Natural
|
||||||
|
@ -132,6 +137,8 @@ class HasExportOpts m where
|
||||||
class HasGitRemoteKey m where
|
class HasGitRemoteKey m where
|
||||||
getGitRemoteKey :: m (Maybe GitRemoteKey)
|
getGitRemoteKey :: m (Maybe GitRemoteKey)
|
||||||
setGitRemoteKey :: GitRemoteKey -> m ()
|
setGitRemoteKey :: GitRemoteKey -> m ()
|
||||||
|
getGitRepoKey :: m (Maybe GitRepoKey)
|
||||||
|
setGitRepoKey :: GitRepoKey -> m ()
|
||||||
|
|
||||||
instance (MonadIO m, MonadReader Git3Env m) => HasGitRemoteKey m where
|
instance (MonadIO m, MonadReader Git3Env m) => HasGitRemoteKey m where
|
||||||
getGitRemoteKey = do
|
getGitRemoteKey = do
|
||||||
|
@ -142,6 +149,14 @@ instance (MonadIO m, MonadReader Git3Env m) => HasGitRemoteKey m where
|
||||||
e <- ask
|
e <- ask
|
||||||
liftIO $ atomically $ writeTVar (gitRefLog e) (Just k)
|
liftIO $ atomically $ writeTVar (gitRefLog e) (Just k)
|
||||||
|
|
||||||
|
getGitRepoKey = do
|
||||||
|
e <- ask
|
||||||
|
liftIO $ readTVarIO (gitRepoKey e)
|
||||||
|
|
||||||
|
setGitRepoKey k = do
|
||||||
|
e <- ask
|
||||||
|
liftIO $ atomically $ writeTVar (gitRepoKey e) (Just k)
|
||||||
|
|
||||||
instance (MonadIO m, MonadReader Git3Env m) => HasExportOpts m where
|
instance (MonadIO m, MonadReader Git3Env m) => HasExportOpts m where
|
||||||
getPackedSegmetSize = asks gitPackedSegmentSize >>= readTVarIO
|
getPackedSegmetSize = asks gitPackedSegmentSize >>= readTVarIO
|
||||||
setPackedSegmedSize x = do
|
setPackedSegmedSize x = do
|
||||||
|
@ -198,6 +213,13 @@ instance (MonadUnliftIO m) => HasClientAPI RefLogAPI UNIX (Git3 m) where
|
||||||
Git3Disconnected{} -> throwIO Git3PeerNotConnected
|
Git3Disconnected{} -> throwIO Git3PeerNotConnected
|
||||||
Git3Connected{..} -> pure reflogAPI
|
Git3Connected{..} -> pure reflogAPI
|
||||||
|
|
||||||
|
|
||||||
|
instance (MonadUnliftIO m) => HasClientAPI LWWRefAPI UNIX (Git3 m) where
|
||||||
|
getClientAPI = do
|
||||||
|
ask >>= \case
|
||||||
|
Git3Disconnected{} -> throwIO Git3PeerNotConnected
|
||||||
|
Git3Connected{..} -> pure lwwAPI
|
||||||
|
|
||||||
nullGit3Env :: MonadIO m => m Git3Env
|
nullGit3Env :: MonadIO m => m Git3Env
|
||||||
nullGit3Env = Git3Disconnected
|
nullGit3Env = Git3Disconnected
|
||||||
<$> newTVarIO Nothing
|
<$> newTVarIO Nothing
|
||||||
|
@ -266,8 +288,9 @@ recover m = fix \again -> do
|
||||||
|
|
||||||
let sto = AnyStorage (StorageClient storageAPI)
|
let sto = AnyStorage (StorageClient storageAPI)
|
||||||
|
|
||||||
connected <- Git3Connected soname sto peerAPI refLogAPI
|
connected <- Git3Connected soname sto peerAPI refLogAPI lwwAPI
|
||||||
<$> newTVarIO (Just ref)
|
<$> newTVarIO (Just ref)
|
||||||
|
<*> newTVarIO Nothing
|
||||||
<*> newTVarIO defSegmentSize
|
<*> newTVarIO defSegmentSize
|
||||||
<*> newTVarIO defCompressionLevel
|
<*> newTVarIO defCompressionLevel
|
||||||
<*> newTVarIO defIndexBlockSize
|
<*> newTVarIO defIndexBlockSize
|
||||||
|
|
|
@ -24,9 +24,10 @@ import HBS2.Git3.Git
|
||||||
import HBS2.Git3.Export
|
import HBS2.Git3.Export
|
||||||
import HBS2.Git3.Import
|
import HBS2.Git3.Import
|
||||||
import HBS2.Git3.State.RefLog
|
import HBS2.Git3.State.RefLog
|
||||||
|
import HBS2.Git3.Repo qualified as Repo
|
||||||
|
|
||||||
import Data.Config.Suckless.Script
|
import Data.Config.Suckless.Script
|
||||||
import Data.Config.Suckless.Script.File
|
import Data.Config.Suckless.Almost.RPC
|
||||||
|
|
||||||
import Codec.Compression.Zstd.Streaming qualified as ZstdS
|
import Codec.Compression.Zstd.Streaming qualified as ZstdS
|
||||||
import Codec.Compression.Zstd.Streaming (Result(..))
|
import Codec.Compression.Zstd.Streaming (Result(..))
|
||||||
|
@ -48,6 +49,9 @@ import Data.ByteString.Char8 qualified as BS8
|
||||||
import Data.ByteString.Lazy ( ByteString )
|
import Data.ByteString.Lazy ( ByteString )
|
||||||
import Data.ByteString.Builder as Builder
|
import Data.ByteString.Builder as Builder
|
||||||
import Network.ByteOrder qualified as N
|
import Network.ByteOrder qualified as N
|
||||||
|
import Data.Text qualified as T
|
||||||
|
import Data.Text.Encoding qualified as TE
|
||||||
|
import Data.Text.Encoding.Error qualified as TE
|
||||||
import Text.InterpolatedString.Perl6 (qc)
|
import Text.InterpolatedString.Perl6 (qc)
|
||||||
import Data.Set qualified as Set
|
import Data.Set qualified as Set
|
||||||
import Data.HashSet qualified as HS
|
import Data.HashSet qualified as HS
|
||||||
|
@ -573,5 +577,35 @@ theDict = do
|
||||||
entry $ bindMatch "reflog:import" $ nil_ $ \syn -> lift $ connectedDo do
|
entry $ bindMatch "reflog:import" $ nil_ $ \syn -> lift $ connectedDo do
|
||||||
importGitRefLog
|
importGitRefLog
|
||||||
|
|
||||||
|
|
||||||
|
entry $ bindMatch "repo:key" $ nil_ $ \case
|
||||||
|
[ SignPubKeyLike k ] -> lift $ connectedDo do
|
||||||
|
setGitRepoKey k
|
||||||
|
|
||||||
|
_ -> throwIO (BadFormException @C nil)
|
||||||
|
|
||||||
|
entry $ bindMatch "repo:init" $ nil_ $ \syn -> lift $ connectedDo do
|
||||||
|
Repo.initRepo syn
|
||||||
|
-- conf <- getConfigRootFile
|
||||||
|
-- mbKey <- getGitRepoKey
|
||||||
|
|
||||||
|
-- case mbKey of
|
||||||
|
-- Nothing -> do
|
||||||
|
|
||||||
|
-- notice "TODO: 1. create new key"
|
||||||
|
-- notice "TODO: 4. subscribe lwwref"
|
||||||
|
|
||||||
|
-- answ <- callProc "hbs2-cli" [] [mkSym "hbs2:lwwref:create"]
|
||||||
|
|
||||||
|
-- pk <- [ puk | ListVal [SymbolVal "pk", SignPubKeyLike puk] <- answ ]
|
||||||
|
-- & lastMay
|
||||||
|
-- & orThrowUser "failed to create new lww ref"
|
||||||
|
|
||||||
|
-- liftIO $ print $ pretty (AsBase58 pk)
|
||||||
|
|
||||||
|
-- notice "TODO: 2. derive reflog key"
|
||||||
|
-- notice "TODO: 3. init lwwblock"
|
||||||
|
-- notice "TODO: 5. subscribe reflog"
|
||||||
|
|
||||||
exportEntries "reflog:"
|
exportEntries "reflog:"
|
||||||
|
|
||||||
|
|
|
@ -0,0 +1,7 @@
|
||||||
|
module HBS2.Git3.State.LWWBlock where
|
||||||
|
|
||||||
|
import HBS2.Git3.Prelude
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
|
@ -13,6 +13,8 @@ import Control.Concurrent.STM qualified as STM
|
||||||
|
|
||||||
type GitRemoteKey = PubKey 'Sign 'HBS2Basic
|
type GitRemoteKey = PubKey 'Sign 'HBS2Basic
|
||||||
|
|
||||||
|
type GitRepoKey = PubKey 'Sign HBS2Basic
|
||||||
|
|
||||||
newtype Short x = Short x
|
newtype Short x = Short x
|
||||||
|
|
||||||
instance Pretty (Short GitObjectType) where
|
instance Pretty (Short GitObjectType) where
|
||||||
|
|
|
@ -23,8 +23,8 @@ import HBS2.Peer.RPC.API.RefChan
|
||||||
import HBS2.Peer.RPC.API.Storage
|
import HBS2.Peer.RPC.API.Storage
|
||||||
import HBS2.Peer.RPC.Client.StorageClient
|
import HBS2.Peer.RPC.Client.StorageClient
|
||||||
|
|
||||||
import Data.Config.Suckless.KeyValue
|
|
||||||
import Data.Config.Suckless
|
import Data.Config.Suckless
|
||||||
|
import Data.Config.Suckless.Script
|
||||||
|
|
||||||
import Data.List qualified as List
|
import Data.List qualified as List
|
||||||
import Options.Applicative qualified as O
|
import Options.Applicative qualified as O
|
||||||
|
@ -261,3 +261,4 @@ main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
(_, action) <- execParser opts
|
(_, action) <- execParser opts
|
||||||
runApp action
|
runApp action
|
||||||
|
|
||||||
|
|
|
@ -19,6 +19,7 @@ import Data.Text.Fuzzy.Tokenize
|
||||||
import Control.Monad.Reader
|
import Control.Monad.Reader
|
||||||
import Data.Typeable
|
import Data.Typeable
|
||||||
import Control.Monad.Except
|
import Control.Monad.Except
|
||||||
|
import Control.Exception
|
||||||
import Control.Monad.RWS
|
import Control.Monad.RWS
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Data.Char (isSpace,digitToInt)
|
import Data.Char (isSpace,digitToInt)
|
||||||
|
@ -69,6 +70,7 @@ data SExpParseError =
|
||||||
| SyntaxError C0
|
| SyntaxError C0
|
||||||
deriving stock (Show,Typeable)
|
deriving stock (Show,Typeable)
|
||||||
|
|
||||||
|
instance Exception SExpParseError
|
||||||
|
|
||||||
data NumType =
|
data NumType =
|
||||||
NumInteger Integer
|
NumInteger Integer
|
||||||
|
|
|
@ -0,0 +1,47 @@
|
||||||
|
{-# Language TypeOperators #-}
|
||||||
|
module Data.Config.Suckless.Almost.RPC where
|
||||||
|
|
||||||
|
import Data.Config.Suckless
|
||||||
|
|
||||||
|
import Control.Exception
|
||||||
|
import Control.Monad
|
||||||
|
import Control.Monad.IO.Class
|
||||||
|
import Data.ByteString.Lazy as LBS
|
||||||
|
import Data.ByteString.Lazy.Char8 as LBS8
|
||||||
|
import Data.Function
|
||||||
|
import Data.Text.Encoding.Error qualified as TE
|
||||||
|
import Data.Text.Encoding qualified as TE
|
||||||
|
import Data.Text qualified as T
|
||||||
|
import Data.Typeable
|
||||||
|
import Prettyprinter
|
||||||
|
import System.Process.Typed
|
||||||
|
|
||||||
|
data CallProcException =
|
||||||
|
CallProcException ExitCode
|
||||||
|
deriving (Show,Typeable)
|
||||||
|
|
||||||
|
instance Exception CallProcException
|
||||||
|
|
||||||
|
-- FIXME: to-suckless-script
|
||||||
|
callProc :: forall m . (MonadIO m)
|
||||||
|
=> FilePath
|
||||||
|
-> [String]
|
||||||
|
-> [Syntax C]
|
||||||
|
-> m [Syntax C]
|
||||||
|
|
||||||
|
callProc name params syn = do
|
||||||
|
let input = fmap (LBS.fromStrict . TE.encodeUtf8 . T.pack . show . pretty) syn
|
||||||
|
& LBS8.unlines
|
||||||
|
& byteStringInput
|
||||||
|
|
||||||
|
let what = proc name params & setStderr closed & setStdin input
|
||||||
|
(code, i, _) <- readProcess what
|
||||||
|
|
||||||
|
unless (code == ExitSuccess) do
|
||||||
|
liftIO $ throwIO (CallProcException code)
|
||||||
|
|
||||||
|
let s = TE.decodeUtf8With TE.lenientDecode (LBS.toStrict i)
|
||||||
|
|
||||||
|
parseTop s & either (liftIO . throwIO) pure
|
||||||
|
|
||||||
|
|
|
@ -82,12 +82,11 @@ pattern LitBoolVal v <- Literal _ (LitBool v)
|
||||||
pattern ListVal :: [Syntax c] -> Syntax c
|
pattern ListVal :: [Syntax c] -> Syntax c
|
||||||
pattern ListVal v <- List _ v
|
pattern ListVal v <- List _ v
|
||||||
|
|
||||||
|
|
||||||
stringLike :: Syntax c -> Maybe String
|
stringLike :: Syntax c -> Maybe String
|
||||||
stringLike = \case
|
stringLike = \case
|
||||||
LitStrVal s -> Just $ Text.unpack s
|
LitStrVal s -> Just $ Text.unpack s
|
||||||
SymbolVal (Id s) -> Just $ Text.unpack s
|
SymbolVal (Id s) -> Just $ Text.unpack s
|
||||||
_ -> Nothing
|
x -> Just $ show $ pretty x
|
||||||
|
|
||||||
stringLikeList :: [Syntax c] -> [String]
|
stringLikeList :: [Syntax c] -> [String]
|
||||||
stringLikeList syn = [ stringLike s | s <- syn ] & takeWhile isJust & catMaybes
|
stringLikeList syn = [ stringLike s | s <- syn ] & takeWhile isJust & catMaybes
|
||||||
|
|
|
@ -67,6 +67,7 @@ library
|
||||||
, Data.Config.Suckless.KeyValue
|
, Data.Config.Suckless.KeyValue
|
||||||
, Data.Config.Suckless.Script
|
, Data.Config.Suckless.Script
|
||||||
, Data.Config.Suckless.Script.File
|
, Data.Config.Suckless.Script.File
|
||||||
|
, Data.Config.Suckless.Almost.RPC
|
||||||
|
|
||||||
other-modules:
|
other-modules:
|
||||||
Data.Config.Suckless.Types
|
Data.Config.Suckless.Types
|
||||||
|
@ -95,6 +96,7 @@ library
|
||||||
, text
|
, text
|
||||||
, time
|
, time
|
||||||
, transformers
|
, transformers
|
||||||
|
, typed-process
|
||||||
, unliftio
|
, unliftio
|
||||||
, unordered-containers
|
, unordered-containers
|
||||||
, vector
|
, vector
|
||||||
|
|
Loading…
Reference in New Issue