home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Monster Media 1994 #1
/
monster.zip
/
monster
/
BBS_UTIL
/
BM0406_A.ZIP
/
RCHAT401.ZIP
/
RCHAT401.BAS
< prev
next >
Wrap
BASIC Source File
|
1992-09-14
|
32KB
|
833 lines
'
' RChat401 -- Or, RBBS-Chat, release 4.01. A character by character
' internode chat program..
'
' Not the worlds prettiest, or cleanest code.. but I'm under no illusions..
'
' Copyright 1989-1992 By John Morris All Rights Reserved
'
' I'm not a big fan of global variables, but here goes..
'
' $INCLUDE: 'RBBS-VAR.MOD' 'RBBS-VAR.BAS minus the DEF FN...
'
REM **********************************************************************
REM *** Change 'CONST LogChatToDisk = -1' if you wish to record ***
REM *** all of the chats. This is for your protection! If you turn ***
REM *** this option on (-1) then the users will be notified that ***
REM *** the chat is being recorded (they have a right to know!) ***
REM *** Chat filenames have this format: MM-DD-HH.CHAT or ***
REM *** month-day-hour.CHT ***
REM **********************************************************************
CONST LogChatToDisk = 0
CONST ChatFileName$ = "H:RBBSCHAT.DEF" 'change this to a RAM drive for
'best possible speed (see docs)
'must change to match BBS default
'drive or RAM disk..
DEFINT A - Z
REM *************************************************************
REM ** The following are needed by only 2 or 3 subprograms, so,**
REM ** they are declared COMMON, and then SHARED only in some **
REM ** of the subprgms.. the fewer that have access the better **
REM *************************************************************
COMMON /Chat/ DoTrueChat, HasPaged, UpperNode, LowerNode, SaveToDisk
COMMON /Chat/ NodesToSquelch$, RePage, DOSVersion
REM *************************************************************
REM ** The below are the shared fields used by the subprograms **
REM ** Each and every one is declared as COMMON SHARED so every**
REM ** subprogram has access to the following variables **
REM *************************************************************
COMMON SHARED /ChatField/ ChatActivity$, PagingNode$, PrivateFor$
COMMON SHARED /ChatField/ ChatInput$, ChatName$, InTrueChat$
COMMON SHARED /ChatField/ TrueChatIndex$, SavingToDisk$, BBSActivity$
'
59800 ' $SUBTITLE: 'LogNewForChat - Save user info for chat'
' $PAGE
'
' NAME -- LogNewForChat
'
' INPUTS -- NodesInSystem -- needed for creation of RBBSCHAT.DEF
'
' OUTPUTS -- Updates the node record in RBBSCHAT.DEF with this users
' name and chat activity (always "I") when the user logs on.
'
' PURPOSE -- See OUTPUTS. Also, if no RBBSCHAT.DEF is not found, one will be
' created.
'
SUB LogNewForChat(NodesInSystem) STATIC
SHARED DOSVersion
CALL FindItX (ChatFileName$, 10)
REM ** If "RBBSCHAT.DEF" does not exist, then create it **
IF NOT ZOK THEN
CALL OpenWrk10 (ChatFileName$)
FIELD 10, 128 AS TempNode$
LSET TempNode$ = SPACE$(128)
FOR Index = 1 TO ZMaxNodes
CALL Update10 (Index, ZFalse)
NEXT
END IF
ChatIndex = ZNodeRecIndex - 1
CLOSE 10
CALL OpenWrk10 (ChatFileName$)
CALL Field10
CALL LockUnlock10 (ZTrue)
CALL Update10 (ChatIndex, ZTrue)
LSET ChatActivity$ = "I" ' I means inactive
LSET PagingNode$ = MKI$(0)
LSET ChatName$ = SPACE$(31)
IF ZActiveUserName$ = ZSysopPswd1$ + " " + ZSysopPswd2$ THEN
LSET ChatName$ = "SYSOP"
ELSE
LSET ChatName$ = ZActiveUserName$
END IF
LSET ChatInput$ = SPACE$(72)
LSET InTrueChat$ = "I"
CALL Update10 (ChatIndex, ZFalse)
CALL LockUnlock10 (ZFalse)
CLOSE 10
HasPaged = 0
END SUB
59810 ' $SUBTITLE: 'CBCHECK - Check for a page attempt'
' $PAGE
'
' NAME -- CBCHECK
'
' INPUTS -- NONE
'
' OUTPUTS -- ChatActivity$ Changed to reflect whether or not they
' are going to chat
' WillChat If WillChat is TRUE, then the user will
' automatically be thrust unawares into
' chat mode.. They said yes... didn't they?
'
' PURPOSE -- Check to see if we have been paged from another node
'
SUB CBCheck(WillChat) STATIC
' You might just wanna REM this out..
IF NOT ZAvailableForChat THEN
EXIT SUB
END IF
WillChat = ZFalse
ZOutTxt$ = ""
IsTrueChat = ZFalse
CALL FindItX (ChatFileName$, 10)
IF NOT ZOK THEN
EXIT SUB
END IF
ChatIndex = ZNodeRecIndex - 1
CLOSE 10
CALL OpenWrk10 (ChatFileName$)
CALL Field10
CALL Update10 (ChatIndex, ZTrue)
IF ChatActivity$ = "R" THEN 'R means request for chat
PagerIndex = CVI(PagingNode$)
CALL RingCaller
CALL Update10 (PagerIndex, ZTrue)
IsTrueChat = (InTrueChat$ = "A")
ZOutTxt$ = ChatName$
CALL TrimTrail (ZOutTxt$, " ")
CALL NameCaps(ZOutTxt$)
CALL UpdtCalr("Paged for Chat by " + ZOutTxt$ + " on node" + STR$(PagerIndex), 1)
CALL QuickTPut( ZOutTxt$ + " is requesting that you join in a chat!", 1)
ZOutTxt$ = "Would you like to join the chat ([Y]/N)" 'JM920206
ZSubParm = 1
CALL TGet
IF ZSubParm = -1 THEN
CLOSE 10
EXIT SUB
END IF
CALL LockUnlock10 (ZTrue)
CALL Update10 (ChatIndex, ZTrue)
IF ZNo THEN
LSET ChatActivity$ = "N" 'No, I don't think I'll chat
ELSE
LSET ChatActivity$ = "Y" 'Yeah, I might just join a chat
WillChat = ZTrue
END IF
IF IsTrueChat THEN
LSET InTrueChat$ = "Y"
ELSE
LSET InTrueChat$ = "I"
END IF
CALL Update10 (ChatIndex, ZFalse)
CALL LockUnlock10 (ZFalse)
END IF
CLOSE 10
END SUB
59820 ' $SUBTITLE: 'PageEm - attempt to page another user to chat'
' $PAGE
'
' NAME -- PageEm
'
' INPUTS -- ShowOnly Show whos is on the other nodes only
' NodesInSystem Number of nodes in this system
'
' OUTPUTS -- HasPaged -1 exit chat mode
' 0 don't check for reply to page
' 1 - NodesInSystem check for page reply
'
' PURPOSE -- Page another user on the system and set up for a reply
' from the other user
'
SUB PageEm(CurrentNodeIndex, NodesInSystem) STATIC
REM ** Page 'Em needs access to the COMMON variable HasPaged & RePage **
SHARED DoTrueChat, HasPaged, UpperNode, LowerNode, RePage
RePageEm:
HasPaged = 0
CALL WhosOn (NodesInSystem)
CALL SkipLine(1)
ZOutTxt$ = "Chat with which node (1 -" + STR$(NodesInSystem) + ")" + ZPressEnter$
ZSubParm = 1
CALL TGet
IF ZWasQ = 0 OR ZSubParm = -1 THEN
EXIT SUB
END IF
CALL CheckInt(ZUserIn$(1))
CALL Field10
IF ZTestedIntValue > 0 AND ZTestedIntValue <= NodesInSystem AND _
ZTestedIntValue <> CurrentNodeIndex THEN
CALL Update10 (ZTestedIntValue, ZTrue)
IF ChatActivity$ = "A" THEN 'if other node already
IF InTrueChat$ = "A" THEN 'can't page 'em if in true chat
CALL QuickTPut1("Sorry, the node you requested is in a private chat!")
EXIT SUB
END IF
'
'If the other node is active in chat , but not in a private chat
'then we'll just drop down to 'CALL CBTrueChat'
'
ELSE
HasPaged = ZTestedIntValue
ZOutTxt$ = "Should this be a private chat ([Y]/N)"
ZSubParm = 1
CALL TGet
IF ZYes OR (ZWasQ = 0) THEN
DoTrueChat = ZTrue
LowerNode = HasPaged
UpperNode = HasPaged
END IF
CALL QuickTPut1("Hang on, I'll let them know you want to chat")
CALL QuickTPut1("If you don't get an answer within a couple minutes,")
CALL QuickTPut1("then you probably won't get an answer")
LSET ChatActivity$ = "R" 'R means Request
LSET PagingNode$ = MKI$(CurrentNodeIndex)
CALL LockUnlock10 (ZTrue)
CALL Update10 (ZTestedIntValue, ZFalse)
CALL LockUnlock10 (ZFalse)
IF DoTrueChat THEN
CALL LockUnlock10 (ZTrue)
CALL Update10 (CurrentNodeIndex, ZTrue)
LSET InTrueChat$ = "A"
CALL Update10 (CurrentNodeIndex, ZFalse)
CALL LockUnlock10 (ZFalse)
END IF
END IF
CALL CBTrueChat(NodesInSystem)
' user might want to repage some other node.. we'll just loop back
' and start over..
IF RePage THEN
GOTO RePageEm
END IF
END IF
END SUB
59830 ' $SUBTITLE: 'CBTrueChat - The letter by letter chat'
' $PAGE
'
' NAME -- CBTrueChat
'
' INPUTS -- NodesInSystem
'
' INTERNAL - NodesToSquelch$ STRING OF NODES NOT TO RECEIVE TEXT FROM
' HasPaged NODE (IF ANY) THAT THIS USER PAGED
' CurrentNodeIndex NODE RECORD IN "RBBSCHAT.DEF"
' ChatActivity$ CURRENT STATUS OF EACH NODE
' PagingNode$ NODE WHICH HAS PAGED THIS ONE
' ChatInput$ CURRENT TEXT INPUT BY USER FOR CHATTING
' ChatName$ NAME OF USER ON EACH NODE (NOT CURRENTLY USED)
' SquelchIt BOOLEAN - MEANS NODE IS IGNORED
' ZUserIn$() USED TO SAVE CURRENT STATUS OF EACH NODE
' THIS INFO IS LATER COMPARED, AND IF THAT
' STATUS IS CHANGED, THEN THE USER IS NOTIFIED
' OF THE CHANGE
' DoTrueChat Means we are in a true chat mode, we'll
' only check one node for input
'
'
' OUTPUTS -- NONE
'
' PURPOSE -- To allow users to chat between nodes in several different
' ways.
'
SUB CBTrueChat(NodesInSystem) STATIC
SHARED DoTrueChat, HasPaged, UpperNode, LowerNode, SaveToDisk
SHARED NodesToSquelch$, RePage
CALL SaveUserActivity("C", ZNodeRecIndex, ZFalse)
ZCol = 1
SendRemote = ZRemoteEcho
SaveToDisk = ZFalse
DoTrueChat = ZFalse
NodesToSquelch$ = ""
REM This can now be set by 'PageEm' -before- CBTrueChat is ever called..
' HasPaged = 0
IF HasPaged AND LogChatToDisk THEN
CALL SetUpLogFile
END IF
ChatSubParm = 0
CALL FindItX (ChatFileName$, 10)
IF ZOK THEN
CurrentNodeIndex = ZNodeRecIndex - 1
CLOSE 10
CALL OpenWrk10 (ChatFileName$)
CALL Field10
IF NOT RePage THEN
CALL UpdtCalr("Entered CBTrueCh@ sim at " + TIME$, 1)
END IF
CALL QuickTPut1("Type Ctrl-Q or ESCape for a list of commands")
REDIM TrueChatIndexHold(NodesInSystem)
RePage = ZFalse
CALL LockUnlock10 (ZTrue)
CALL Update10 (CurrentNodeIndex, ZTrue)
REM ** Set up for truechat mode.. two nodes in a private chat **
IF InTrueChat$ = "Y" OR InTrueChat$ = "A" THEN
IF InTrueChat$ = "Y" THEN
LSET InTrueChat$ = "A"
LowerNode = CVI(PagingNode$)
UpperNode = CVI(PagingNode$)
END IF
DoTrueChat = ZTrue
ELSE
LowerNode = 1
UpperNode = NodesInSystem
END IF
LSET ChatActivity$ = "A"
LSET TrueChatIndex$ = MKI$(1)
CALL Update10 (CurrentNodeIndex, ZFalse)
CALL LockUnlock10 (ZFalse)
REM ** Load in current node status for later comparison **
FOR LineIndex = 1 TO NodesInSystem
CALL Update10 (LineIndex, ZTrue)
ZUserIn$(LineIndex) = ChatActivity$
REM ** save current index so we don't get a bunch of trash if **
REM ** a chat is already in progress. **
IF ChatActivity$ = "A" THEN
TrueChatIndexHold(LineIndex) = CVI(TrueChatIndex$)
ELSE
TrueChatIndexHold(LineIndex) = 1
END IF
NEXT
REM ** Set Autologoff time before we start looping **
ZAutoLogoff! = TIMER + ZWaitBeforeDisconnect
REM ** We are currently getting name from MESSAGES file.. set that up..
WasA1$ = ZActiveMessageFile$
ZActiveMessageFile$ = ZOrigMsgFile$
CALL OpenMsg
FIELD 1, 128 AS ZMsgRec$
DO 'the wild chat thingie..
REM **************************************************************************
REM ******Check for answer to page, or text from other users in chat ********
REM ******If the other guy has 'page availability' turned off, then ********
REM ******we simply won't tell this guy.. he won't know the difference********
REM **************************************************************************
FOR LineIndex = LowerNode TO UpperNode
SquelchIt = ZFalse
IF LineIndex <> CurrentNodeIndex THEN
CALL Update10 (LineIndex, ZTrue)
Index$ = MID$(STR$(LineIndex), 2, 1)
REM ** Check to see if node (LineIndex) has been squelched **
IF NodesToSquelch$ <> "" THEN
SquelchIt = (INSTR(NodesToSquelch$, Index$) > 0)
END IF
REM ** Check to see if other node in truechat **
IF NOT SquelchIt AND NOT DoTrueChat THEN
SquelchIt = (InTrueChat$ = "A")
END IF
REM ** Check for answer to page (if a page was done) **
IF HasPaged = LineIndex THEN
IF ChatActivity$ <> "R" THEN
IF ChatActivity$ = "N" THEN
CALL QuickTPut("Paged user said NO to chat mode!", 1)
HasPaged = 0
ELSEIF ChatActivity$ = "Y" THEN
REM ** if the other dude answered Yes, they will automatically
REM ** be sent into the chat mode.. so don't bother telling the
REM ** guy that they answered yes.. just turn off HasPaged
HasPaged = 0
END IF
END IF
END IF
ChatTemp$ = ""
NameTemp$ = ""
REM ** Check for change in node activity **
REM ** In this case, see if someone has left the chat **
REM ** node must not be squelched **
IF NOT SquelchIt THEN
IF (ZUserIn$(LineIndex) = "A") AND (ChatActivity$ = "I") THEN
GOSUB 59840
CALL QuickTPut(NameTemp$ + " on Node " + Index$ + " has exited chat mode!", 1)
IF DoTrueChat THEN
DoTrueChat = ZFalse
CALL LockUnlock10 (ZTrue)
CALL Update10 (CurrentNodeIndex, ZTrue)
LSET InTrueChat$ = "I"
LSET ChatInput$ = SPACE$(72)
LSET TrueChatIndex$ = MKI$(1)
CALL Update10 (CurrentNodeIndex, ZFalse)
CALL LockUnlock10 (ZFalse)
REM ** TrueChat over.. start looping thru all nodes
LowerNode = 1
UpperNode = NodesInSystem
END IF
END IF
REM ** OR, If someone has joined the chat **
IF (ZUserIn$(LineIndex) <> "A") AND (ChatActivity$ = "A") THEN
GOSUB 59840
CALL QuickTPut(NameTemp$ + " on Node " + Index$ + " has entered the chat!", 1)
REM ** Save the ring buffer index as they currently see it **
TrueChatIndexHold(LineIndex) = CVI(TrueChatIndex$)
END IF
END IF
REM ** Save new node status (if any) **
ZUserIn$(LineIndex) = ChatActivity$
REM ** If other node is active (& not squelched) check it **
IF (ChatActivity$ = "A") AND (NOT SquelchIt) THEN
IF (CVI(TrueChatIndex$) <> TrueChatIndexHold(LineIndex)) THEN
OtherNodeInput$ = MID$(ChatInput$, TrueChatIndexHold(LineIndex), 1)
IF OtherNodeInput$ = CHR$(8) THEN
CALL LPrnt(ZLocalBkSp$, 0)
CALL PutCom (ZBackSpace$)
IF SaveToDisk THEN
CALL PrintWork(ZBackSpace$)
END IF
IF ZCol > 0 THEN
ZCol = ZCol - 1
END IF
ELSEIF OtherNodeInput$ = ZCarriageReturn$ THEN
CALL SkipLine(1)
IF SaveToDisk THEN
CALL PrintWorkA("")
END IF
ZCol = 1
ELSE
IF SaveToDisk THEN 'save to disk before colorization
CALL PrintWork(OtherNodeInput$)
END IF
CALL ColorText(OtherNodeInput$, LineIndex)
CALL LPrnt (OtherNodeInput$, 0)
CALL PutCom(OtherNodeInput$)
ZCol = ZCol + 1
IF (ZCol > 65 AND OtherNodeInput$ = CHR$(32)) THEN
CALL SkipLine(1)
IF SaveToDisk THEN
CALL PrintWorkA("")
END IF
ZCol = 1
END IF
END IF
TrueChatIndexHold(LineIndex) = TrueChatIndexHold(LineIndex) + 1
IF TrueChatIndexHold(LineIndex) > 72 THEN TrueChatIndexHold(LineIndex) = 1
END IF
END IF
END IF
NEXT
REM *************************************************************************
REM *******Get text from local user (local, as in, this node of RBBS)********
REM *******Also local, as in.. SysOp ********
REM *************************************************************************
CALL FindFKey ' will also get local key pressed
IF ZSubParm < 0 THEN
EXIT DO
END IF
Key$ = ""
IF NOT ZLocalUser THEN
CALL EOFComm (Char%)
ELSE
Char% = -1
END IF
IF Char% <> -1 THEN 'if remote key in then get it
CALL GetCom(Key$)
ELSE
Key$ = ZKeyPressed$ 'INKEY$ is performed in FindFKey
END IF
IF Key$ <> "" THEN
IF LEN(Key$) = 1 THEN
IF Key$ = ZEscape$ OR Key$ = CHR$(17) THEN
CALL ChatCommand(ChatSubParm, CurrentNodeIndex, NodesInSystem)
IF ChatSubParm OR RePage THEN
EXIT DO
END IF
ELSE
CALL LockUnlock10 (ZTrue)
CALL Update10(CurrentNodeIndex, ZTrue)
TempChatInput$ = ChatInput$
TempTrueChatIndex = CVI(TrueChatIndex$)
MID$(TempChatInput$, TempTrueChatIndex, 1) = Key$
LSET ChatInput$ = TempChatInput$
TempTrueChatIndex = TempTrueChatIndex + 1
IF TempTrueChatIndex > 72 THEN
TempTrueChatIndex = 1
END IF
LSET TrueChatIndex$ = MKI$(TempTrueChatIndex)
CALL Update10(CurrentNodeIndex, ZFalse)
CALL LockUnlock10 (ZFalse)
IF Key$ <> CHR$(8) THEN
IF SaveToDisk THEN
CALL PrintWork(Key$)
END IF
IF ZWasGR = 2 AND Key$ <> ZCarriageReturn$ THEN
Key$ = ZEmphasizeOff$ + Key$
END IF
CALL QuickTPut(Key$, 0)
ELSE
CALL LPrnt(ZLocalBkSp$, 0)
IF (NOT ZLocalUser) AND SendRemote THEN
CALL PutCom (ZBackSpace$)
END IF
IF SaveToDisk THEN
CALL PrintWork(ZBackSpace$)
END IF
ZCol = ZCol - 2
END IF
IF Key$ = ZCarriageReturn$ THEN
IF SendRemote AND ZLineFeeds THEN
CALL PutCom(ZLineFeed$)
END IF
ZCol = 0
END IF
ZCol = ZCol + 1
END IF
REM ** Reset auto log-off timeski..
ZAutoLogoff! = TIMER + ZWaitBeforeDisconnect
END IF
END IF
REM ** I'll call the below.. pseudo-wordwrap.. or a way to
REM ** get around having to do word wrap.. it ain't easy in
REM ** char by char mode... Much easier in C than in BASIC
IF (ZCol > 72) OR (ZCol > 65 AND Key$ = CHR$(32)) THEN
CALL SkipLine(1)
IF SaveToDisk THEN
CALL PrintWorkA("")
END IF
ZCol = 1
END IF
CALL CheckCarrier
IF ZSubParm = -1 THEN
EXIT DO
END IF
CALL CheckTimeRemain(MinsRemaining)
IF ZSubParm = -1 THEN
EXIT DO
END IF
CALL CheckTime(ZAutoLogoff!, TempElapsed!, 1)
IF TempElapsed! <= 0 THEN
ZWaitExpired = ZTrue
EXIT DO
END IF
LOOP
CALL LockUnlock10 (ZTrue)
CALL Update10 (CurrentNodeIndex, ZTrue)
LSET ChatInput$ = SPACE$(72)
LSET ChatActivity$ = "I"
LSET InTrueChat$ = "I"
CALL Update10 (CurrentNodeIndex, ZFalse)
CALL LockUnlock10 (ZFalse)
IF HasPaged > 0 THEN
CALL LockUnlock10 (ZTrue)
CALL Update10 (HasPaged, ZTrue)
IF ChatActivity$ = "R" THEN
LSET ChatActivity$ = "I"
CALL Update10 (HasPaged, ZFalse)
END IF
CALL LockUnlock10 (ZFalse)
END IF
CLOSE 10
CLOSE 2
ZActiveMessageFile$ = WasA1$
ERASE TrueChatIndexHold 'free memory taken by integer array
END IF
HasPaged = 0
EXIT SUB
59840 GET 1, (LineIndex + 1)
IF MID$(ZMsgRec$, 55, 2) = "-1" AND NOT ZSysop THEN
NameTemp$ = "SYSOP"
ELSE
NameTemp$ = MID$(ZMsgRec$, 1, 26)
END IF
CALL TrimTrail (NameTemp$, " ")
CALL NameCaps(NameTemp$)
RETURN
END SUB
59900 SUB ColorText(Text$, NodeIndex) STATIC
IF ZWasGR = 2 THEN
TextColor = (NodeIndex MOD 5) + 2
Text$ = CHR$(27) + "[1;3" + RIGHT$(STR$(TextColor), 1) + ";40m" + Text$
END IF
END SUB
REM **
REM ** Save what a user is doing in the BBS.. for W)hos on mods..... **
REM **
59910 SUB SaveUserActivity(Activity$, NodeRecordIndex, ReadIt) STATIC
ChatNodeIndex = NodeRecordIndex - 1
CLOSE 10
CALL OpenWrk10 (ChatFileName$)
CALL Field10
IF ReadIt THEN
CALL Update10(ChatNodeIndex, ZTrue)
Activity$ = BBSActivity$
ELSE
CALL LockUnlock10 (ZTrue)
CALL Update10(ChatNodeIndex, ZTrue)
LSET BBSActivity$ = Activity$
CALL Update10(ChatNodeIndex, ZFalse)
CALL LockUnlock10 (ZFalse)
END IF
IF NOT ReadIt THEN
CLOSE 10
END IF
END SUB
REM **
REM ** Chat command line mode.. this is where they can do certain functions
REM ** pertaining to the chat
REM **
REM ** ChatSubParm is returned TRUE when a user wishes to exit the chat mode
59920 SUB ChatCommand(ChatSubParm, CurrentNodeIndex, NodesInSystem) STATIC
SHARED DoTrueChat, HasPaged, UpperNode, LowerNode, SaveToDisk
SHARED NodesToSquelch$, RePage
CALL SkipLine(1)
59921 IF NOT ZExpertUser THEN
59922 ZFileName$ = "CHAT.MNU"
CALL Graphic(ZFileName$)
CALL BufFile(ZFileName$, WasX)
END IF
ZOutTxt$ = "CHAT command "
IF ZExpertUser THEN
ZOutTxt$ = ZOutTxt$ + "<[C],H,W,Q,X"
IF NOT DoTrueChat THEN
ZOutTxt$ = ZOutTxt$ + ",P,S,U"
END IF
ELSE
ZOutTxt$ = ZOutTxt$ + "<[C]hat,H)elp,W)ho,Q)uit,X)pert"
IF NOT DoTrueChat THEN
ZOutTxt$ = ZOutTxt$ + ",P)age,S)qlch,U)nsqlch"
END IF
END IF
ZOutTxt$ = ZOutTxt$ + ">"
ZSubParm = 1
CALL TGet
IF ZSubParm = -1 THEN
GOTO 59940
END IF
ChatSubParm = ZFalse
IF ZWasQ > 0 THEN
CALL AllCaps(ZUserIn$(1))
SELECT CASE LEFT$(ZUserIn$(1), 1)
CASE "C" REM ** Return to chat mode
EXIT SUB
CASE "H", "?" REM ** Help.. means show the Chat menu
GOTO 59922
CASE "W" REM ** Show whos on the system
CALL WhosOn(NodesInSystem)
GOTO 59921
CASE "Q" REM ** Quit/Exit out of chat mode
ChatSubParm = ZTrue
EXIT SUB
CASE "X" REM ** Toggle expert mode
CALL Toggle(9)
GOTO 59921
REM Got to eliminate this for now..
CASE "P" REM ** Page another node to chat
RePage = ZTrue
EXIT SUB
CASE "S" REM ** Squelch -- turn off reception of any node
IF NOT DoTrueChat THEN
ZOutTxt$ = "Which node do you wish to squelch (1 -" + STR$(NodesInSystem) + ")" + PRESS.ENTER$
ZSubParm = 1
CALL TGet
IF ZSubParm = -1 THEN
GOTO 59940
END IF
IF ZWasQ > 0 THEN
CALL CheckInt(ZUserIn$(1))
IF ZTestedIntValue <> CurrentNodeIndex THEN
NodesToSquelch$ = NodesToSquelch$ + MID$(STR$(ZTestedIntValue), 2, 1)
CALL QuickTPut("Node" + STR$(ZTestedIntValue) + " has been squelched!", 1)
ELSE
CALL QuickTPut1("Why Squelch Yourself?")
END IF
END IF
END IF
GOTO 59921
CASE "U" REM ** Turn reception of a node back to ON
IF NOT DoTrueChat THEN
IF NodesToSquelch$ <> "" THEN
ZOutTxt$ = "Which node do you wish to UNsquelch (1 -" + STR$(NodesInSystem) + ")" + PRESS.ENTER$
ZSubParm = 1
CALL TGet
IF ZSubParm = -1 THEN
GOTO 59940
END IF
IF ZWasQ > 0 THEN
CALL CheckInt(ZUserIn$(1))
Squelched = INSTR(NodesToSquelch$, MID$(STR$(ZTestedIntValue), 2, 1))
IF Squelched = 1 THEN
IF LEN(NodesToSquelch$) = 1 THEN
NodesToSquelch$ = ""
ELSE
NodesToSquelch$ = MID$(NodesToSquelch$, Squelched + 1)
END IF
ELSEIF Squelched > 1 THEN
NodesToSquelch$ = LEFT$(NodesToSquelch$, Squelched - 1) + _
MID$ (NodesToSquelch$, Squelched + 1)
END IF
IF Squelched > 0 THEN
CALL QuickTPut("Node" + STR$(ZTestedIntValue) + " has been UNsquelched!", 1)
END IF
END IF
END IF
END IF
GOTO 59921
CASE ELSE REM ** Illegal command entered.. show menu..
CALL QuickTPut1("Unknown command <" + LEFT$(ZUserIn$(1), 1) + ">")
GOTO 59922
END SELECT
END IF
EXIT SUB
REM ** user dropped carrier.. return in a way to abort chat mode
59940 ChatSubParm = ZTrue
END SUB
REM ** here is where we set up chat log file.. hopefully with a unique
REM ** filename. The logging code is still quite fallible..
59930 SUB SetUpLogFile STATIC
SHARED SaveToDisk
TempTime$ = TIME$
TempDate$ = DATE$
FileName$ = LEFT$(TempDate$, 2) + _ 'filename format is now:
MID$ (TempDate$, 4, 2) + _ ' mmddhhmm.Css
LEFT$(TempTime$, 2) + _
MID$ (TempTime$, 4, 2) + _
".C" + _
RIGHT$(Temptime$, 2)
CLOSE 2
CALL OpenOutW(FileName$)
CALL QuickTPut1("The SysOp has chosen to record all chats to disk.")
CALL LockUnlock10 (ZTrue)
CALL Update10 (CurrentNodeIndex, ZTrue)
LSET SavingToDisk$ = "Y"
CALL Update10 (CurrentNodeIndex, ZFalse)
CALL LockUnlock10 (ZFalse)
SaveToDisk = ZTrue
END SUB
59990 SUB Field10 STATIC
REM ** all of these variables are SHARED between all subprograms in **
REM ** this module (RCHAT401.BAS) **
FIELD 10, 1 AS ChatActivity$, _
2 AS PagingNode$, _
2 AS PrivateFor$, _
72 AS ChatInput$, _
31 AS ChatName$, _
1 AS InTrueChat$, _
2 AS TrueChatIndex$,_
1 AS SavingToDisk$, _
1 AS BBSActivity$
END SUB
REM ** Lock/Unlock if LockMode = ZTrue, then Lock, else Unlock
59999 SUB LockUnlock10(LockMode) STATIC
ZWasEN$ = ChatFileName$
IF LockMode THEN
ZSubParm = 9
ELSE
ZSubParm = 10
END IF
CALL FileLock
END SUB