COMPILE FUNCTION obj_Notes(Method,Parms) /* Methods for Notes table 07/11/2004 JCH - Initial Coding Properties: Methods: Inbox(UserName) ;* Displays annoying message box that the user has new notes (was check_notes() function) Create() ;* Creates new Note RebuildPointers(UserName) ;* Rebuilds NOTE_PTRS record if it gets clobbered ForwardEMail ;* Checks EMAIL_BOX and sends any messages via Outlook eMail */ DECLARE FUNCTION Get_Status, Msg, Utility, obj_Tables, NextKey, SRPSendMail, obj_Calendar, Database_Services, SRP_Send_Mail DECLARE SUBROUTINE Set_Status, Msg, obj_Tables, RList, ErrMsg, obj_Notes_Sent, Btree.Extract, Send_Info, obj_Notes $INSERT MSG_EQUATES $INSERT NOTES_EQU $INSERT NOTE_PTRS_EQU $INSERT LSL_USERS_EQU $INSERT EMAIL_BOX_EQUATES $INSERT LOGICAL $INSERT SRPMail_Inserts EQU TARGET_ACTIVELIST$ TO 5 ErrTitle = 'Error in Stored Procedure "obj_Notes"' ErrorMsg = '' IF NOT(ASSIGNED(Method)) THEN ErrorMsg = 'Unassigned parameter "Method" passed to subroutine' IF NOT(ASSIGNED(Parms)) THEN Parms = '' IF ErrorMsg NE '' THEN Set_Status(-1,ErrTitle:@SVM:ErrorMsg) RETURN '' END Result = '' BEGIN CASE CASE Method = 'Inbox' ; GOSUB Inbox CASE Method = 'Create' ; GOSUB Create CASE Method = 'Rebuild' ; GOSUB Rebuild CASE Method = 'AllActiveUsers' ; GOSUB AllActiveUsers CASE Method = 'PostEMail' ; GOSUB PostEMail CASE Method = 'ForwardEMail' ; GOSUB ForwardEMail CASE Method = 'EMail' ; GOSUB EMail CASE 1 ErrorMsg = 'Unknown Method ':QUOTE(Method):' passed to object.' END CASE IF ErrorMsg NE '' THEN Set_Status(-1,ErrTitle:@SVM:ErrorMsg) RETURN '' END RETURN Result * * * * * * * Inbox: * * * * * * * UserName = Parms[1,@RM] IF UserName = '' THEN UserName = @USER4 IF UserName = '' THEN UserName = @USERNAME IF XLATE( 'NOTE_PTRS', UserName, 'NEW_MESSAGES', 'X' ) THEN NotePtrRec = XLATE( 'NOTE_PTRS', UserName, '', 'X' ) IF NotePtrRec = 'Yes' THEN * the top one is new MsgInfo = '' MsgInfo = '!' Mtext = 'You have a new message from ':NotePtrRec:'.' MsgInfo = MText MsgInfo = -2 MsgInfo = -2 Msg( @WINDOW, MsgInfo ) END END RETURN * * * * * * * Create: * * * * * * * Recipients = Parms[1,@RM] SentFrom = Parms[COL2()+1,@RM] Subject = Parms[COL2()+1,@RM] Message = Parms[COL2()+1,@RM] AttachWindow = Parms[COL2()+1,@RM] AttachKeys = Parms[COL2()+1,@RM] SendToGroup = Parms[COL2()+1,@RM] IF NOT(ASSIGNED(Recipients)) THEN ErrorMsg = 'Unassigned Parameter "Recipients" passed to object. (':Method:')' IF NOT(ASSIGNED(SentFrom)) THEN ErrorMsg = 'Unassigned Parameter "SentFrom" passed to object. (':Method:')' IF NOT(ASSIGNED(Subject)) THEN ErrorMsg = 'Unassigned Parameter "Subject" passed to object. (':Method:')' IF NOT(ASSIGNED(Message)) THEN ErrorMsg = 'Unassigned Parameter "Message" passed to object. (':Method:')' IF NOT(ASSIGNED(AttachWindow)) THEN AttachWindow = '' IF NOT(ASSIGNED(AttachKeys)) THEN AttachKeys = '' IF NOT(ASSIGNED(SendToGroup)) THEN SendToGroup = '' IF ErrorMsg NE '' THEN RETURN thisRecipients = '' RecipCnt = 0 FOR I = 1 TO COUNT(Recipients,@VM) + (Recipients NE '') Recipient = Recipients<1,I> IF Recipient NE '' THEN LOCATE Recipient IN thisRecipients USING @VM SETTING Pos ELSE thisRecipients = INSERT(thisRecipients,1,Pos,0,Recipient) RecipCnt += 1 END END NEXT I NextNoteKey = NextKey('NOTES') NoteRec = '' NoteRec = 'I' NoteRec = Date() NoteRec = Time() NoteRec = thisRecipients NoteRec = SentFrom NoteRec = Message NoteRec = @USER4 NoteRec = Subject NoteRec = AttachWindow NoteRec = AttachKeys NoteRec = SendToGroup OtParms = 'NOTES':@RM:NextNoteKey:@RM:@RM:NoteRec obj_Tables('WriteRec',OtParms) ;* Writes the Note record to disk CurrDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTHS') RecipientsText = thisRecipients SWAP @VM WITH ', ' IN RecipientsText FOR I = 1 TO RecipCnt thisRecipient = thisRecipients<1,I> obj_Notes_Sent('Create',thisRecipient:@RM:NextNoteKey:@RM:CurrDTM) ;* Add to Notes Sent buffer table UserRec = XLATE('LSL_USERS',thisRecipient,'','X') FwdFlag = UserRec eMailAddr = UserRec IF FwdFlag = 1 AND eMailAddr NE '' THEN Text = '' Text<-1> = 'OI eMail From: ':OCONV(SentFrom,'[XLATE_CONV,LSL_USERS*FIRST_LAST]'):' at ':CurrDTM Text<-1> = '' Text<-1> = 'Recipients: ':RecipientsText Text<-1> = '' Text<-1> = 'Subject: ':Subject Text<-1> = '' Text<-1> = 'Message: ' Text<-1> = '' Text<-1> = Message Text<-1> = '' IF AttachWindow NE '' THEN Text<-1> = '' Text<-1> = 'Attached Window: ':AttachWindow END IF AttachKeys NE '' THEN Text<-1> = '' Text<-1> = 'Record Key: ':AttachKeys END IF SendToGroup NE '' THEN Text<-1> = '' Text<-1> = 'Sent to Group: ':SendToGroup END HeaderText = Text<1> CONVERT \00\ TO ',' IN Text SWAP @VM WITH ':@VM:' IN Text SWAP @FM WITH CHAR(13):CHAR(10) IN Text SWAP @TM WITH CHAR(13):CHAR(10) IN Text eMailBoxKey = NextNoteKey:'*':thisRecipient eMailBoxRec = '' eMailBoxRec = eMailAddr eMailBoxRec = Text eMailBoxRec = HeaderText eMailBoxRec = SentFrom ebParms = 'EMAIL_BOX':@RM:eMailBoxKey:@RM:@RM:eMailBoxRec obj_Tables('WriteRec',ebParms) END ;* End of check for forwarding flag NEXT I RETURN * * * * * * * Rebuild: * * * * * * * thisRecipient = Parms[1,@RM] IF thisRecipient = '' THEN thisRecipient = @USER4 IF thisRecipient = '' THEN thisRecipient = @USERNAME SelectSent = 'SELECT NOTES WITH SEND_TO "':thisRecipient:'" AND WITH ENTRY_DATE GE ':QUOTE(OCONV(Date()-90,'D4/')) RList(SelectSent,'NOTES',TARGET_ACTIVELIST$,'','') IF Get_Status(errCode) THEN ErrMsg(errCode) END NoteIDs = '' Done = 0 LOOP READNEXT NoteID ELSE Done = 1 UNTIL Done LOCATE NoteID IN NoteIDs BY 'DR' USING @FM SETTING Pos ELSE NoteIDs = INSERT(NoteIDs,Pos,0,0,NoteID) END REPEAT OtParms = 'NOTE_PTRS':@RM:thisRecipient obj_Tables('LockRec',OtParms) ;* If not found then returns null, otherwise reads and sets the lock NPRec = '' FOR I = 1 TO COUNT(NoteIDs,@FM) + (NoteIDs NE '') NoteID = NoteIDs NoteRec = XLATE('NOTES',NoteID,'','X') Subject = NoteRec SentFrom = NoteRec NoteDt = OCONV(NoteRec,'D2/') NoteTime = OCONV(NoteRec,'MTH') AttachWindow = NoteRec AttachKeys = NoteRec IF AttachWindow NE '' AND AttachKeys NE '' THEN Attachment = 'Yes' END ELSE Attachment = 'No' END LOCATE NoteID IN NPRec BY 'DR' USING @VM SETTING Pos ELSE NPRec = INSERT( NPRec, note_ptrs_subject$, Pos, 0, Subject ) ;* Add the subject ConvSentFrom = OCONV(SentFrom,'[XLATE_CONV,LSL_USERS*FIRST_LAST]') IF ConvSentFrom NE '' THEN SentFrom = ConvSentFrom NPRec = INSERT( NPRec, note_ptrs_from$, Pos, 0, SentFrom ) NPRec = INSERT( NPRec, note_ptrs_date$, Pos, 0, NoteDt ) NPRec = INSERT( NPRec, note_ptrs_time$, Pos, 0, NoteTime ) NPRec = INSERT( NPRec, note_ptrs_new$, Pos, 0, 'Yes' ) NPRec = INSERT( NPRec, note_ptrs_note_ids$, Pos, 0, NoteID ) NPRec = INSERT( NPRec, note_ptrs_attachment$, Pos, 0, Attachment ) NPRec = INSERT( NPRec, note_ptrs_archived$, Pos, 0, '0') END UNTIL LEN(NPRec) > 128000 NEXT I OtParms = FIELDSTORE(OtParms,@RM,4,0,NPRec) obj_Tables('WriteRec',OtParms) RETURN * * * * * * * AllActiveUsers: * * * * * * * OPEN 'DICT.LSL_USERS' TO DictVar ELSE RETURN SearchString = 'ACTIVE':@VM:'1':@FM TableName = 'LSL_USERS' Option = '' Flag = '' Btree.Extract(SearchString, TableName, DictVar, AllUserList, Option, Flag ) IF Get_Status(errCode) THEN RETURN Result = AllUserList RETURN * * * * * * * PostEMail: * * * * * * * NoteKey = Parms[1,@RM] IF NoteKey = '' THEN RETURN NoteRec = XLATE('NOTES',NoteKey,'','X') SentFrom = NoteRec Recipients = NoteRec Subject = NoteRec Message = NoteRec AttachWindow = NoteRec AttachKeys = NoteRec SendToGroup = NoteRec CurrDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTHS') RecipientsText = Recipients SWAP @VM WITH ', ' IN RecipientsText RecipCnt = COUNT(Recipients,@VM) + (Recipients NE '') FOR I = 1 TO RecipCnt Recipient = Recipients<1,I> UserRec = XLATE('LSL_USERS',Recipient,'','X') FwdFlag = UserRec eMailAddr = UserRec IF FwdFlag = 1 AND eMailAddr NE '' THEN Text = '' Text<-1> = 'OI eMail from: ':OCONV(SentFrom,'[XLATE_CONV,LSL_USERS*FIRST_LAST]'):' at ':CurrDTM Text<-1> = '' Text<-1> = 'Recipients: ':RecipientsText Text<-1> = '' Text<-1> = 'Subject: ':Subject Text<-1> = '' Text<-1> = 'Message: ' Text<-1> = '' Text<-1> = Message Text<-1> = '' IF AttachWindow NE '' THEN Text<-1> = '' Text<-1> = 'Attached Window: ':AttachWindow END IF AttachKeys NE '' THEN Text<-1> = '' Text<-1> = 'Record Key: ':AttachKeys END IF SendToGroup NE '' THEN Text<-1> = '' Text<-1> = 'Sent to Group: ':SendToGroup END HeaderText = TEXT<1> CONVERT \00\ TO ',' IN Text SWAP @VM WITH ':@VM:' IN Text SWAP @FM WITH CHAR(13):CHAR(10) IN Text SWAP @TM WITH CHAR(13):CHAR(10) IN Text eMailBoxKey = NoteKey:'*':Recipient eMailBoxRec = '' eMailBoxRec = eMailAddr eMailBoxRec = Text eMailBoxRec = HeaderText eMailBoxRec = SentFrom ebParms = 'EMAIL_BOX':@RM:eMailBoxKey:@RM:@RM:eMailBoxRec obj_Tables('WriteRec',ebParms) IF Get_Status(errCode) THEN ErrMsg(errCode) END END ;* End of check for forwarding flag NEXT I RETURN * * * * * * * ForwardEMail: * * * * * * * hSysLists = Database_Services('GetTableHandle', 'SYSLISTS') ServiceKeyID = 'Obj_Notes*ForwardEMail' Lock hSysLists, ServiceKeyID then rv = Set_Status(0) RList('SELECT EMAIL_BOX BY NOTE_KEY', 5, '', '', '') Done = 0 LOOP ReadNext eMailBoxKey else Done = 1 UNTIL Done mbParms = 'EMAIL_BOX':@RM:eMailBoxKey eMailBoxRec = obj_Tables('ReadRec',mbParms) If @File_Error EQ '' then eMailAddr = eMailBoxRec eMailText = eMailBoxRec eMailHeader = eMailBoxRec OISentFrom = eMailBoxRec ConfigFile = '' ConfigFile<1> = SendUsing_Port$ ConfigFile<2> = '' ConfigFile<3> = 25 ;* Server port ConfigFile<4> = 'smtp.intra.infineon.com' ;* Infinfeon Mail Server for internal recipents ConfigFile<5> = Yes$ ;* Authenticate ConfigFile<6> = 'oinotify@infineon.com' ;* Username (IFX) ConfigFile<7> = 'oinotify1' ;* Password ConfigFile<8> = No$ ;* Use SSL SentFrom = 'oinotify@infineon.com' SendTo = eMailAddr IF OISentFrom = 'OI_ERROR' THEN SendTo := XLATE('SEC_GROUPS', 'OI_ADMIN', 'USER', 'X') Message = '' Message<1> = eMailHeader ; // Subject Message<2> = SentFrom ; // From (email address) Message<3> = SendTo ; // Send to (email address) Message<5> = '' ; // Blind Carbon Copy (email address) Message<6> = '' ; // Reply To (email address) Message<7> = 'TEXT' ; // Content Type (TEXT or HTML) Message<8> = eMailText ; // Content / Body Message<9> = '' ; // Attachment(s) (path to file name(s)) MsgSent = SRP_Send_Mail(Message, ConfigFile) IF MsgSent = 1 THEN * obj_Tables('DeleteRec',mbParms) END ELSE Set_Status(0) obj_Tables('UnlockRec',mbParms) Recipients = XLATE('NOTIFICATION', 'FI_SUPPORT', 'USER_ID', 'X') SentFrom = 'FI Support' Subject = 'OpenInsight eMail Server Error' Message = 'Unable to send email.' : \0D0A\ Message := 'Sent From: ' : SentFrom : \0D0A\ Message := 'Send To: ' : SendTo : \0D0A\ Message := 'Original Subject: ' : eMailHeader : \0D0A\ Message := 'Original Message: ' : eMailText : \0D0A\ Message := '========================================' : \0D0A\ Message := 'Error Message: ' : MsgSent AttachWindow = '' AttachKey = '' SendToGroup = '' Parms = Recipients:@RM:SentFrom:@RM:Subject:@RM:Message:@RM:AttachWindow:@RM:AttachKey:@RM:SendToGroup obj_Notes('Create',Parms) END obj_Tables('DeleteRec',mbParms) end REPEAT Unlock hSysLists, ServiceKeyID else Null end RETURN * * * * * * * EMail: * * * * * * * * Direct outside eMail without creating a NOTES record Recipients = Parms[1,@RM] SentFrom = Parms[COL2()+1,@RM] Subject = Parms[COL2()+1,@RM] Message = Parms[COL2()+1,@RM] IF NOT(ASSIGNED(Recipients)) THEN ErrorMsg = 'Unassigned Parameter "Recipients" passed to object. (':Method:')' IF NOT(ASSIGNED(SentFrom)) THEN ErrorMsg = 'Unassigned Parameter "SentFrom" passed to object. (':Method:')' IF NOT(ASSIGNED(Subject)) THEN ErrorMsg = 'Unassigned Parameter "Subject" passed to object. (':Method:')' IF NOT(ASSIGNED(Message)) THEN ErrorMsg = 'Unassigned Parameter "Message" passed to object. (':Method:')' IF ErrorMsg NE '' THEN RETURN thisRecipients = '' RecipCnt = 0 FOR I = 1 TO COUNT(Recipients,@VM) + (Recipients NE '') Recipient = Recipients<1,I> IF Recipient NE '' THEN LOCATE Recipient IN thisRecipients USING @VM SETTING Pos ELSE thisRecipients = INSERT(thisRecipients,1,Pos,0,Recipient) RecipCnt += 1 END END NEXT I RecipientsText = OCONV(thisRecipients,'[XLATE_CONV,LSL_USERS*FIRST_LAST]') SWAP @VM WITH ', ' IN RecipientsText CurrDTM = obj_Calendar('CurrDTM') FOR I = 1 TO RecipCnt thisRecipient = thisRecipients<1,I> UserRec = XLATE('LSL_USERS',thisRecipient,'','X') eMailAddr = UserRec IF eMailAddr NE '' THEN Text = '' Text<-1> = 'OI eMail from: ':OCONV(SentFrom,'[XLATE_CONV,LSL_USERS*FIRST_LAST]'):' at ':CurrDTM Text<-1> = '' Text<-1> = 'Recipients: ':RecipientsText Text<-1> = '' Text<-1> = 'Subject: ':Subject Text<-1> = '' Text<-1> = 'Message: ' Text<-1> = '' Text<-1> = Message Text<-1> = '' HeaderText = TEXT<1> CONVERT \00\ TO ',' IN Text SWAP @VM WITH ':@VM:' IN Text SWAP @FM WITH CHAR(13):CHAR(10) IN Text SWAP @TM WITH CHAR(13):CHAR(10) IN Text ConfigFile = '' ConfigFile<1> = SendUsing_Port$ ConfigFile<2> = '' ConfigFile<3> = 25 ;* Server port *ConfigFile<4> = 'appmail.eu.infineon.com' ;* IFX Mail server ConfigFile<4> = 'mailrelay-external.infineon.com' ConfigFile<5> = Yes$ ;* Authenticate ConfigFile<6> = 'oinotify@infineon.com' ;* Username ConfigFile<7> = 'oinotify1' ;* Password ConfigFile<8> = No$ ;* Use SSL SentFrom = 'oinotify@infineon.com' SendTo = eMailAddr Message = '' Message<1> = HeaderText ; * Subject Message<2> = SentFrom ; * From (email address) Message<3> = eMailAddr ; * Send to (email address) Message<5> = '' ; * Blind Carbon Copy (email address) Message<6> = '' ; * Reply To (email address) Message<7> = 'TEXT' ; * Content Type (TEXT or HTML) Message<8> = Text ; * Content / Body Message<9> = '' ; * Attachment(s) (path to file name(s)) MsgSent = SRPSendMail(Message, ConfigFile) END NEXT I ;* End of Recipient Loop RETURN