added LSL2 stored procedures
This commit is contained in:
294
LSL2/STPROC/DIALOG_SCHED_WO.txt
Normal file
294
LSL2/STPROC/DIALOG_SCHED_WO.txt
Normal file
@ -0,0 +1,294 @@
|
||||
COMPILE FUNCTION Dialog_Sched_WO(EntID,Event,Parm1,Parm2,Parm3,Parm4,Parm5)
|
||||
|
||||
/*
|
||||
Commuter module for DIALOG_SCHED_WO window
|
||||
|
||||
07/14/2014 - John C. Henry, J.C. Henry & Co., Inc.
|
||||
*/
|
||||
|
||||
DECLARE SUBROUTINE Set_Property, ErrMsg, obj_Appwindow, Btree.Extract, Send_Event, Send_Message, RList
|
||||
DECLARE SUBROUTINE End_Dialog
|
||||
DECLARE FUNCTION Get_Property, Send_Message, NextKey, Popup, obj_Calendar, Printer_Select
|
||||
DECLARE FUNCTION Set_Printer, obj_Install, obj_Popup, Send_Message, Msg
|
||||
|
||||
$INSERT APPCOLORS
|
||||
$INSERT SCHED_DET_EQUATES
|
||||
$INSERT REACTOR_EQUATES
|
||||
$INSERT PROD_SPEC_EQUATES
|
||||
$INSERT RLIST_EQUATES
|
||||
$INSERT RTI_STYLE_EQUATES
|
||||
$INSERT MSG_EQUATES
|
||||
$INSERT POPUP_EQUATES
|
||||
|
||||
EQU CRLF$ TO \0D0A\
|
||||
|
||||
EQU COL$REACT_NO TO 1
|
||||
EQU COL$TYPE TO 2
|
||||
EQU COL$START_DATE TO 3
|
||||
EQU COL$END_DATE TO 4
|
||||
|
||||
|
||||
|
||||
ErrTitle = 'Error in Dialog_Sched'
|
||||
ErrorMsg = ''
|
||||
|
||||
Result = ''
|
||||
|
||||
BEGIN CASE
|
||||
CASE EntID = @WINDOW
|
||||
BEGIN CASE
|
||||
CASE Event = 'CREATE' ; GOSUB Create
|
||||
CASE Event = 'CLOSE' ; GOSUB Cancel
|
||||
END CASE
|
||||
|
||||
CASE EntID = @WINDOW:'.LU_WO_NO' AND Event = 'CLICK' ; GOSUB LUWONo
|
||||
CASE EntID = @WINDOW:'.SCHED_BUTTON' AND Event = 'CLICK' ; GOSUB Schedule
|
||||
CASE EntID = @WINDOW:'.CANCEL_BUTTON' AND Event = 'CLICK' ; GOSUB Cancel
|
||||
|
||||
CASE EntID = @WINDOW:'.REACT_NO'
|
||||
BEGIN CASE
|
||||
CASE Event = 'DBLCLK' ; GOSUB ReactDC
|
||||
CASE Event = 'POSCHANGED' ; GOSUB ReactPC
|
||||
CASE Event = 'OPTIONS' ; GOSUB ReactOptions
|
||||
END CASE
|
||||
|
||||
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)
|
||||
|
||||
CtrlEntID = @WINDOW:'.REACT_NO'
|
||||
|
||||
col1Style = Send_Message(CtrlEntID,'STYLE_BY_POS',COL$REACT_NO,0)
|
||||
col1Style = bitor(col1Style,DTCS_OPTIONSBUTTON$)
|
||||
col1Style = Send_Message(CtrlEntID,'STYLE_BY_POS',COL$REACT_NO,0,col1Style)
|
||||
|
||||
col3Style = Send_Message(CtrlEntID,'STYLE_BY_POS',COL$START_DATE,0)
|
||||
col3Style = bitor(col3Style,DTCS_OPTIONSBUTTON$)
|
||||
col3Style = Send_Message(CtrlEntID,'STYLE_BY_POS',COL$START_DATE,0,col3Style)
|
||||
|
||||
col4Style = Send_Message(CtrlEntID,'STYLE_BY_POS',COL$END_DATE,0)
|
||||
col4Style = bitor(col4Style,DTCS_OPTIONSBUTTON$)
|
||||
col4Style = Send_Message(CtrlEntID,'STYLE_BY_POS',COL$END_DATE,0,col4Style)
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Refresh:
|
||||
* * * * * * *
|
||||
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
LUWONo:
|
||||
* * * * * * *
|
||||
|
||||
* Lookup unscheduled WO's
|
||||
|
||||
Def = ""
|
||||
Def<MTEXT$> = "Selecting Uncheduled Work Order Steps..."
|
||||
Def<MTYPE$> = "U"
|
||||
|
||||
MsgUp = Msg(@window, Def) ;* Put up message
|
||||
|
||||
SelectSent = 'SELECT WO_STEP WITH SCHEDULED NE "Yes" '
|
||||
RList(SelectSent,TARGET_ACTIVELIST$,'','','')
|
||||
|
||||
void = Msg(@window, MsgUp) ;* Take down the message
|
||||
|
||||
WOStepKeys = ''
|
||||
Done = 0
|
||||
LOOP
|
||||
READNEXT WOStepKey ELSE Done = 1
|
||||
UNTIL Done
|
||||
WOStepKeys<1,-1> = WOStepKey
|
||||
REPEAT
|
||||
|
||||
IF WOStepKeys = '' THEN
|
||||
ErrMsg('No Work Order Steps remain unscheduled.')
|
||||
RETURN
|
||||
END
|
||||
|
||||
TypeOver = ''
|
||||
TypeOver<PDISPLAY$> = WOStepKeys
|
||||
TypeOver<PMODE$> = 'K'
|
||||
TypeOver<PSELECT$> = 1
|
||||
TypeOver<PTYPE$> = 'E' ;* Return entire row
|
||||
|
||||
WOStepDat = Popup(@WINDOW,TypeOver,'WO_STEP_SELECT')
|
||||
IF Get_Status(errCode) THEN
|
||||
ErrMsg(errCode)
|
||||
RETURN
|
||||
END
|
||||
|
||||
|
||||
|
||||
WONo = WOStepDat[1,@VM]
|
||||
WOStep = WOStepDat[COL2()+1,@VM]
|
||||
Desc = WOStepDat[COL2()+1,@VM]
|
||||
PSNo = WOStepDat[COL2()+1,@VM]
|
||||
|
||||
IF WOStepDat = '' OR WOStepKey = CHAR(27) THEN RETURN ;* No selection or cancelled
|
||||
|
||||
Set_Property(@WINDOW:'.WO_NO','DEFPROP',WONo)
|
||||
Set_Property(@WINDOW:'.STEP_NO','DEFPROP',StepNo)
|
||||
Set_Property(@WINDOW:'.PS_NO','DEFPROP',PSNo)
|
||||
|
||||
PSRec = XLATE('PROD_SPEC',PSNo,'','X')
|
||||
|
||||
ReactTypeOps = OCONV(PSRec<PROD_SPEC_REACTOR_TYPE$>,'[REACT_TYPE_CONV,OPSREF]')
|
||||
ReactTypeCode = OCONV(PSRec<PROD_SPEC_REACTOR_TYPE$>,'[REACT_TYPE_CONV,CODE]')
|
||||
|
||||
QualReacts = PSRec<PROD_SPEC_QUAL_REACTS$>
|
||||
BlockedReacts = PSRec<PROD_SPEC_BLOCKED_REACTS$>
|
||||
|
||||
Set_Property(@WINDOW:'.REACT_TYPE','DEFPROP',ReactType)
|
||||
Set_Property(@WINDOW,'@QUAL_REACTS',QualReacts)
|
||||
Set_Property(@WINDOW,'@BLOCKED_REACTS',BlockedReacts)
|
||||
|
||||
|
||||
OPEN 'DICT.REACTOR' TO DictReactor ELSE
|
||||
ErrMsg('Unable to open DICT.REACTOR for Btree.Extract')
|
||||
RETURN
|
||||
END
|
||||
|
||||
|
||||
|
||||
IF ReactTypeCode = 'ASM' OR ReactType = 'ASM+' THEN
|
||||
ReactTypeCode = 'ASM':@VM:'ASM+'
|
||||
END
|
||||
|
||||
SearchString = 'REACT_TYPE':@VM:ReactTypeCode:@FM
|
||||
|
||||
Btree.Extract(SearchString,'REACTOR',DictReactor,ReactNos,'','')
|
||||
|
||||
IF Get_Status(errCode) THEN
|
||||
ErrMsg(errCode)
|
||||
RETURN
|
||||
END
|
||||
|
||||
DEBUG
|
||||
|
||||
brCnt = COUNT(BlockedReacts,@VM) + (BlockedReacts NE '')
|
||||
|
||||
FOR I = 1 TO brCnt
|
||||
BlockedReact = BlockedReacts<1,I>
|
||||
LOCATE BlockedReact IN ReactNos USING @VM SETTING Pos THEN
|
||||
ReactNos = DELETE(ReactNos,1,Pos,0)
|
||||
END
|
||||
|
||||
|
||||
NEXT I
|
||||
|
||||
|
||||
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
ReactDC:
|
||||
* * * * * * *
|
||||
|
||||
CtrlEntID = @WINDOW:'.REACT_NO'
|
||||
|
||||
CurrPos = Get_Property(CtrlEntID,'SELPOS')
|
||||
CurrCol = CurrPos<1>
|
||||
CurrRow = CurrPos<2>
|
||||
|
||||
CurrList = Get_Property(CtrlEntID,'LIST')
|
||||
|
||||
BEGIN CASE
|
||||
CASE CurrCol = COL$REACT_NO
|
||||
ReactNo = CurrList<CurrRow,COL$REACT_NO>
|
||||
IF ReactNo NE '' THEN
|
||||
obj_AppWindow('ViewRelated','REACTOR':@RM:ReactNo)
|
||||
END
|
||||
|
||||
END CASE
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
ReactPC:
|
||||
* * * * * * *
|
||||
|
||||
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
|
||||
* * * * * * *
|
||||
ReactOptions:
|
||||
* * * * * * *
|
||||
|
||||
CtrlEntID = @WINDOW:'.REACT_NO'
|
||||
|
||||
SelPos = Get_Property(CtrlEntID,'SELPOS')
|
||||
CurCol = SelPos<1>
|
||||
CurRow = SelPos<2>
|
||||
CurrArray = Get_Property(CtrlEntID,'ARRAY')
|
||||
|
||||
BEGIN CASE
|
||||
CASE CurCol = COL$REACT_NO
|
||||
|
||||
RetVal = Popup(@WINDOW,'','REACTOR')
|
||||
|
||||
IF RetVal NE '' THEN
|
||||
obj_AppWindow('LUValReturn',RetVal:@RM:CtrlEntID:@RM:SelPos)
|
||||
END
|
||||
|
||||
|
||||
END CASE
|
||||
|
||||
GOSUB Refresh
|
||||
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Schedule:
|
||||
* * * * * * *
|
||||
|
||||
debug
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Cancel:
|
||||
* * * * * * *
|
||||
|
||||
End_Dialog(@WINDOW,'Cancel')
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
|
Reference in New Issue
Block a user