mirror of https://github.com/voidlizard/hbs2
bf6: show man for bound alias
This commit is contained in:
parent
f96f37f9d1
commit
1edd50008c
|
@ -487,6 +487,8 @@ compression ; prints compression level
|
|||
manifest <- Repo.getRepoManifest
|
||||
liftIO $ print $ pretty $ mkForm "manifest" (coerce manifest)
|
||||
|
||||
entry $ bindAlias "manifest" "repo:manifest"
|
||||
|
||||
brief "shows repo reflog" $
|
||||
entry $ bindMatch "repo:reflog" $ nil_ $ \syn -> lift $ connectedDo do
|
||||
resolveRepo syn
|
||||
|
|
|
@ -40,12 +40,18 @@ helpList hasDoc p = do
|
|||
docDefined _ = False
|
||||
|
||||
helpEntry :: MonadUnliftIO m => Id -> RunM c m ()
|
||||
helpEntry what = do
|
||||
man <- ask >>= readTVarIO
|
||||
<&> HM.lookup what
|
||||
<&> maybe mzero bindMan
|
||||
helpEntry what' = do
|
||||
|
||||
liftIO $ hPutDoc stdout (pretty man)
|
||||
found <- flip fix what' $ \next what -> do
|
||||
ask >>= readTVarIO
|
||||
<&> HM.lookup what
|
||||
<&> (bindMan =<<)
|
||||
>>= \case
|
||||
Nothing -> pure Nothing
|
||||
Just (Man{manIsAliasFor = Just x, manBrief = Nothing}) -> next x
|
||||
Just x -> pure (Just ( x { manName = Just (ManName what') } ))
|
||||
|
||||
liftIO $ hPutDoc stdout (pretty found)
|
||||
|
||||
pattern HelpEntryBound :: forall {c}. Id -> [Syntax c]
|
||||
pattern HelpEntryBound what <- [ListVal (SymbolVal "builtin:lambda" : SymbolVal what : _ )]
|
||||
|
|
|
@ -113,18 +113,19 @@ class ManNameOf a ann where
|
|||
|
||||
data Man a =
|
||||
Man
|
||||
{ manName :: Maybe (ManName a)
|
||||
, manHidden :: Bool
|
||||
, manBrief :: Maybe ManBrief
|
||||
, manSynopsis :: [ManSynopsis]
|
||||
, manDesc :: Maybe ManDesc
|
||||
, manReturns :: Maybe ManReturns
|
||||
, manExamples :: [ManExamples]
|
||||
{ manName :: Maybe (ManName a)
|
||||
, manHidden :: Bool
|
||||
, manBrief :: Maybe ManBrief
|
||||
, manSynopsis :: [ManSynopsis]
|
||||
, manDesc :: Maybe ManDesc
|
||||
, manReturns :: Maybe ManReturns
|
||||
, manExamples :: [ManExamples]
|
||||
, manIsAliasFor :: Maybe Id
|
||||
}
|
||||
deriving stock (Eq,Show,Generic)
|
||||
|
||||
instance Monoid (Man a) where
|
||||
mempty = Man Nothing False Nothing mempty Nothing Nothing mempty
|
||||
mempty = Man Nothing False Nothing mempty Nothing Nothing mempty Nothing
|
||||
|
||||
instance Semigroup (Man a) where
|
||||
(<>) a b = Man (manName b <|> manName a)
|
||||
|
@ -134,6 +135,7 @@ instance Semigroup (Man a) where
|
|||
(manDesc b <|> manDesc a)
|
||||
(manReturns b <|> manReturns a)
|
||||
(manExamples a <> manExamples b)
|
||||
(manIsAliasFor b <|> manIsAliasFor a)
|
||||
|
||||
instance ManNameOf Id a where
|
||||
manNameOf = ManName
|
||||
|
@ -873,7 +875,7 @@ bindAlias :: forall c m . ( MonadUnliftIO m
|
|||
=> Id -> Id -> Dict c m
|
||||
bindAlias n fn = HM.singleton n (Bind man (BindLambda callAlias))
|
||||
where
|
||||
man = Just $ mempty { manName = Just (manNameOf n) }
|
||||
man = Just $ mempty { manName = Just (manNameOf n), manIsAliasFor = Just fn }
|
||||
callAlias syn = do
|
||||
ask >>= readTVarIO
|
||||
<&> (fmap bindAction . HM.lookup fn)
|
||||
|
|
Loading…
Reference in New Issue