FUNCTION Dialog_Sched(EntID,Event,Parm1,Parm2,Parm3,Parm4,Parm5)
/*
Commuter module for DIALOG_SCHED window
06/27/2014 - John C. Henry, J.C. Henry & Co., Inc.
*/
#pragma precomp SRP_PreCompiler
DECLARE SUBROUTINE Set_Property, ErrMsg, obj_Appwindow, Btree.Extract, Send_Event, Send_Message, RList, Print_Demand
DECLARE SUBROUTINE ErrMsg, Set_Status, Security_Err_Msg, Make.List, Start_Window
DECLARE FUNCTION Get_Property, Send_Message, NextKey, Popup, obj_Calendar, Printer_Select
DECLARE FUNCTION Set_Printer, obj_Install, obj_Popup, Send_Message
DECLARE FUNCTION EntID, MemberOf, Repository, Security_Check, Start_Window, obj_Prod_Spec, Set_Property, Msg, rds_supplement_maint
$insert LOGICAL
$insert FILE.SYSTEM.EQUATES
$insert ACTION_SETUP
$INSERT APPCOLORS
$INSERT WO_LOG_EQUATES
$INSERT SCHED_DET_EQUATES
$INSERT REACTOR_EQUATES
$INSERT RLIST_EQUATES
$INSERT RTI_STYLE_EQUATES
$INSERT PRS_LAYER_EQU
$INSERT POPUP_EQUATES
$INSERT SECURITY_RIGHTS_EQU
$INSERT RDS_EQUATES
$INSERT WO_STEP_EQUATES
EQU CRLF$ TO \0D0A\
EQU COL$REACT_NO TO 1
EQU COL$TYPE TO 2
EQU COL$WFR_SIZE TO 3
EQU COL$ASSIGN_DESC TO 4
EQU COL$SCHED_DAY_1 TO 5
EQU COL$SCHED_DAY_2 TO 6
EQU COL$SCHED_DAY_3 TO 7
EQU COL$SCHED_DAY_4 TO 8
EQU COL$SCHED_DAY_5 TO 9
EQU COL$WO_NO TO 1
EQU COL$SPLIT TO 2
EQU COL$EPI_PN TO 3
EQU WM_USER$ TO 1024
EQU DTM_SELROW$ TO (WM_USER$ + 59)
EQU DTM_SELALLROWS$ TO (WM_USER$ + 61)
EQU ETM_INSERTROW$ TO (WM_USER$ + 2004)
EQU ETM_DELETEROW$ TO (WM_USER$ + 2005)
EQU NOTIFICATION_PERIOD$ TO 12
ErrTitle = 'Error in Dialog_Sched'
ErrorMsg = ''
Result = ''
BEGIN CASE
CASE EntID = @WINDOW
BEGIN CASE
CASE Event = 'CREATE' ; GOSUB Create
END CASE
CASE EntID = @WINDOW:'.PREV' AND Event = 'CLICK' ; GOSUB PrevDate
CASE EntID = @WINDOW:'.NEXT' AND Event = 'CLICK' ; GOSUB NextDate
CASE EntID = @WINDOW:'.SCHED_DT' AND Event = 'CHANGED' ; GOSUB Refresh
CASE EntID = @WINDOW:'.SCHED_DT' AND Event = 'LOSTFOCUS' ; GOSUB SchedDtLF
CASE EntID = @WINDOW:'.SCHED' AND Event = 'DBLCLK' ; GOSUB SchedDC
CASE EntID = @WINDOW:'.WO_NO' AND Event = 'DBLCLK' ; GOSUB WONoDoubleClick
CASE EntID = @WINDOW:'.SCHED' AND Event = 'GOTFOCUS' ; GOSUB SchedGotFocus
CASE EntID = @WINDOW:'.SCHED' AND Event = 'CLICK' ; GOSUB SchedGotFocus
CASE EntID = @WINDOW:'.WO_NO' AND Event = 'POSCHANGED' ; GOSUB WO_PC
CASE EntID = @WINDOW:'.UPDATE' AND Event = 'CLICK' ; GOSUB Update
CASE EntID = @WINDOW:'.INVENTORY_DEMAND' AND Event = 'CLICK' ; GOSUB InventoryDemand
CASE EntID = @WINDOW:'.SCHED' AND Event = 'WINMSG' ; GOSUB TrapKeys
CASE EntID = @WINDOW:'.WO_NO' AND Event = 'WINMSG' ; GOSUB TrapKeys
CASE EntID = @WINDOW:'.SEARCHED_WO' AND Event = 'LOSTFOCUS' ; GOSUB WONoSearch
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)
Set_Property(@WINDOW:'.SCHED_DT','TEXT',OCONV(Date(),'D4HL'))
CtrlID = @WINDOW:'.SCHED'
SchedStyles = Send_Message(CtrlID,'COLSTYLE',1)
eventOp = TRUE$ ; * // Turn tracking on
eventOp<4> = TRUE$ ; * // Track Synchronously
CALL send_Message( @window : ".SCHED", "QUALIFY_EVENT", ETM_DELETEROW$, eventOp )
CALL send_Message( @window : ".SCHED", "QUALIFY_EVENT", ETM_INSERTROW$, eventOp )
CALL send_Message( @window : ".WO_NO", "QUALIFY_EVENT", ETM_DELETEROW$, eventOp )
CALL send_Message( @window : ".WO_NO", "QUALIFY_EVENT", ETM_INSERTROW$, eventOp )
SchedStyles
= BitOr(SchedStyles,DTCS_VALIGNCENTER$)
SchedStyles = BitOr(SchedStyles,DTCS_VALIGNCENTER$)
SchedStyles = BitOr(SchedStyles,DTCS_VALIGNCENTER$)
SchedStyles = BitOr(SchedStyles,DTCS_VALIGNCENTER$)
SchedStyles = BitOr(SchedStyles,DTCS_MULTILINE$)
SchedStyles = BitOr(SchedStyles,DTCS_VSCROLL$)
SchedStyles = BitOr(SchedStyles,DTCS_HSCROLL$)
SchedStyles = BitOr(SchedStyles,DTCS_AUTOVSCROLL$)
SchedStyles = BitOr(SchedStyles,DTCS_AUTOHSCROLL$)
SchedStyles = BitOr(SchedStyles,DTCS_MULTILINE$)
SchedStyles = BitOr(SchedStyles,DTCS_VSCROLL$)
SchedStyles = BitOr(SchedStyles,DTCS_HSCROLL$)
SchedStyles = BitOr(SchedStyles,DTCS_AUTOVSCROLL$)
SchedStyles = BitOr(SchedStyles,DTCS_AUTOHSCROLL$)
SchedStyles = BitOr(SchedStyles,DTCS_MULTILINE$)
SchedStyles = BitOr(SchedStyles,DTCS_VSCROLL$)
SchedStyles = BitOr(SchedStyles,DTCS_HSCROLL$)
SchedStyles = BitOr(SchedStyles,DTCS_AUTOVSCROLL$)
SchedStyles = BitOr(SchedStyles,DTCS_AUTOHSCROLL$)
SchedStyles = BitOr(SchedStyles,DTCS_MULTILINE$)
SchedStyles = BitOr(SchedStyles,DTCS_VSCROLL$)
SchedStyles = BitOr(SchedStyles,DTCS_HSCROLL$)
SchedStyles = BitOr(SchedStyles,DTCS_AUTOVSCROLL$)
SchedStyles = BitOr(SchedStyles,DTCS_AUTOHSCROLL$)
SchedStyles = BitOr(SchedStyles,DTCS_MULTILINE$)
SchedStyles = BitOr(SchedStyles,DTCS_VSCROLL$)
SchedStyles = BitOr(SchedStyles,DTCS_HSCROLL$)
SchedStyles = BitOr(SchedStyles,DTCS_AUTOVSCROLL$)
SchedStyles = BitOr(SchedStyles,DTCS_AUTOHSCROLL$)
Send_Message(CtrlID,'COLSTYLE',0,SchedStyles)
Send_Message(CtrlID,'ROWHEIGHT',0,36)
/* Do not refresh after the 'Create' updated the edit table */
Set_Property(@WINDOW,'@REFRESH',0)
RETURN
*********
NextDate:
*********
CurrDt = ICONV(Get_Property(@WINDOW:'.SCHED_DT','TEXT'),'D')
CurrDt += 1
Set_Property(@WINDOW:'.SCHED_DT','TEXT',OCONV(CurrDt,'D4HL'))
RETURN
*********
PrevDate:
*********
CurrDt = ICONV(Get_Property(@WINDOW:'.SCHED_DT','TEXT'),'D')
CurrDt -= 1
Set_Property(@WINDOW:'.SCHED_DT','TEXT',OCONV(CurrDt,'D4HL'))
RETURN
**********
SchedDtLF:
**********
CurrDt = ICONV(Get_Property(@WINDOW:'.SCHED_DT','TEXT'),'D')
Set_Property(@WINDOW:'.SCHED_DT','TEXT',OCONV(CurrDt,'D4HL'))
RETURN
********
Refresh:
********
Gosub Update
RETURN
**************
SchedGotFocus:
**************
RefreshFlag = Get_Property(@WINDOW,'@REFRESH')
if (RefreshFlag = 1) then
GOSUB Update
Set_Property(@WINDOW,'@REFRESH',0)
end else
SelectedItem = Get_Property(@WINDOW:'.SCHED','SELPOS')
Set_Property("SYSTEM", "BLOCK_EVENTS", True$)
Set_Property(@WINDOW:'.SCHED','SELPOS',SelectedItem)
Handle = Get_Property(@WINDOW:'.SCHED', 'HANDLE')
CALL sendMessage(Handle, DTM_SELROW$, 0, SelectedItem<2>-1)
Set_Property("SYSTEM", "BLOCK_EVENTS", False$)
Col = SelectedItem<1>
Row = SelectedItem<2>
CellData = Get_Property(@WINDOW:'.SCHED', 'CELLPOS', Col:@FM:Row)
ClickedWONo = CellData[1,6]
WONos = Get_Property(@WINDOW,'@WO_NOS')
LOCATE ClickedWONo IN WONos USING @FM SETTING Pos THEN
Set_Property(@WINDOW:'.WO_NO', 'SELPOS', 1:@FM:Pos)
END
END
RETURN
*******
Update:
*******
OPEN 'REACTOR' TO ReactorTable ELSE
ErrMsg('Unable to open "REACTOR" table fo index lookup.')
RETURN
END
SelectSent = 'SELECT REACTOR WITH REACT_NO > 0 BY REACT_NO'
RList(SelectSent,TARGET_ACTIVELIST$,'','','')
ReactNos = ''
ReactTypes = ''
ReactWfrSizes = ''
ReactAssignments = ''
ReactAssignDescs = ''
Done = 0
LOOP
READNEXT ReactNo ELSE Done = 1
UNTIL Done
ReactNos := ReactNo:@VM
READ ReactRec FROM ReactorTable,ReactNo THEN
ReactTypes := OCONV(ReactRec, '[REACT_TYPE_CONV,OPSREF]'):@VM
ReactWfrSizes := ReactRec:@VM
ReactAssignments := ReactRec:@VM
ReactAssignDescs := OCONV(ReactRec,'[REACT_ASSIGN_CONV]'):@VM
END
REPEAT
ReactNos[-1,1] = ''
ReactTypes[-1,1] = ''
ReactWfrSizes[-1,1] = ''
ReactAssignments[-1,1] = ''
ReactAssignDescs[-1,1] = ''
SchedArray = ''
SchedArray = ReactNos
SchedArray = ReactTypes
SchedArray = ReactWfrSizes
SchedArray = ReactAssignDescs
SchedDt = Get_Property(@WINDOW:'.SCHED_DT','TEXT')
SchedDay = ICONV(SchedDt,'D') ;* Start with today
StartDay = SchedDay - 1
EndDay = SchedDay + 3
CurrDay = StartDay
FOR Col = COL$SCHED_DAY_1 TO COL$SCHED_DAY_5
Day = Mod(CurrDay, 7)
BEGIN CASE
CASE Day = 0 ; Day = "Sunday"
CASE Day = 1 ; Day = "Monday"
CASE Day = 2 ; Day = "Tuesday"
CASE Day = 3 ; Day = "Wednesday"
CASE Day = 4 ; Day = "Thursday"
CASE Day = 5 ; Day = "Friday"
CASE Day = 6 ; Day = "Saturday"
END CASE
void = Send_Message(@WINDOW:'.SCHED', 'COLLABEL', Col, Day:' ':OCONV(CurrDay,'D4HL'))
CurrDay += 1
NEXT Col
OPEN 'DICT.SCHED_DET' TO SchedDictVar ELSE
ErrMsg('Unable to open DICT.SCHED_DET for index lookup')
RETURN
END
WONos = '' ;* @FM delimited list of WONos in displayed dates
WOData = '' ;* @FM delimited WO data CustName:@VM:HotLot
WODispPos = '' ;* @FM delimited WODispPositions, DispPos : @SVM : colIndex : @VM : DispPos : @SVM : colIndex...
HotCells = '' ;* CurrCol:@VM:CurrLine array with 1 or 0 for contains Hot Lot
WOReactors = '' ;* @FM delimited list of Reactors per WO
ReactorModified = ''
ColIndex = COL$SCHED_DAY_1
FOR DispDt = StartDay TO EndDay
SearchString = 'SCHED_DT':@VM:DispDt:@FM
Btree.Extract(SearchString,'SCHED_DET',SchedDictVar,SchedDetKeys,'','')
IF Get_Status(errCode) THEN
ErrMsg(errCode)
RETURN
END
keyCnt = COUNT(SchedDetKeys,@VM) + (SchedDetKeys NE '')
ColData = ''
FOR N = 1 TO keyCnt
SchedDetKey = SchedDetKeys<1,N>
ReactNo = SchedDetKey[1,'*']
DetNo = SchedDetKey[-1,'B*']
LOCATE ReactNo IN ReactNos USING @VM SETTING DispPos ELSE null
DetRec = XLATE('SCHED_DET',SchedDetKey,'','X')
WONo = DetRec
Desc = DetRec
IF Desc NE '' THEN
Desc = '(':Desc:')'
END
IF (DispDt >= Date()) THEN
ModifiedDateTime = DetRec
IF (ModifiedDateTime NE '') THEN
CurrentDateTime = ICONV(OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTH'),'DTM')
ElapseTime = (CurrentDateTime - ModifiedDateTime) * 24
IF (ElapseTime <= NOTIFICATION_PERIOD$) then
IF (ReactorModified = '') THEN
ReactorModified = ElapseTime
END ELSE
IF (ElapseTime < ReactorModified) THEN
ReactorModified = ElapseTime
END
END
END
END
END
LOCATE WONo IN WONos BY 'AR' USING @FM SETTING woPos THEN
WODispPos = WODispPos:@VM:DispPos:@SVM:colIndex
CustName = WOData
HotLot = WOData
*****************************************************
* Build a reference list of reactors per work order *
*****************************************************
LOCATE ReactNo IN WOReactors BY 'AR' USING @VM SETTING woReactorsPos THEN
Null
END ELSE
WOReactors = INSERT(WOReactors,1,woReactorsPos,0,ReactNo)
END
END ELSE
CustName = XLATE('WO_LOG',WONo,'CUST_ABBREV','X')
HotLot = XLATE('WO_LOG',WONo,'HOT_LOT','X')
WONos = INSERT(WONos,woPos,0,0,WONo)
WOData = INSERT(WOData,woPos,0,0,CustName:@VM:HotLot)
WODispPos = INSERT(WODispPos,woPos,0,0,DispPos:@SVM:colIndex)
WOReactors = INSERT(WOReactors,woPos,0,0,ReactNo)
END
CellData = ''
IF WONo NE '' THEN CellData := WONo:' ':CustName[1,23]
IF Desc NE '' THEN CellData := ' ':Desc
CurrCellData = ColData<1,DispPos>
IF CurrCellData = '' THEN
ColData<1,DispPos> = CellData
END ELSE
ColData<1,DispPos> = CurrCellData:CRLF$:CellData
END
IF HotLot THEN HotCells<1,-1> = ColIndex:@SVM:DispPos
NEXT N
SchedArray = ColData
ColIndex += 1
NEXT DispDt
Set_Property(@WINDOW:'.SCHED','ARRAY',SchedArray)
Set_Property(@WINDOW,'@WO_NOS',WONos)
Set_Property(@WINDOW,'@WO_CELLS',WODispPos)
CONVERT @FM TO @VM IN WONos
CONVERT @VM TO ',' IN WOReactors
CONVERT @FM TO @VM IN WOReactors
EPIPns = XLATE('WO_LOG', WONos, WO_LOG_EPI_PART_NO$, 'X')
Set_Property(@WINDOW:'.WO_NO','ARRAY',WONos:@FM:WOReactors:@FM:EPIPns)
***************************************
* Color the WO which have been closed *
***************************************
FOR WONosIndex = 1 TO COUNT(WONos,@VM) + (WONos NE '')
WONo = WONos<1,WONosIndex>
WOCloseDate = XLATE('WO_LOG', WONo, WO_LOG_CLOSE_DATE$, 'X')
IF (WOCloseDate NE '') THEN
stat = Send_Message(@WINDOW:'.WO_NO', 'COLOR_BY_POS', 0, WONosIndex, GREY$)
END ELSE
stat = Send_Message(@WINDOW:'.WO_NO', 'COLOR_BY_POS', 0, WONosIndex, WHITE$)
END
NEXT WONosIndex
**********************************************************************
* Color the schedule cells 'grey' if the reactor is 'out of service' *
**********************************************************************
LineCnt = COUNT(ReactNos,@VM) + (ReactNos NE '')
FOR Line = 1 TO LineCnt
/* Default White = Normal */
stat = Send_Message(@WINDOW:'.SCHED', 'COLOR_BY_POS', 1, Line, WHITE$)
IF ReactAssignments<1,Line> = 'O' THEN
stat = Send_Message(@WINDOW:'.SCHED', 'COLOR_BY_POS', 1, Line, GREY$)
END ELSE
IF (ReactorModified NE '') THEN
Intensity = (NOTIFICATION_PERIOD$ - ReactorModified) / NOTIFICATION_PERIOD$
DynamicYellow = 255 + (255*256) + (INT(Intensity*202)*65536)
stat = Send_Message(@WINDOW:'.SCHED', 'COLOR_BY_POS', 1, Line, DynamicYellow)
END
END
NEXT Line
****************************************************************
* Color the schedule cells 'red' is the WO contains 'hot' lots *
****************************************************************
hcCnt = COUNT(HotCells,@VM) + (HotCells NE '')
FOR H = 1 TO hcCnt
CellLoc = HotCells<1,H>
Col = CellLoc[1,@SVM]
Row = CellLoc[COL2()+1,@SVM]
stat = Send_Message(@WINDOW:'.SCHED','COLOR_BY_POS', Col, Row, RED$)
NEXT H
RETURN
****************
WONoDoubleClick:
****************
CtrlEntID = @WINDOW:'.WO_NO'
CurrPos = Get_Property(CtrlEntID,'SELPOS')
CurrCol = CurrPos<1>
CurrRow = CurrPos<2>
If (CurrCol = COL$WO_NO) Then
WONo = Get_Property(CtrlEntID, 'CELLPOS', COL$WO_NO:@FM:CurrRow)
WOStepKey = WONo:'*1'
Reactor = Get_Property(CtrlEntID, 'CELLPOS', COL$SPLIT:@FM:CurrRow)
Reactor = Reactor<1,1>
PopupId = entid( @appid<1>, 'POPUP', '', 'DAILY_SCHED_OPTS' )
OverRide = ''
Display = xlate( 'SYSREPOSPOPUPS', 'LSL2**DAILY_SCHED_OPTS', pdisplay$, 'X' )
if MemberOf(@USER4, 'ENGINEERING') OR MemberOf(@USER4, 'SUPERVISOR') OR MemberOf(@USER4, 'LEAD') then ;* Added LEAD security group to allow asign supplements -dkk 12/5/14
* ADD OPTION TO ASSIGN SUPPLEMENTS
Display := @vm:'Assign Supplements':@tm:'SUPPLEMENTS'
end
OverRide = Display
ChosenOpt = repository( 'EXECUTE', PopupId, @window, OverRide )
RdsKeys = ''
BEGIN CASE
CASE ChosenOpt = 'QUOTE'
IF security_check( 'Quote', Read$ ) THEN
WORec = XLATE('WO_LOG',WoNo,'','X')
OrderNo = WORec
OrderItemNos = WORec
QuoteNo = XLATE('ORDER_DET',OrderNo:'*':OrderItemNos<1,1>,1,'X')
Void = start_window( 'QUOTE2', @window, QuoteNo:'*CENTER', '', '' )
END ELSE
security_err_msg( 'Quote', Read$ )
END
CASE ChosenOpt = 'PSN'
IF security_check( 'Prod Spec', Read$ ) THEN
PSNId = XLATE('WO_STEP',WOStepKey,WO_STEP_PROD_SPEC_ID$,'X')
Void = start_window( 'PROD_SPEC', @window, PSNId:'*CENTER', '', '' )
END ELSE
security_err_msg( 'Prod Spec', Read$ )
END
CASE ChosenOpt = 'RECIPE'
if security_check( 'Recipe', Read$ ) then
PSN = XLATE('WO_STEP',WOStepKey,1,'X')
LayerSpecs = obj_Prod_Spec('GetLayerProp',PSN:@RM:@RM:1) ;* Returns specs for all layers in internal format
LayerSpec = FIELD(LayerSpecs,@RM,1) ;* Take the first Layer
LayerSet = FIELD(LayerSpec,@FM,1) ;* Not used here but shown for clarity
LayerSpec = FIELD(LayerSpec,@FM,2,99) ;* LayerSpec without the LayerSet
RecipeNo = LayerSpec
Void = start_window( 'RECIPE', @window, RecipeNo:'*CENTER', '', '' )
end else
security_err_msg( 'Recipe', Read$ )
end
CASE ChosenOpt = 'RDS'
if security_check( 'RDS', Read$ ) then
RDSKeys = XLATE('WO_STEP',WOStepKey,WO_STEP_RDS_KEY$,'X')
TypeOver = ''
TypeOver = 'K'
TypeOver = RDSKeys
RDSKeys = Popup(@WINDOW,TypeOver,'RDS_QUERY')
IF RDSKeys NE '' THEN
Void = start_window( 'RDS', @window, RDSKeys:'*CENTER', '', '' )
END
end else
security_err_msg( 'RDS', Read$ )
end
CASE ChosenOpt = 'WO'
if security_check( 'WO Log', Read$ ) then
NewForm = Xlate('APP_INFO', 'NEW_WO_FORM', '', 'X')
If NewForm then
Start_Window('NDW_WO_LOG', @Window, WONo)
end else
Start_Window('WO_LOG2',@WINDOW, WONo:'*CENTER', '', '' ) ;* Added (copied from ViewPSN) -dkk 10/23/14
end
end else
security_err_msg( 'WO Log', Read$ )
end
CASE ChosenOpt = 'WO_STAT'
PSN = XLATE('WO_STEP',WOStepKey,1,'X')
ReactorType = XLATE('PROD_SPEC',PSN,80,'X')
BEGIN CASE
CASE ReactorType = 'P' Or ReactorType = 'EPP'
obj_Appwindow('ViewRelated','WO_PROD_EPI':@RM:WOStepKey)
CASE ReactorType = 'GAN'
obj_Appwindow('ViewRelated','WO_PROD_GAN':@RM:WOStepKey)
CASE 1
obj_Appwindow('ViewRelated','WO_PROD':@RM:WOStepKey)
END CASE
case ChosenOpt = 'SUPPLEMENTS'
Void = rds_supplement_maint( WoNo )
case 1
Null
end case
end
return
********
SchedDC:
********
CtrlEntID = @WINDOW:'.SCHED'
CurrPos = Get_Property(CtrlEntID,'SELPOS')
CurrCol = CurrPos<1>
CurrRow = CurrPos<2>
ReactNo = Get_Property(CtrlEntID,'CELLPOS',COL$REACT_NO:@FM:CurrRow)
If (CurrCol = COL$REACT_NO) Then
Open 'DICT.SCHED_DET' TO hSCHED_DET Then
Set_Status(0)
FoundOpenedDate = False$
Error = False$
DispDt = Date()
Loop
Until (FoundOpenedDate) OR (Error)
SearchString = 'SCHED_DT':@VM:DispDt
Btree.Extract(SearchString, 'SCHED_DET', hSCHED_DET, SchedDetKeys, '', '')
If Get_Status(errCode) Then
ErrMsg(errCode)
Error = True$
End else
ReactorFound = False$
keyCnt = COUNT(SchedDetKeys,@VM) + (SchedDetKeys NE '')
For LoopIndex = 1 TO keyCnt
SchedDetKey = SchedDetKeys<1,LoopIndex>
ScheduledReactor = SchedDetKey[1,'*']
If (ScheduledReactor = ReactNo) then
ReactorFound = True$
end
Next LoopIndex
If (ReactorFound = False$) then
FoundOpenedDate = True$
end else
DispDt = DispDt + 1
end
End
Repeat
If (FoundOpenedDate = True$) then
Set_Property(@WINDOW:'.SCHED_DT','TEXT',OCONV(DispDt,'D4HL'))
end
end else
ErrMsg('Unable to open DICT.SCHED_DET for index lookup')
end
end else
if (CurrCol = COL$TYPE) OR (CurrCol = COL$WFR_SIZE) OR (CurrCol = COL$ASSIGN_DESC) then
oaParms = 'REACT_STATE':@RM
oaParms := ReactNo:@RM
obj_Appwindow('ViewRelated',oaParms)
end else
SchedDt = ICONV(Get_Property(@WINDOW:'.SCHED_DT','TEXT'),'D')
BEGIN CASE
CASE CurrCol = COL$SCHED_DAY_1 ; SchedDt -= 1
CASE CurrCol = COL$SCHED_DAY_2 ; NULL
CASE CurrCol = COL$SCHED_DAY_3 ; SchedDt += 1
CASE CurrCol = COL$SCHED_DAY_4 ; SchedDt += 2
CASE CurrCol = COL$SCHED_DAY_5 ; SchedDt += 3
CASE 1 ; SchedDt = ''
END CASE
if (SchedDt NE '') then
oaParms = 'SCHED':@RM
oaParms := ReactNo:'*':SchedDt:@RM
obj_Appwindow('ViewRelated',oaParms)
end
end
end
Set_Property(@WINDOW,'@REFRESH',1)
return
***********
WONoSearch:
***********
SearchedWONo = Get_Property(@WINDOW:'.SEARCHED_WO','TEXT')
WONos = Get_Property(@WINDOW,'@WO_NOS')
LOCATE SearchedWONo IN WONos USING @FM SETTING Pos THEN
Set_Property(@WINDOW:'.WO_NO', 'SELPOS', 1:@FM:Pos)
END
RETURN
******
WO_PC:
******
CtrlEntID = @WINDOW:'.WO_NO'
CurrPos = Get_Property(CtrlEntID,'SELPOS')
CurrCol = CurrPos<1>
CurrRow = CurrPos<2>
PrevPos = Get_Property(CtrlEntID,'PREVSELPOS')
PrevCol = PrevPos<1>
PrevRow = PrevPos<2>
WONos = Get_Property(@WINDOW,'@WO_NOS')
WOCells = Get_Property(@WINDOW,'@WO_CELLS')
****************************
* Clear Previous Selection *
****************************
WONo = Get_Property(CtrlEntID,'CELLPOS',1:@FM:PrevRow)
LOCATE WONo IN WONos USING @FM SETTING Pos THEN
CellLocs = WOCells
cCnt = COUNT(CellLocs,@VM) + (CellLocs NE '')
FOR I = 1 to cCnt
Cell = CellLocs<1,I>
Row = Cell[1,@SVM]
Col = Cell[COL2()+1,@SVM]
stat = Send_Message(@WINDOW:'.SCHED','COLOR_BY_POS',Col,Row,WHITE$)
NEXT I
END
*******************************
* Highlight Current Selection *
*******************************
ScrolledTopPosition = false$
WONo = Get_Property(CtrlEntID,'CELLPOS',1:@FM:CurrRow)
LOCATE WONo IN WONos USING @FM SETTING Pos THEN
CellLocs = WOCells
cCnt = COUNT(CellLocs,@VM) + (CellLocs NE '')
FOR I = 1 to cCnt
Cell = CellLocs<1,I>
SelRow = Cell[1,@SVM]
SelCol = Cell[COL2()+1,@SVM]
if (ScrolledTopPosition = false$) then
Set_Property(@WINDOW:'.SCHED', 'TOPPOS', 1:@FM:SelRow)
ScrolledTopPosition = true$
end
stat = Send_Message(@WINDOW:'.SCHED','COLOR_BY_POS',SelCol,SelRow,PRE_BLUE$)
NEXT I
END
return
****************
InventoryDemand:
****************
ReportType = 'D'
Print_Demand(ReportType)
return
*********
TrapKeys:
*********
Message = Parm2
BEGIN CASE
CASE ( Message = ETM_INSERTROW$ )
* // Stop the insert here...
CALL set_WinMsgVal( TRUE$, 0 ) ; * // Force PS to return 0 to Windows
CASE ( Message = ETM_DELETEROW$ )
* // Stop the delete here...
CALL set_WinMsgVal( TRUE$, 0 ) ; * // Force PS to return 0 to Windows
END CASE
RETURN