suckless-conf, hide entries

This commit is contained in:
voidlizard 2025-01-20 09:23:30 +03:00
parent e7081e495c
commit 4ba2f040ae
4 changed files with 34 additions and 11 deletions

View File

@ -107,7 +107,8 @@ initRepo syn = do
callRpcWaitMay @RpcPollAdd (TimeoutSec 1) peerAPI (reflog, "reflog", 17) callRpcWaitMay @RpcPollAdd (TimeoutSec 1) peerAPI (reflog, "reflog", 17)
>>= orThrowUser "rpc timeout" >>= orThrowUser "rpc timeout"
liftIO $ print $ pretty repo -- FIXME: remove-this
liftIO $ print $ pretty $ mkForm "manifest" repo
CreateRepoDefBlock pk -> do CreateRepoDefBlock pk -> do

View File

@ -47,18 +47,25 @@ theDict :: forall m . ( HBS2GitPerks m
theDict = do theDict = do
makeDict @C do makeDict @C do
-- TODO: write-man-entries -- TODO: write-man-entries
myHelpEntry myEntries
entry $ bindValue "best" (mkInt 22) entry $ bindValue "best" (mkInt 22)
internalEntries hidden $ internalEntries
where where
myHelpEntry = do myEntries = hidePrefix "test:" do
entry $ bindMatch "--help" $ nil_ $ \case entry $ bindMatch "--help" $ nil_ $ \case
HelpEntryBound what -> do HelpEntryBound what -> do
helpEntry what helpEntry what
quit quit
[ StringLike x ] -> helpList True (Just x) >> quit
_ -> helpList True Nothing >> quit
hidden do
entry $ bindMatch "--help-all" $ nil_ $ \case
[ StringLike x ] -> helpList False (Just x) >> quit
_ -> helpList False Nothing >> quit _ -> helpList False Nothing >> quit
entry $ bindMatch "compression" $ nil_ $ \case entry $ bindMatch "compression" $ nil_ $ \case
@ -90,6 +97,8 @@ theDict = do
entry $ bindMatch "debug" $ nil_ $ const do entry $ bindMatch "debug" $ nil_ $ const do
setLogging @DEBUG $ toStderr . logPrefix "[debug] " setLogging @DEBUG $ toStderr . logPrefix "[debug] "
-- hidden do
entry $ bindMatch "test:git:normalize-ref" $ nil_ \case entry $ bindMatch "test:git:normalize-ref" $ nil_ \case
[ StringLike s ] -> display $ mkStr @C (show $ pretty $ gitNormaliseRef (fromString s)) [ StringLike s ] -> display $ mkStr @C (show $ pretty $ gitNormaliseRef (fromString s))
_ -> throwIO (BadFormException @C nil) _ -> throwIO (BadFormException @C nil)

View File

@ -1,5 +1,6 @@
{-# Language UndecidableInstances #-} {-# Language UndecidableInstances #-}
{-# Language PatternSynonyms #-} {-# Language PatternSynonyms #-}
{-# Language RecordWildCards #-}
module Data.Config.Suckless.Script module Data.Config.Suckless.Script
( module Exported ( module Exported
, module Data.Config.Suckless.Script , module Data.Config.Suckless.Script
@ -29,13 +30,13 @@ helpList hasDoc p = do
d <- ask >>= readTVarIO d <- ask >>= readTVarIO
let ks = [k | Id k <- List.sort (HM.keys d) let ks = [k | Id k <- List.sort (HM.keys d)
, match k , match k
, not hasDoc || docDefined (HM.lookup (Id k) d) , docDefined (HM.lookup (Id k) d) || not hasDoc
] ]
display_ $ vcat (fmap pretty ks) display_ $ vcat (fmap pretty ks)
where where
docDefined (Just (Bind (Just w) _)) = True docDefined (Just (Bind (Just Man{..}) _)) | not manHidden = True
docDefined _ = False docDefined _ = False
helpEntry :: MonadUnliftIO m => Id -> RunM c m () helpEntry :: MonadUnliftIO m => Id -> RunM c m ()
@ -50,7 +51,6 @@ pattern HelpEntryBound :: forall {c}. Id -> [Syntax c]
pattern HelpEntryBound what <- [ListVal (SymbolVal "builtin:lambda" : SymbolVal what : _ )] pattern HelpEntryBound what <- [ListVal (SymbolVal "builtin:lambda" : SymbolVal what : _ )]
-- FIXME: move-to-suckless-script
splitOpts :: [(Id,Int)] splitOpts :: [(Id,Int)]
-> [Syntax C] -> [Syntax C]
-> ([Syntax C], [Syntax C]) -> ([Syntax C], [Syntax C])

View File

@ -23,6 +23,8 @@ import Data.Data
import Data.Function as Export import Data.Function as Export
import Data.Functor as Export import Data.Functor as Export
import Data.Hashable import Data.Hashable
import Data.HashSet (HashSet)
import Data.HashSet qualified as HS
import Data.HashMap.Strict (HashMap) import Data.HashMap.Strict (HashMap)
import Data.HashMap.Strict qualified as HM import Data.HashMap.Strict qualified as HM
import Data.Kind import Data.Kind
@ -393,8 +395,20 @@ makeDict w = execWriter ( fromMakeDict w )
entry :: Dict c m -> MakeDictM c m () entry :: Dict c m -> MakeDictM c m ()
entry = tell entry = tell
hide :: MakeDictM c m () hide :: Bind c m -> Bind c m
hide = pure () hide (Bind w x) = Bind (Just updatedMan) x
where
updatedMan = case w of
Nothing -> mempty { manHidden = True }
Just man -> man { manHidden = True }
hidden :: MakeDictM c m () -> MakeDictM c m ()
hidden = censor (HM.map hide)
hidePrefix :: Id -> MakeDictM c m () -> MakeDictM c m ()
hidePrefix (Id p) = censor (HM.filterWithKey exclude)
where
exclude (Id k) _ = not (Text.isPrefixOf p k)
desc :: Doc ann -> MakeDictM c m () -> MakeDictM c m () desc :: Doc ann -> MakeDictM c m () -> MakeDictM c m ()
desc txt = censor (HM.map setDesc) desc txt = censor (HM.map setDesc)
@ -414,7 +428,6 @@ returns tp txt = censor (HM.map setReturns)
w0 = mempty { manReturns = Just (ManReturns tp txt) } w0 = mempty { manReturns = Just (ManReturns tp txt) }
setReturns (Bind w x) = Bind (Just (maybe w0 (<>w0) w)) x setReturns (Bind w x) = Bind (Just (maybe w0 (<>w0) w)) x
addSynopsis :: ManSynopsis -> Bind c m -> Bind c m addSynopsis :: ManSynopsis -> Bind c m -> Bind c m
addSynopsis synopsis (Bind w x) = Bind (Just updatedMan) x addSynopsis synopsis (Bind w x) = Bind (Just updatedMan) x
where where