FindMenu

From Pickwiki
Jump to navigationJump to search

Back to BasicSource, InfoLease

*SPLC**********************************************************************
*                                                                         *
*   Program Title    : FIND.MENU                                          *
*   Author           : Ian [[McGowan]]                                        *
*   Date Started     : January 11, 1991                                   *
*   Last Modified    : 14:22:26  17 MAY 1991 By Ian                       *
*   Description      : Given a string will go and look in menu file and   *
*                    : show menu tree of how to get to that string        *
*                    :                                                    *
*   Comments         : Most of the work is done in recursive subroutine   *
*                    : SPLC-BP,SUBS SPLC.SEARCH.MENU                      *
*   Usage            : FIND.MENU <search string>                          *
*                                                                         *
***************************************************************************
OPEN "DB.MENUS" TO MENU.F ELSE STOP 201,"DB.MENUS"

STR=FIELD(@SENTENCE,' ',2)
IF STR='' THEN
   PRINT "Enter menu or program to search for : ": ; INPUT STR
   IF STR="" OR STR="/" THEN STOP
END

PATH = '' ; MENU = 1 ; STR = OCONV(STR,"MCU")
CALL SPLC.SEARCH.MENU(MENU,STR,MENU.F,PATH)

--cut--

SUBROUTINE SPLC.SEARCH.MENU(MENU,STR,MENU.F,PATH)
*SPLC**********************************************************************
*                                                                         *
*   Program Title    : SPLC.SEARCH.MENU                                   *
*   Author           : Ian [[McGowan]]                                        *
*   Date Started     : January 11, 1991                                   *
*   Last Modified    : 15:07:10  14 MAY 1991 By Matt                      *
*   Description      : Subroutine to recursively descend menu tree,       *
*                    : looking for a specified program, or menu title.    *
*                    :                                                    *
*   Comments         : Called from UTILS FIND.MENU                        *
*                    :                                                    *
*   Usage            :                                                    *
*                                                                         *
***************************************************************************
**** Modified by JIM at 11:00:49  14 JAN 1991
* -- Added code to build a path description - how to get to
* -- the menu found.
VM = CHAR(253)
READ R FROM MENU.F, MENU THEN
   TITLES = OCONVS(R<2>,"MCU") ; PROGS  = OCONVS(R<3>,"MCU") ; FLAGS  = R<4>
   I = DCOUNT(PROGS,VM)
   FOR F = 1 TO I
      IF FLAGS<1,F> # 'M' THEN
         IF INDEX(PROGS<1,F>,STR,1) # 0 OR INDEX(TITLES<1,F>,STR,1) # 0 THEN
            PRINT TITLES<1,F>"L#30":"  ":PROGS<1,F>"L#30":"  ":
            K = DCOUNT(PATH,VM) ; FOR J = 2 TO K ; PRINT PATH<1,J>:',': ; NEXT J ; PRINT F
         END
      END ELSE
         MENU = PROGS<1,F>
         PATH = PATH:VM:F
         CALL SPLC.SEARCH.MENU(MENU,STR,MENU.F,PATH)
         K = DCOUNT(PATH,VM) ; PATH=DELETE(PATH,1,K)
      END
   NEXT F
END
RETURN