added LSL2 stored procedures
This commit is contained in:
486
LSL2/STPROC/PRINT_DEMAND.txt
Normal file
486
LSL2/STPROC/PRINT_DEMAND.txt
Normal file
@ -0,0 +1,486 @@
|
||||
COMPILE SUBROUTINE Print_Demand(ReportParm)
|
||||
#pragma precomp SRP_PreCompiler
|
||||
|
||||
/*
|
||||
Print Material Demand Report
|
||||
10/27/2016 - John C Henry, J.C. Henry & Co., Inc. - Initial Coding
|
||||
10/05/2017 - Donald Bakke - No longer select SCHED_DET rows with an end date specified.
|
||||
10/24/2018 - Daniel Stieber - Patch added to resolve scheduling conflicts on the same day
|
||||
*/
|
||||
|
||||
DECLARE SUBROUTINE Utility, ErrMsg, Set_Status, Set_Printer, RList, SRP_Stopwatch
|
||||
DECLARE FUNCTION Set_Printer, Get_Printer, Msg, Get_Status, Printer_Select, obj_Install, Dialog_Box, obj_Location
|
||||
DECLARE FUNCTION Schedule_Services
|
||||
|
||||
$INSERT OIPRINT_EQUATES
|
||||
$INSERT SCHED_DET_EQUATES
|
||||
$INSERT WO_LOG_EQUATES
|
||||
$INSERT APPCOLORS
|
||||
$INSERT MSG_EQUATES
|
||||
$INSERT LOGICAL
|
||||
$INSERT SCHEDULE_EQU
|
||||
|
||||
EQU TAB$ TO \09\
|
||||
EQU TARGET_ACTIVELIST$ TO 5
|
||||
|
||||
Main:
|
||||
ErrorTitle = 'Error in stored procedure Print_Demand'
|
||||
ErrCode = ''
|
||||
ErrorMsg = ''
|
||||
SRP_Stopwatch('Reset')
|
||||
SRP_Stopwatch('Start', 'Initializing')
|
||||
OPEN 'SCHED_DET' TO SchedDetTable ELSE
|
||||
ErrorMsg = 'Unable to open "SCHED_DET" table.'
|
||||
ErrMsg(ErrorTitle:@SVM:ErrorMsg)
|
||||
RETURN
|
||||
END
|
||||
|
||||
OPEN 'DICT.SCHED_DET' TO @DICT ELSE
|
||||
ErrorMsg = 'Unable to open "SCHED_DET" table.'
|
||||
ErrMsg(ErrorTitle:@SVM:ErrorMsg)
|
||||
RETURN
|
||||
END
|
||||
|
||||
|
||||
Today = OCONV(Date(),'D4/')
|
||||
|
||||
EndDate = OCONV(Date()+13,'D4/')
|
||||
|
||||
|
||||
ReactList = ''
|
||||
WOList = ''
|
||||
SchedDetKeys = ''
|
||||
PrevReactNo = ''
|
||||
PrevWO = ''
|
||||
|
||||
SelectSent = 'SELECT SCHED_DET WITH SCHED_DT GE ':QUOTE(Today):' BY REACT_NO'
|
||||
|
||||
SRP_Stopwatch('Stop', 'Initializing')
|
||||
SRP_Stopwatch('Start', 'Data Select')
|
||||
|
||||
RList(SelectSent,TARGET_ACTIVELIST$,'','','')
|
||||
IF Get_Status(errCode) THEN
|
||||
ErrMsg(errCode)
|
||||
RETURN
|
||||
END
|
||||
SRP_Stopwatch('Stop', 'Data Select')
|
||||
SRP_Stopwatch('Start', 'Build Key List')
|
||||
Done = 0
|
||||
@ID = ''
|
||||
LOOP
|
||||
PrevSchedDetKey = @ID
|
||||
READNEXT @ID ELSE Done = 1
|
||||
UNTIL Done
|
||||
ReactNo = @ID[1,'*']
|
||||
SchedDt = @ID[COL2()+1,'*']
|
||||
SeqNo = @ID[COL2()+1,'*']
|
||||
|
||||
READ SchedDetRec FROM SchedDetTable,@ID THEN
|
||||
|
||||
WONo = SchedDetRec<SCHED_DET_WO_NO$>
|
||||
|
||||
LOCATE ReactNo IN ReactList BY 'AR' USING @FM SETTING Pos ELSE
|
||||
ReactList = INSERT(ReactList,Pos,0,0,ReactNo)
|
||||
END
|
||||
|
||||
PrevReactNo = Field(PrevSchedDetKey, '*', 1)
|
||||
PrevSchedDt = Field(PrevSchedDetKey, '*', 2)
|
||||
|
||||
LOCATE WONo IN WOList<Pos> USING @VM SETTING WPos ELSE
|
||||
WOList = INSERT(WOList,Pos,-1,0,WONo)
|
||||
// Patch added on 10/24/18 to resolve scheduling conflicts on the same day for
|
||||
// the material track report. - djs
|
||||
If (PrevReactNo EQ ReactNo) and (PrevSchedDt EQ SchedDt) then
|
||||
PrevSeqNo = Field(PrevSchedDetKey, '*', 3)
|
||||
NumWO = DCount(WOList<Pos>, @VM)
|
||||
PrevWONo = WOList<Pos, NumWO - 1>
|
||||
SchedEvents = Schedule_Services('GetScheduleEventSummary', ReactNo, WONo, SchedDt, SeqNo, True$)
|
||||
StartDt = IConv(SchedEvents<SCHEDULE_ENTRY_DATE$>, 'D')
|
||||
PrevSchedEvents = Schedule_Services('GetScheduleEventSummary', ReactNo, PrevWONo, PrevSchedDt, PrevSeqNo, True$)
|
||||
PrevStartDt = IConv(PrevSchedEvents<SCHEDULE_ENTRY_DATE$>, 'D')
|
||||
If StartDt GT PrevStartDt then
|
||||
// This is the common case
|
||||
SchedDetKeys = INSERT(SchedDetKeys,-1,0,0,@ID)
|
||||
end else
|
||||
// Scheduling irregularity - Insert this key in the second to last position.
|
||||
NumKeys = DCount(SchedDetKeys, @FM)
|
||||
InsertPos = NumKeys
|
||||
SchedDetKeys = INSERT(SchedDetKeys,InsertPos,0,0,@ID)
|
||||
end
|
||||
end else
|
||||
SchedDetKeys = INSERT(SchedDetKeys,-1,0,0,@ID)
|
||||
end
|
||||
END
|
||||
END
|
||||
|
||||
REPEAT
|
||||
|
||||
CALL Make.List(0,SchedDetKeys,SchedDetTable,@DICT)
|
||||
SRP_Stopwatch('Stop', 'Build Key List')
|
||||
SRP_Stopwatch('Start', 'Build Report')
|
||||
IF ReportParm = 'T' THEN
|
||||
|
||||
* Tracking Report
|
||||
|
||||
Header = "'D'":@VM:obj_Install('Get_Prop','CompTitle'):' Material Tracking by Reactor':@VM:"Page 'P'"
|
||||
MinDemand = 0
|
||||
|
||||
END
|
||||
|
||||
IF ReportParm = 'D' THEN
|
||||
|
||||
* Demand Report
|
||||
|
||||
MinDemand = Msg(@WINDOW,'','MIN_DEMAND_QTY')
|
||||
Header = "'D'":@VM:obj_Install('Get_Prop','CompTitle'):' Material Demand with Reactor Queue < ':MinDemand:' Cassettes':@VM:"Page 'P'"
|
||||
|
||||
END
|
||||
|
||||
Set_Status(0)
|
||||
|
||||
* Start of printing process
|
||||
|
||||
FileName = 'Print Material Demand'
|
||||
Title = 'Printing Material Demand'
|
||||
|
||||
TopMargin = 1.0
|
||||
BottomMargin = 0.75
|
||||
LeftMargin = 0.25
|
||||
RightMargin = 0.25
|
||||
|
||||
Margins = LeftMargin:@FM:TopMargin:@FM:RightMargin:@FM:BottomMargin
|
||||
|
||||
PageSetup = '1' ;* LandScape
|
||||
PrintSetup = '2' ;* Preview Normal
|
||||
PrintSetup<1,2> = '0' ;* All buttons
|
||||
PrintSetup<1,5> = '1' ;* Page Range
|
||||
PrintSetup<1,6> = 7 ;* full mouse and keyboard support
|
||||
|
||||
If @UserName EQ 'MESCATXMUSER' then
|
||||
PageSetup = '1' ;* Landscape
|
||||
PrintSetup = '0' ;* Print to specific location
|
||||
PrintPath = Printer_Select(PrinterID) ;* Select printer - Displays popup if PrinterPort not found
|
||||
end else
|
||||
PrintPath = ''
|
||||
end
|
||||
stat = Set_Printer('INIT',FileName,Title,Margins,PageSetup,PrintSetup,PrintPath)
|
||||
|
||||
IF stat < 0 THEN
|
||||
ErrorMsg = 'Stat = ' : Stat : ', PrintPath = ' : PrintPath
|
||||
GOTO OIPrintErr
|
||||
end
|
||||
DateRange = 'Effective ':OCONV(Date(),'D4')
|
||||
|
||||
Header<-1> = "'T'"
|
||||
Header<-1> = '' ;* Blank line following heading
|
||||
|
||||
font = 'Arial'
|
||||
font<2> = '10'
|
||||
font<4> = '0' ;* Bold
|
||||
|
||||
stat = Set_Printer('FONTHEADFOOT',font) ; IF stat < 0 THEN GOTO OIPrintErr
|
||||
stat = Set_Printer('HEADER',Header) ; IF stat < 0 THEN GOTO OIPrintErr
|
||||
|
||||
Footer = " 'D' 'T'":@VM:@VM:"Page: 'P'"
|
||||
stat = Set_Printer('FOOTER',Footer) ; IF stat < 0 THEN GOTO OIPrintErr
|
||||
|
||||
*
|
||||
@RECCOUNT = 0
|
||||
FirstPass = 1
|
||||
LastRecord = 0
|
||||
FirstLine = 1
|
||||
fontSpacing = 100
|
||||
|
||||
* Make Column Heading
|
||||
|
||||
ColHead = '' ; ColFmt = ''
|
||||
ColHead<1,1> = 'React No' ; ColFmt<1,1> = '+^720'
|
||||
ColHead<1,2> = 'React Type' ; ColFmt<1,2> = '+<^720'
|
||||
ColHead<1,4> = 'WO No' ; ColFmt<1,4> = '+^1000'
|
||||
ColHead<1,5> = 'SAP Prod No' ; ColFmt<1,5> = '+^1000'
|
||||
ColHead<1,6> = 'Sub Part No' ; ColFmt<1,6> = '+<1200'
|
||||
ColHead<1,7> = 'Epi Part No' ; ColFmt<1,7> = '+<1200'
|
||||
ColHead<1,8> = 'WO Qty' ; ColFmt<1,8> = '+>720'
|
||||
ColHead<1,9> = 'RX Qty' ; ColFmt<1,9> = '+>720'
|
||||
ColHead<1,10> = 'UnRel Qty' ; ColFmt<1,10> = '+>720'
|
||||
ColHead<1,11> = 'Kit Location' ; ColFmt<1,11> = '+^1260'
|
||||
ColHead<1,12> = 'Kit Qty' ; ColFmt<1,12> = '+^720'
|
||||
IF ReportParm = 'T' THEN
|
||||
ColHead<1,3> = 'Wafer Size' ; ColFmt<1,3> = '+^1400'
|
||||
ColHead<1,13> = 'PTI Location' ; ColFmt<1,13> = '+^1260'
|
||||
ColHead<1,14> = 'PTI RO' ; ColFmt<1,14> = '+^3380'
|
||||
END ELSE
|
||||
ColHead<1,3> = 'Wafer Size' ; ColFmt<1,3> = '+^1000'
|
||||
ColHead<1,13> = '1K Stage Location' ; ColFmt<1,13> = '+^1260'
|
||||
ColHead<1,14> = 'Stage Qty' ; ColFmt<1,14> = '+^1260'
|
||||
ColHead<1,15> = 'PTI Location' ; ColFmt<1,15> = '+^1260'
|
||||
ColHead<1,16> = 'PTI RO' ; ColFmt<1,16> = '+^1260'
|
||||
END
|
||||
|
||||
|
||||
* Zero Accumulators For Each Break
|
||||
|
||||
Prev.ReactNo = ''
|
||||
Last.ReactNo.Break = 1
|
||||
|
||||
* * * * * * *
|
||||
ReadRecord:
|
||||
* * * * * * *
|
||||
|
||||
* Zero Break Flags To False
|
||||
|
||||
ReactNo.Break=0
|
||||
|
||||
READNEXT @ID, Which.Value ELSE
|
||||
LastRecord = 1
|
||||
ReactNo.Break = 1
|
||||
ReactNo = Prev.ReactNo
|
||||
END
|
||||
|
||||
S.ATID = @ID
|
||||
|
||||
IF FirstPass AND LastRecord THEN
|
||||
GOTO Bail
|
||||
END
|
||||
|
||||
IF LastRecord THEN GOTO BREAKS
|
||||
|
||||
READO @RECORD FROM SchedDetTable,@ID ELSE
|
||||
GOTO ReadRecord
|
||||
END
|
||||
|
||||
@RECCOUNT += 1
|
||||
|
||||
* Calculate Value(s) For Column(s)
|
||||
|
||||
S.ATID = {@ID}
|
||||
I.ATID = S.ATID
|
||||
S.ReactNo = {REACT_NO}
|
||||
I.ReactNo = S.ReactNo
|
||||
S.WoNo = {WO_NO}
|
||||
I.WoNo = S.WoNo
|
||||
S.SubPartNo = XLATE('WO_LOG',S.WoNo,'ORD_SUB_PART_NO','X')
|
||||
I.SubPartNo = S.SubPartNo
|
||||
S.EpiPartNo = XLATE('WO_LOG',S.WoNo,WO_LOG_EPI_PART_NO$,'X')
|
||||
I.EpiPartNo = S.EpiPartNo
|
||||
S.WO_Qty = {WO_QTY}
|
||||
I.WO_Qty = S.WO_Qty
|
||||
S.WO_RX_Qty = {WO_RX_QTY}
|
||||
I.WO_RX_Qty = S.WO_RX_Qty
|
||||
S.WO_UnRel_QTY = {WO_UNREL_QTY}
|
||||
I.WO_UnRel_QTY = S.WO_UnRel_QTY
|
||||
S.Sched_DT = {SCHED_DT}
|
||||
I.Sched_DT = S.Sched_DT
|
||||
*Changed Here JRO
|
||||
S.REACT_TYPE = {REACTOR_TYPE}
|
||||
S.WAFER_SIZE = {WAFER_SIZE}
|
||||
S.ProdOrdNo = {PROD_ORD_NO}
|
||||
|
||||
KitData = obj_Location('KitLocations',S.WONo)
|
||||
|
||||
SWAP CRLF$ WITH @VM IN KitData
|
||||
|
||||
S.KitLocation = KitData<1>
|
||||
I.KitLocation = S.KitLocation
|
||||
|
||||
S.KitQty = OCONV(SUM(KitData<2>) * 25,'MD0,Z')
|
||||
I.KitQty = S.KitQty
|
||||
|
||||
S.KitCassCnt = COUNT(KitData<3>,',') + (KitData<3> NE '')
|
||||
I.KitCassCnt = S.KitCassCnt
|
||||
|
||||
StageData = obj_Location('StageLocations',S.WONo)
|
||||
|
||||
SWAP CRLF$ WITH @VM IN StageData
|
||||
|
||||
S.StageLocation = StageData<1>
|
||||
I.StageLocation = S.StageLocation
|
||||
|
||||
S.StageQty = StageData<3>
|
||||
I.StageQty = S.StageQty
|
||||
|
||||
S.StageCassCnt = COUNT(S.StageQty,',') + (S.StageQty NE '')
|
||||
I.StageCassCnt = S.StageCassCnt
|
||||
|
||||
PTIData = obj_Location('PTILocations',S.WONo)
|
||||
|
||||
SWAP CRLF$ WITH @VM IN PTIData
|
||||
|
||||
S.PTILocation = PTIData<1>
|
||||
I.PTILocation = S.PTILocation
|
||||
|
||||
S.PTIQty = PTIData<3>
|
||||
I.PTIQty = S.PTIQty
|
||||
|
||||
S.PTICassCnt = COUNT(S.PTIQty,',') + (S.PTIQty NE '')
|
||||
I.PTICassCnt = S.PTICassCnt
|
||||
|
||||
CassQueueCnt = I.KitCassCnt + I.StageCassCnt + I.PTICassCnt
|
||||
|
||||
* TEST FOR CONTROL BREAK(S)
|
||||
|
||||
IF (S.ReactNo NE Prev.ReactNo) OR ReactNo.Break THEN
|
||||
ReactNo = Prev.ReactNo
|
||||
Prev.ReactNo = S.ReactNo
|
||||
ReactNo.Break += 1
|
||||
END
|
||||
|
||||
IF FirstPass THEN
|
||||
FirstPass=0
|
||||
GOTO DETAIL
|
||||
END
|
||||
|
||||
* * * * * * *
|
||||
BREAKS:
|
||||
* * * * * * *
|
||||
|
||||
* Print Break Total(s) And Accumulate Total(s)
|
||||
|
||||
IF ReactNo.Break THEN
|
||||
|
||||
IF ReportParm = 'D' ELSE
|
||||
stat = Set_Printer('TEXT')
|
||||
END
|
||||
|
||||
END
|
||||
|
||||
|
||||
* Perform Last Record Output If Done
|
||||
|
||||
IF LastRecord THEN
|
||||
|
||||
colData = ''
|
||||
|
||||
|
||||
GOTO Bail
|
||||
|
||||
END
|
||||
|
||||
|
||||
* * * * * * *
|
||||
DETAIL:
|
||||
* * * * * * *
|
||||
|
||||
* Do Conversion If Any
|
||||
|
||||
IF ReportParm = 'T' OR CassQueueCnt < MinDemand THEN
|
||||
|
||||
IF S.REACTNO NE "" THEN S.REACTNO = OCONV(S.REACTNO,"MD0,")
|
||||
IF S.WONO NE "" THEN S.WONO = OCONV(S.WONO,"MD0")
|
||||
IF S.WO_QTY NE "" THEN S.WO_QTY = OCONV(S.WO_QTY,"MD0,")
|
||||
IF S.WO_RX_QTY NE "" THEN S.WO_RX_QTY = OCONV(S.WO_RX_QTY,"MD0,")
|
||||
IF S.WO_UNREL_QTY NE "" THEN S.WO_UNREL_QTY = OCONV(S.WO_UNREL_QTY,"MD0,")
|
||||
IF S.SCHED_DT NE "" THEN S.SCHED_DT = OCONV(S.SCHED_DT,"D4/")
|
||||
|
||||
* PRINT DETAIL LINE
|
||||
|
||||
COLDATA = ''
|
||||
RowNumber = 0
|
||||
CassList = ''
|
||||
|
||||
For each Location in S.PTILocation using @VM setting fPos
|
||||
LocationCassNos = S.PTIQty<0, fPos>
|
||||
If S.React_Type NE 'EPP' then
|
||||
For each CassNo in LocationCassNos using ','
|
||||
WOMatKey = S.WONO:'*':CassNo
|
||||
CurrStatus = Xlate('WO_MAT', WOMatKey, 'CURR_STATUS', 'X')
|
||||
If ( (CurrStatus EQ 'VER') OR (CurrStatus EQ 'LOAD') OR (CurrStatus EQ 'REL') ) then
|
||||
* If ( (CurrStatus EQ 'VER') ) then
|
||||
CassList = Insert(CassList, 0, -1, 0, CassNo)
|
||||
end
|
||||
Next CassNo
|
||||
end else
|
||||
CassList = Insert(CassList, 0, -1, 0, LocationCassNos)
|
||||
end
|
||||
Next Location
|
||||
|
||||
If CassList NE '' then
|
||||
RowNumber += 1
|
||||
Convert @VM to ',' in CassList
|
||||
COLDATA<RowNumber,1> = S.ReactNo
|
||||
COLDATA<RowNumber,2> = S.React_Type
|
||||
COLDATA<RowNumber,3> = S.Wafer_Size
|
||||
COLDATA<RowNumber,4> = S.WoNo
|
||||
SWAP '.1' WITH '' IN S.ProdOrdNo
|
||||
COLDATA<RowNumber,5> = S.ProdOrdNo
|
||||
COLDATA<RowNumber,6> = S.SubPartNo
|
||||
ColData<RowNumber,7> = S.EpiPartNo
|
||||
COLDATA<RowNumber,8> = S.WO_Qty
|
||||
COLDATA<RowNumber,9> = S.WO_RX_Qty
|
||||
COLDATA<RowNumber,10> = S.WO_UnRel_Qty
|
||||
COLDATA<RowNumber,11> = S.KitLocation
|
||||
COLDATA<RowNumber,12> = S.KitQty
|
||||
COLDATA<RowNumber,13> = S.PTILocation<0, fPos>
|
||||
COLDATA<RowNumber,14> = CassList
|
||||
|
||||
If COLDATA NE '' then GoSub PrintTable
|
||||
END
|
||||
END
|
||||
|
||||
GOTO ReadRecord
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Bail:
|
||||
* * * * * * *
|
||||
|
||||
stat = Set_Printer('TERM',1)
|
||||
SRP_Stopwatch('Stop', 'Build Report')
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
OIPrintErr:
|
||||
* * * * * * *
|
||||
|
||||
ErrMsg(ErrorTitle:@SVM:ErrorMsg)
|
||||
ErrMsg(ErrorTitle:@SVM:'Set_Printer returned errorcode ':stat)
|
||||
stat = Set_Printer('TERM',1)
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * *
|
||||
PrintTable:
|
||||
* * * * * *
|
||||
|
||||
PageHeight = Get_Printer('PAGESIZE')<2>
|
||||
PrintableHeight = PageHeight - TopMargin - BottomMargin
|
||||
PrinterHeight = Get_Printer('POS')<2>
|
||||
|
||||
stat = Set_Printer('CALCTABLE',ColFmt:@FM:ColData)
|
||||
TableSize = Get_Printer('CALCTABLE')
|
||||
|
||||
|
||||
TableHeight = TableSize<2>
|
||||
|
||||
fontSpacing = 120
|
||||
|
||||
IF ( TableHeight + PrinterHeight >= PrintableHeight ) OR FirstLine THEN
|
||||
IF NOT(FirstLine) THEN
|
||||
stat = Set_Printer('PAGEBREAK')
|
||||
END
|
||||
FirstLine = 0
|
||||
font<2> = 10
|
||||
font<4> = 1 ;* Bold
|
||||
stat = Set_Printer('FONT',font,'100')
|
||||
|
||||
stat = Set_Printer('ADDTABLE',colFmt,colHead,'',LTGREY$,'',0,TB_ALL)
|
||||
|
||||
|
||||
font<4> = 0
|
||||
stat = Set_Printer('FONT',font,fontSpacing)
|
||||
|
||||
stat = Set_Printer('ADDTABLE',colFmt,'',colData,LTGREY$,'',0,7)
|
||||
|
||||
END ELSE
|
||||
font<2> = 10
|
||||
font<4> = 0
|
||||
stat = Set_Printer('FONT',font,fontSpacing)
|
||||
stat = Set_Printer('ADDTABLE',colFmt,'',colData,LTGREY$,'',1,TB_ALL)
|
||||
|
||||
END
|
||||
|
||||
|
||||
RETURN
|
Reference in New Issue
Block a user