386 lines
10 KiB
Plaintext
386 lines
10 KiB
Plaintext
COMPILE FUNCTION Dialog_Label_Check(EntID,Event,Parm1,Parm2,Parm3,Parm4,Parm5)
|
|
|
|
/*
|
|
Commuter module for Dialog_Mat_Scan (Material - Barcode Scan) window
|
|
|
|
10/24/2004 - John C. Henry, J.C. Henry & Co., Inc.
|
|
*/
|
|
|
|
DECLARE SUBROUTINE Set_Property, Set_Status, ErrMsg, Set_Property, Dialog_Box, obj_WO_Mat_Log
|
|
DECLARE SUBROUTINE Btree.Extract, Send_Event, Security_Err_Msg, obj_Appwindow, End_Dialog, Post_Event
|
|
DECLARE SUBROUTINE Send_Message, Print_Cass_Ship_Label, Print_SAP_Cass_Ship_Label, obj_Notes
|
|
DECLARE FUNCTION Get_Property, Get_Status, Popup, Send_Message, Msg, Security_Check, Dialog_Box
|
|
DECLARE FUNCTION Dialog_Box, Utility, obj_WO_Mat
|
|
|
|
|
|
$INSERT MSG_EQUATES
|
|
$INSERT APPCOLORS
|
|
$INSERT LSL_USERS_EQU
|
|
$INSERT SECURITY_RIGHTS_EQU
|
|
$Insert REACT_RUN_EQUATES
|
|
$Insert WM_IN_EQUATES
|
|
$Insert WM_OUT_EQUATES
|
|
$Insert WO_MAT_EQUATES
|
|
$Insert RDS_EQUATES
|
|
$Insert NOTIFICATION_EQUATES
|
|
|
|
EQU CRLF$ TO \0D0A\
|
|
|
|
EQU COL$SMALL_LABEL TO 1
|
|
EQU COL$LARGE_LABEL TO 2
|
|
EQU COL$RESULT TO 3
|
|
|
|
ErrTitle = 'Error in Dialog_Label_Check'
|
|
ErrorMsg = ''
|
|
|
|
Result = ''
|
|
|
|
BEGIN CASE
|
|
CASE EntID = @WINDOW
|
|
BEGIN CASE
|
|
CASE Event = 'CREATE' ; GOSUB Create
|
|
CASE Event = 'CLOSE' ; GOSUB Done
|
|
|
|
END CASE
|
|
|
|
CASE EntID = @WINDOW:'.DONE_BUTTON' AND Event = 'CLICK' ; GOSUB Done
|
|
|
|
CASE EntID = @WINDOW:'.CASS_IDS' AND Event = 'POSCHANGED' ; GOSUB CassIdPC
|
|
|
|
CASE 1
|
|
|
|
ErrorMsg = 'Unknown Parameters ':EntID:' - ':Event:' passed to commuter'
|
|
ErrMsg(ErrorMsg)
|
|
|
|
END CASE
|
|
|
|
IF ErrorMsg NE '' THEN
|
|
ErrMsg(ErrTitle:@SVM:ErrorMsg)
|
|
END
|
|
|
|
RETURN Result
|
|
|
|
|
|
* * * * * * *
|
|
Create:
|
|
* * * * * * *
|
|
|
|
obj_Appwindow('Create',@WINDOW)
|
|
|
|
GOSUB Refresh
|
|
|
|
RETURN
|
|
|
|
|
|
* * * * * * *
|
|
Refresh:
|
|
* * * * * * *
|
|
|
|
WindowLabel = Get_Property(@WINDOW:'.WINDOW_LABEL','TEXT')
|
|
|
|
RETURN
|
|
|
|
|
|
|
|
* * * * * * * *
|
|
Done:
|
|
* * * * * * * *
|
|
|
|
End_Dialog(@WINDOW,'')
|
|
|
|
RETURN
|
|
|
|
|
|
|
|
* * * * * * * *
|
|
CassIdPC:
|
|
* * * * * * * *
|
|
|
|
CtrlEntID = @WINDOW:'.CASS_IDS'
|
|
|
|
PrevSelPos = Get_Property(CtrlEntId,"PREVSELPOS")
|
|
PrevCol = PrevSelPos<1>
|
|
PrevRow = PrevSelPos<2>
|
|
|
|
CurrPos = Get_Property(CtrlEntId,'SELPOS')
|
|
CurrCol = CurrPos<1>
|
|
CurrRow = CurrPos<2>
|
|
|
|
ListData = Get_Property(CtrlEntId,'LIST')
|
|
ArrayData = Get_Property(CtrlEntId,'ARRAY')
|
|
|
|
IF ListData<CurrRow,CurrCol> = '' THEN
|
|
|
|
ColPointer = CurrCol
|
|
LinePointer = CurrRow
|
|
ColCnt = 2
|
|
|
|
* Find the first non-empty cell
|
|
|
|
LOOP
|
|
Test = ListData<LinePointer,(ColPointer) >
|
|
UNTIL Test NE '' OR (LinePointer = 0 AND ColPointer = 1)
|
|
ColPointer -= 1
|
|
IF ColPointer = 0 THEN
|
|
ColPointer = ColCnt
|
|
LinePointer -= 1
|
|
END
|
|
REPEAT
|
|
|
|
* Move one past the non empty cell
|
|
|
|
BEGIN CASE
|
|
CASE LinePointer = 0
|
|
* Empty Table
|
|
LinePointer = 1
|
|
CoilPointer = 1
|
|
|
|
CASE ColPointer = ColCnt
|
|
LinePointer += 1
|
|
ColPointer = 1
|
|
|
|
CASE 1
|
|
ColPointer += 1
|
|
|
|
END CASE
|
|
Set_Property(CtrlEntId,"SELPOS",ColPointer:@FM:LinePointer)
|
|
END
|
|
|
|
IF ListData<PrevRow,PrevCol> NE '' AND PrevCol = COL$SMALL_LABEL THEN
|
|
|
|
CassID = TRIM(ListData<PrevRow,PrevCol>)
|
|
|
|
IF CassID[1,1] EQ 'Q' then
|
|
Set_Property(CtrlEntId,"CELLPOS",'',PrevSelPos)
|
|
Set_Property(CtrlEntId,"SELPOS",PrevSelPos)
|
|
end else IF CassID[1,2] EQ '1T' THEN
|
|
Swap '1T' with '' in CassID
|
|
Set_Property(CtrlEntId,"CELLPOS",CassID,PrevSelPos)
|
|
END
|
|
|
|
If CurrRow > 1 THEN
|
|
* Check for data already in the list (repeat scan)
|
|
|
|
TestArray = ArrayData<COL$SMALL_LABEL> ;* First Column
|
|
TestArray<COL$SMALL_LABEL,PrevRow> = '' ;* Remove the label just scanned
|
|
LOCATE CassID IN TestArray USING @VM SETTING Pos THEN
|
|
Set_Property(CtrlEntId,"SELPOS",PrevSelPos)
|
|
Set_Property(CtrlEntID,'INVALUE','',PrevSelPos) ;* Label Data already scanned
|
|
RETURN
|
|
END
|
|
End
|
|
|
|
BEGIN CASE
|
|
CASE CassID[1,1] = 'I'
|
|
* WM_IN table
|
|
CassID = CassID[2,99] ;*
|
|
WOMatKey = FIELD(CassID,'.',1):'*':FIELD(CassID,'.',3)
|
|
Set_Property(CtrlEntID,'INVALUE',CassID,PrevSelPos)
|
|
CASE CassID[1,1] = 'O'
|
|
* WM_OUT table
|
|
CassID = CassID[2,99]
|
|
WONo = CassID[1, 'F.']
|
|
CassNo = CassID[-1, 'B.']
|
|
WOMatKey = WONo:'*':CassNo
|
|
Set_Property(CtrlEntID,'INVALUE',CassID,PrevSelPos)
|
|
CASE INDEX(CassID,'.',1) AND NOT(INDEX(CassID,'.',2))
|
|
* This is a WO_MAT format label
|
|
Convert '.' To '*' In CassID
|
|
WOMatKey = CassID
|
|
CASE INDEX(CassID,'.',2)
|
|
* EpiPRO material indeterminate direction
|
|
WOMatKey = FIELD(CassID,'.',1):'*':Field(CassID,'.',3)
|
|
CASE 1
|
|
ReactRunRec = XLATE('REACT_RUN',CassID,'','X')
|
|
IF ReactRunRec = '' THEN
|
|
RDSRec = XLATE('RDS',CassID,'','X')
|
|
TestWO = RDSRec<RDS_WO$>
|
|
CassNo = RDSRec<RDS_CASS_NO$>
|
|
END ELSE
|
|
TestWO = ReactRunRec<REACT_RUN_WO_NO$>
|
|
CassNo = ReactRunRec<REACT_RUN_CASS_NO$>
|
|
End
|
|
|
|
WOMatKey = TestWO:'*':CassNo
|
|
|
|
END CASE
|
|
|
|
WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
|
|
|
|
IF WOMatRec = '' THEN
|
|
Set_Property(CtrlEntId,"SELPOS",PrevSelPos)
|
|
Set_Property(CtrlEntID,'INVALUE','',PrevSelPos) ;* No corresponding data record found for label scanned bad read or wrong thing scanned
|
|
RETURN
|
|
END
|
|
|
|
End
|
|
|
|
|
|
IF ListData<PrevRow,PrevCol> NE '' AND PrevCol = COL$LARGE_LABEL Then
|
|
|
|
CassID = TRIM(ListData<PrevRow,PrevCol>)
|
|
CheckID = TRIM(ListData<PrevRow,COL$SMALL_LABEL>)
|
|
BatchID = Field(CassID,' ',2)
|
|
|
|
If BatchID NE '' Then
|
|
|
|
Open 'DICT.WO_MAT' To DictWOMat Then
|
|
|
|
Search = 'SAP_BATCH_NO':@VM:BatchID:@FM
|
|
Flag = ''
|
|
ScanWOMatKey = ''
|
|
|
|
Set_Status(0)
|
|
Btree.Extract(Search,'WO_MAT',DictWOMat,ScanWOMatKey,'',Flag)
|
|
If Get_Status(errCode) Then
|
|
ErrMsg(errCode)
|
|
End
|
|
|
|
If ScanWOMatKey NE '' Then
|
|
CassID = Xlate('WO_MAT',ScanWOMatKey,'CASS_ID_SAP','X')
|
|
If CheckID Matches "0N'.'1N'.'0N" THEN
|
|
WMOKey = Xlate('WO_MAT',ScanWOMatKey,WO_MAT_WMO_KEY$,'X')
|
|
Convert '*' To '.' In WMOKey
|
|
CassID = WMOKey
|
|
End
|
|
Set_Property(CtrlEntID,'INVALUE',CassID,PrevSelPos)
|
|
End Else
|
|
Set_Property(CtrlEntId,"SELPOS",PrevSelPos)
|
|
Set_Property(CtrlEntID,'INVALUE','',PrevSelPos) ;* No corresponding data record found for label scanned bad read or wrong thing scanned
|
|
Return
|
|
RETURN
|
|
END
|
|
End ;* End of DictWOMat open
|
|
End Else
|
|
Set_Property(CtrlEntId,"SELPOS",PrevSelPos)
|
|
Set_Property(CtrlEntID,'INVALUE','',PrevSelPos) ;* Field other than the combined label scanned
|
|
RETURN
|
|
END;* End of check for null BatchID
|
|
|
|
If CurrRow > 1 THEN
|
|
|
|
* Check for data already in the list (repeat scan)
|
|
|
|
TestArray = ArrayData<COL$LARGE_LABEL>
|
|
TestArray<1,PrevRow> = '' ;* Remove the label just scanned
|
|
LOCATE CassID IN TestArray USING @VM SETTING Pos THEN
|
|
Set_Property(CtrlEntId,"SELPOS",PrevSelPos)
|
|
Set_Property(CtrlEntID,'INVALUE','',PrevSelPos) ;* Label Data already scanned
|
|
RETURN
|
|
END
|
|
End
|
|
|
|
* Setup parameters to WO_Mat_Log method *
|
|
|
|
CurrDTM = OCONV(Date(),'D2/'):' ':OCONV(Time(),'MTS')
|
|
UserID = @USER4
|
|
|
|
LogFile = 'WO_MAT' ;* Changed so all scans are logged in the WO_MAT table 12/3/2006
|
|
Action = 'PSVER'
|
|
WHCd = 'SR'
|
|
LocCd = 'VER'
|
|
|
|
If CassID NE CheckID Then
|
|
void = Utility('BEEP')
|
|
Set_Property(CtrlEntID,'CELLPOS','*Mismatch*',3:@FM:PrevRow) ;* Load Current Location
|
|
stat = Send_Message(CtrlEntID,'COLOR_BY_POS',0,PrevRow,RED$)
|
|
|
|
OK = Msg(@WINDOW,'','LABEL_MISMATCH')
|
|
|
|
* Inform Quality Insurance that a mismatch has occurred *
|
|
|
|
Recipients = ''
|
|
|
|
OtherRecipients = XLATE('NOTIFICATION','LABEL_CHECK',NOTIFICATION_USER_ID$,'X') ;* Added 10/03/2005 JCH - J.C. Henry & Co., Inc Changed from LABEL_MISMATCH by dkk 11/6/15
|
|
|
|
FOR N = 1 TO COUNT(OtherRecipients,@VM) + (OtherRecipients NE '')
|
|
OtherRecip = OtherRecipients<1,N>
|
|
LOCATE OtherRecip IN Recipients USING @VM SETTING Pos ELSE
|
|
Recipients = INSERT(Recipients,1,Pos,0,OtherRecip)
|
|
END
|
|
NEXT N
|
|
|
|
SentFrom = @USER4
|
|
Subject = 'Preship Label Check Mismatch'
|
|
Message = 'Cassette ':QUOTE(CheckID):' has incorrect 4 inch label from Cass ID ':QUOTE(CassID)' applied.'
|
|
AttachWindow = ''
|
|
AttachKey = ''
|
|
SendToGroup = ''
|
|
|
|
Parms = Recipients:@RM:SentFrom:@RM:Subject:@RM:Message:@RM:AttachWindow:@RM:AttachKey:@RM:SendToGroup
|
|
obj_Notes('Create',Parms)
|
|
|
|
* Reprint correct 4" labels *
|
|
If Count(CheckID, '.') then
|
|
// EpiPro Silicon or GaN
|
|
IF CheckID[1,1] = 'O' THEN CheckID[1,1] = ''
|
|
IF CheckID[1,1] = 'I' Then CheckID[1,1] = ''
|
|
WONo = CheckID[1, 'F.']
|
|
StepNo = 1
|
|
CassNo = CheckID[-1, 'B.']
|
|
RDSNo = ''
|
|
end else
|
|
// Non-EpiPro Silicon
|
|
RDSNo = CheckID
|
|
ReactRunRec = XLATE('REACT_RUN',RDSNo,'','X')
|
|
WONo = ReactRunRec<REACT_RUN_WO_NO$>
|
|
StepNo = ReactRunRec<REACT_RUN_WO_STEP$>
|
|
CassNo = ReactRunRec<REACT_RUN_CASS_NO$>
|
|
end
|
|
|
|
Print_SAP_Cass_Ship_Label(WONo,StepNo,CassNo,RDSNo)
|
|
|
|
Set_Status(0)
|
|
|
|
obj_WO_Mat_Log('Create',LogFile:@RM:CurrDTM:@RM:Action:@RM:WhCd:@RM:LocCd:@RM:WONo:@RM:CassNo:@RM:UserID:@RM:'Mismatch')
|
|
|
|
IF Get_Status(errCode) THEN
|
|
Errmsg(errCode)
|
|
End
|
|
|
|
Goto Done ;* Stop afer a mistmatch - no more scans allowed. Change to allow the net line item scan. -dkk 6/14/16
|
|
|
|
End Else
|
|
|
|
Set_Property(CtrlEntID,'CELLPOS','OK',3:@FM:PrevRow)
|
|
stat = Send_Message(CtrlEntID,'COLOR_BY_POS',0,PrevRow,GREEN$)
|
|
|
|
If Count(CheckID, '.') then
|
|
// EpiPro Silicon or GaN
|
|
IF CheckID[1,1] = 'O' THEN CheckID[1,1] = ''
|
|
IF CheckID[1,1] = 'I' Then CheckID[1,1] = ''
|
|
WONo = CheckID[1, 'F.']
|
|
StepNo = 1
|
|
CassNo = CheckID[-1, 'B.']
|
|
RDSNo = ''
|
|
end else
|
|
// Non-EpiPro Silicon
|
|
RDSNo = CheckID
|
|
ReactRunRec = XLATE('REACT_RUN',RDSNo,'','X')
|
|
WONo = ReactRunRec<REACT_RUN_WO_NO$>
|
|
StepNo = ReactRunRec<REACT_RUN_WO_STEP$>
|
|
CassNo = ReactRunRec<REACT_RUN_CASS_NO$>
|
|
end
|
|
|
|
* Add transaction to Posting system to time-stamp WO_MAT record
|
|
|
|
Set_Status(0)
|
|
|
|
obj_WO_Mat_Log('Create',LogFile:@RM:CurrDTM:@RM:Action:@RM:WhCd:@RM:LocCd:@RM:WONo:@RM:CassNo:@RM:UserID:@RM:'Match')
|
|
|
|
IF Get_Status(errCode) THEN
|
|
Errmsg(errCode)
|
|
End
|
|
|
|
End ;* End of check for matching CassID's
|
|
|
|
|
|
End ;* End of check for Large Label
|
|
|
|
GOSUB Refresh
|
|
|
|
RETURN
|
|
|
|
|
|
|