open-insight/LSL2/STPROC/PRINT_BLISS_RPT.txt
Infineon\StieberD 7762b129af pre cutover push
2024-09-04 20:33:41 -07:00

493 lines
14 KiB
Plaintext

COMPILE SUBROUTINE Print_BLISS_Rpt(Dummy)
DECLARE FUNCTION Msg, set_property, send_event, dialog_box, Utility, get_property
DECLARE FUNCTION Set_Printer, FieldCount, Printer_Select, Get_Printer, obj_RDS2, obj_WM_In, obj_WM_Out
DECLARE SUBROUTINE RList, ErrMsg, Msg
/*
Report rewritten 07/08/2005 John C. Henry, J.C. Henry & Co., Inc.
*/
$INSERT RLIST_EQUATES
$INSERT LOGICAL
$INSERT MSG_EQUATES
$INSERT OIPRINT_EQUATES
$INSERT WO_LOG_EQU
$INSERT WO_MAT_EQUATES
$INSERT WM_OUT_EQUATES
$INSERT WM_IN_EQUATES
$INSERT APPCOLORS
EQU DAY1$ TO 1 ;* Columns for the date total buckets
EQU DAY2$ TO 2
EQU DAY3$ TO 3
EQU WEEK1$ TO 4
EQU WEEK2$ TO 5
EQU WEEK3$ TO 6
EQU WEEK4$ TO 7
OPEN 'WO_MAT' to WOMatTable ELSE
Msg( '', 'Unable to open WO_MAT' )
RETURN
END
*OPEN 'DICT.RDS' to DictRDSTable ELSE
* Msg( '', 'Unable to open DICT_RDS' )
* RETURN
*END
Void = Utility( 'CURSOR', 'H' )
*Stmt = 'SELECT WO_LOG WITH STATUS = "O" BY CUST_NAME BY PROD_SPEC_ID'
Stmt = 'SELECT WO_MAT WITH CURR_STATUS = "RX" "REL" "PREC" "INF" "BLD" "PSTC" "RQA" "RTS" "COMP" "HOLD" "RTU" BY CUST_NAME BY SHIP_PSN'
RList( Stmt, target_activelist$, '', '', '' )
IF Get_Status(errCode) THEN
ErrMsg(errCode)
END
colHdr = '' ; colFmt = ''
colHdr<1,1> = 'Customer' ; colFmt<1,1> = '<+1800'
colHdr<1,2> = 'PSN' ; colFmt<1,2> = '>+806'
colHdr<1,3> = 'Thk' ; colFmt<1,3> = '>+806'
colHdr<1,4> = '' ; colFmt<1,4> = '>+9' ;* Dummy columns to give the fat line separators
colHdr<1,5> = '' ; colFmt<1,5> = '>+9'
colHdr<1,6> = '' ; colFmt<1,6> = '>+9'
colHdr<1,7> = 'Rec' ; colFmt<1,7> = '>+806'
colHdr<1,8> = 'Pre' ; colFmt<1,8> = '>+806'
colHdr<1,9> = 'In' ; colFmt<1,9> = '>+806'
colHdr<1,10> = 'Post' ; colFmt<1,10> = '>+806'
colHdr<1,11> = 'Ready' ; colFmt<1,11> = '>+806'
colHdr<1,12> = 'Hold' ; colFmt<1,12> = '>+806'
colHdr<1,13> = 'Makeup' ; colFmt<1,13> = '>+806'
colHdr<1,14> = '' ; colFmt<1,14> = '>+9' ;* Dummy columns to give the fat line separators
colHdr<1,15> = '' ; colFmt<1,15> = '>+9'
colHdr<1,16> = '' ; colFmt<1,16> = '>+9'
colHdr<1,17> = 'Today' ; colFmt<1,17> = '>+806'
colHdr<1,18> = 'Day 2' ; colFmt<1,18> = '>+806'
colHdr<1,19> = 'Day 3' ; colFmt<1,19> = '>+806'
colHdr<1,20> = 'Remain Week1' ; colFmt<1,20> = '>+806'
colHdr<1,21> = 'Week2' ; colFmt<1,21> = '>+806'
colHdr<1,22> = 'Week3' ; colFmt<1,22> = '>+806'
colHdr<1,23> = 'Wk4->' ; colFmt<1,23> = '>+806'
SpaceOut = str( ' ', 17 )
SpaceOut2 = str( ' ', 20 )
PrintPath = Printer_Select('',1) ;* Get default printer path
Void = Set_Printer( 'INIT', '', '', .38:@fm:.75:@fm:.38:@fm:.75, 1, 3:@vm:'':@vm:'':@vm:2:@fm:96, PrintPath )
Void = Utility( 'CURSOR', 'H' )
Font = "Courier New,8,L,1"
convert ',' to @fm in Font
TFont = font
TFont<2> = 12
Void = Set_Printer( 'FONTHEADFOOT', TFont )
Header = "Page 'P'":@VM:"'BLISS'"
Header<2> = "'D' 'T'":SpaceOut:"Inventory report":SpaceOut2:"Demand/Schedule"
Void = Set_Printer( 'HEADER',Header)
TFont<2> = 8
TFont<4> = 0
Void = Set_Printer( 'FONT', TFont )
* Set Up Break Totals
* PSN Break totals
ReceivedQty_PSN_Tot = 0
PreEpiQty_PSN_Tot = 0
InProcessQty_PSN_Tot = 0
PostEpiQty_PSN_Tot = 0
ReadyToShipQty_PSN_Tot = 0
HoldQty_PSN_Tot = 0
MakeupQty_PSN_Tot = 0
DateArray_PSN_Tot = ''
DateArray_PSN_Tot<DAY1$> = 0
DateArray_PSN_Tot<DAY2$> = 0
DateArray_PSN_Tot<DAY3$> = 0
DateArray_PSN_Tot<WEEK1$> = 0
DateArray_PSN_Tot<WEEK2$> = 0
DateArray_PSN_Tot<WEEK3$> = 0
DateArray_PSN_Tot<WEEK4$> = 0
* Report Grand Totals
ReceivedQty_Grand_Tot = 0
PreEpiQty_Grand_Tot = 0
InProcessQty_Grand_Tot = 0
PostEpiQty_Grand_Tot = 0
ReadyToShipQty_Grand_Tot = 0
HoldQty_Grand_Tot = 0
MakeupQty_Grand_Tot = 0
DateArray_Grand_Tot = ''
DateArray_Grand_Tot<DAY1$> = 0
DateArray_Grand_Tot<DAY2$> = 0
DateArray_Grand_Tot<DAY3$> = 0
DateArray_Grand_Tot<WEEK1$> = 0
DateArray_Grand_Tot<WEEK2$> = 0
DateArray_Grand_Tot<WEEK3$> = 0
DateArray_Grand_Tot<WEEK4$> = 0
* Build Date Locator array (defines date buckets)
Today = date()
DateLocatorArray = Today ;* Today
DateLocatorArray<2> = Today+1 ;* Tommorrow
DateLocatorArray<3> = Today+2 ;* Day after tommorrow
DateLocatorArray<4> = Today+6 ;* Days 3 thru 7
DateLocatorArray<5> = Today+13 ;* Next week
DateLocatorArray<6> = Today+20 ;* Week after next
DateLocatorArray<7> = Today+9999 ;* Rest of the next 30 years
ThisPSN = ''
OrigPSN = ''
* Baby, this thing gives me GAS gauge
Def = ''
Def<MCAPTION$> = 'Building BLISS Report...'
Def<MTYPE$> = 'G'
Def<MEXTENT$> = @RECCOUNT
Def<MTEXTWIDTH$> = 600
MsgUp = Msg(@WINDOW,Def)
FirstLine = 1
Done = 0
ReadCnt = 0
MakeupBoxes = ''
LOOP
READNEXT WOMatKey ELSE Done = 1
UNTIL Done
READ WOMatRec FROM WOMatTable, WOMatKey ELSE
Msg(@WINDOW,MsgUp)
Msg( '', 'Unable to read ':WOMatKey:' from WO_MAT Table...' )
RETURN
END
ReadCnt += 1
Msg(@WINDOW, MsgUp, ReadCnt, MSGINSTUPDATE$) ;* Updates the gas gauge
WOStepKey = XLATE('WO_LOG',WOMatKey[1,'*'],WO_LOG_WO_STEP_KEY$,'X')
IF INDEX(WOStepKey,@VM,1) THEN
WOStepKey = FIELD(WOStepKey,@VM,2)
END
ThisPSN = XLATE('WO_STEP',WOStepKey,1,'X')
IF ( ThisPSN <> OrigPSN ) AND ( OrigPSN <> '' ) THEN
GOSUB PrintPSNLine
END
OrigPSN = ThisPSN
WafersOnHand = 0
ReceivedQty = 0
PreEpiQty = 0
InProcessQty = 0
PostEpiQty = 0
ReadyToShipQty = 0
HoldQty = 0
MakeupQty = 0
RepStatuses = XLATE('WO_MAT',WOMatKey,'REP_STATUS','X')
RepWfrCnts = XLATE('WO_MAT',WOMatKey,'REP_CURR_WFR_CNT','X')
CurrStatus = XLATE('WO_MAT',WOMatKEy,'CURR_STATUS','X')
IF INDEX(RepStatuses,@VM,1) THEN RepCnt = 2 ELSE RepCnt =1
FOR I = 1 TO RepCnt
RepStatus = TRIM(RepStatuses<1,I>)
RepWfrCnt = RepWfrCnts<1,I>
BEGIN CASE
CASE CurrStatus = 'RX' ; Bucket = 'RECVD'
CASE INDEX(RepStatus,'Hold',1) ; Bucket = 'HOLD'
CASE INDEX(RepStatus,'M/U',1) ; Bucket = 'MAKEUP'
CASE RepStatus = 'ASM - In Fab - Loaded' ; Bucket = 'INPROCESS'
CASE RepStatus = 'ASM - In Fab - QA Complete' ; Bucket = 'SHIP'
CASE RepStatus = 'ASM - In Fab - Ready for QA' ; Bucket = 'POST'
CASE RepStatus = 'ASM - In Fab - Ready to Load' ; Bucket = 'PRE'
CASE RepStatus = 'ASM - In Fab - Ready to Post Clean' ; Bucket = 'POST'
CASE RepStatus = 'ASM - In Fab - Ready to Start' ; Bucket = 'PRE'
CASE RepStatus = 'ASM - Ready to Ship - QA Complete' ; Bucket = 'SHIP'
CASE RepStatus = 'WMI - Ready to Pre Clean' ; Bucket = 'PRE'
CASE RepStatus = 'WMI - Ready to Use' ; Bucket = 'PRE'
CASE RepStatus = 'WMO - Building' ; Bucket = 'POST'
CASE RepStatus = 'WMO - Ready for QA' ; Bucket = 'POST'
CASE RepStatus = 'WMO - Ready to Post Clean' ; Bucket = 'POST'
CASE RepStatus = 'WMO - QA Complete' ; Bucket = 'SHIP'
CASE RepStatus = 'WMO - Ready to Ship' ; Bucket = 'SHIP'
CASE 1 ; Bucket = ''
END CASE
BEGIN CASE
CASE Bucket = 'RECVD'
ReceivedQty += RepWfrCnt
WafersOnHand += RepWfrCnt
CASE Bucket = 'HOLD'
HoldQty += RepWfrCnt
WafersOnHand += RepWfrCnt
CASE Bucket = 'MAKEUP'
MakeupQty += RepWfrCnt
*WafersOnHand += RepWfrCnt
CASE Bucket = 'INPROCESS'
InProcessQty += RepWfrCnt
WafersOnHand += RepWfrCnt
CASE Bucket = 'SHIP'
ReadyToShipQty += RepWfrCnt
WafersOnHand += RepWfrCnt
CASE Bucket = 'PRE'
PreEpiQty += RepWfrCnt
WafersOnHand += RepWfrCnt
CASE Bucket = 'POST'
PostEpiQty += RepWfrCnt
WafersOnHand += RepWfrCnt
END CASE
NEXT I
HoldQty_PSN_Tot += HoldQty
ReceivedQty_PSN_Tot += ReceivedQty
PreEpiQty_PSN_Tot += PreEpiQty
InProcessQty_PSN_Tot += InProcessQty
PostEpiQty_PSN_Tot += PostEpiQty
ReadyToShipQty_PSN_Tot += ReadyToShipQty
MakeupQty_PSN_Tot += MakeupQty
* Got the status total now update the daily/weekly totals
WONo = WOStepKey[1,'*']
CommitDate = XLATE('WO_LOG',WONo,WO_LOG_PROMISE_SHIP_DT$,'X')
LOCATE CommitDate IN DateLocatorArray BY 'AR' USING @FM SETTING DateCol THEN Null
DateArray_PSN_Tot<DateCol> = DateArray_PSN_Tot<DateCol> + WafersOnHand
REPEAT
Msg(@WINDOW,MsgUp) ;* Take down the gas gauge
GOSUB PrintPSNLine
* Print the total line at the bottom of the report
TotInFab_Grand_Tot = ReceivedQty_Grand_Tot + PreEpiQty_Grand_Tot + InProcessQty_Grand_Tot + PostEpiQty_Grand_Tot + ReadyToShipQty_Grand_Tot
TotInFab_Grand_Tot += MakeupQty_Grand_Tot
TFont<4> = 1
Void = Set_Printer( 'FONT', TFont )
colData = ''
colData<1,1> = 'Totals:'
colData<1,2> = 'NA'
colData<1,3> = 'NA'
colData<1,4> = '' ;* Dummy column
colData<1,5> = ''
colData<1,6> = ''
colData<1,7> = OCONV(ReceivedQty_Grand_Tot,'MD0,')
colData<1,8> = OCONV(PreEpiQty_Grand_Tot,'MD0,')
colData<1,9> = OCONV(InProcessQty_Grand_Tot,'MD0,')
colData<1,10> = OCONV(PostEpiQty_Grand_Tot,'MD0,')
colData<1,11> = OCONV(ReadyToShipQty_Grand_Tot,'MD0,')
colData<1,12> = OCONV(HoldQty_Grand_Tot,'MD0,')
colData<1,13> = OCONV(MakeupQty_Grand_Tot,'MD0,')
colData<1,14> = '' ;* Dummy column
colData<1,15> = ''
colData<1,16> = ''
colData<1,17> = OCONV(DateArray_Grand_Tot<DAY1$>,'MD0,')
colData<1,18> = OCONV(DateArray_Grand_Tot<DAY2$>,'MD0,')
colData<1,19> = OCONV(DateArray_Grand_Tot<DAY3$>,'MD0,')
colData<1,20> = OCONV(DateArray_Grand_Tot<WEEK1$>,'MD0,')
colData<1,21> = OCONV(DateArray_Grand_Tot<WEEK2$>,'MD0,')
colData<1,22> = OCONV(DateArray_Grand_Tot<WEEK3$>,'MD0,')
colData<1,23> = OCONV(DateArray_Grand_Tot<WEEK4$>,'MD0,')
GOSUB PrintTable
Void = Utility( 'CURSOR', 'A' )
Void = Set_Printer( 'TERM', 1 )
RETURN
* * * * * * *
PrintPSNLine:
* * * * * * *
* Do printing logic for the OrigPSN
* Set all variables to null
Customer = XLATE( 'PROD_SPEC', OrigPSN, 'ABBREV_OR_CO_NAME', 'X' )
Thickness = OCONV( XLATE( 'PROD_SPEC', OrigPSN, 'THICK_TARGET_L1', 'X' ), 'MD2' )
IF ( sum( DateArray_PSN_Tot ) NE 0 ) OR ( ( HoldQty_PSN_Tot + ReceivedQty_PSN_Tot + PreEpiQty_PSN_Tot + InProcessQty_PSN_Tot + PostEpiQty_PSN_Tot + ReadyToShipQty_PSN_Tot ) NE 0 ) THEN
TotInFab_PSN_Tot = ReceivedQty_PSN_Tot + PreEpiQty_PSN_Tot + InProcessQty_PSN_Tot + PostEpiQty_PSN_Tot + ReadyToShipQty_PSN_Tot
*Makeup_PSN_Tot = OCONV( (( TotInFab_PSN_Tot - ReadyToShipQty_PSN_Tot )*.99), 'MD0' )
*Makeup_PSN_Tot += ReadyToShipQty_PSN_Tot
colData = ''
colData<1,1> = Customer
colData<1,2> = OrigPSN
colData<1,3> = Thickness
colData<1,4> = '' ;* Dummy column
colData<1,5> = ''
colData<1,6> = ''
colData<1,7> = OCONV(ReceivedQty_PSN_Tot,'MD0,')
colData<1,8> = OCONV(PreEpiQty_PSN_Tot,'MD0,')
colData<1,9> = OCONV(InProcessQty_PSN_Tot,'MD0,')
colData<1,10> = OCONV(PostEpiQty_PSN_Tot, 'MD0,')
colData<1,11> = OCONV(ReadyToShipQty_PSN_Tot,'MD0,')
colData<1,12> = OCONV(HoldQty_PSN_Tot,'MD0,')
colData<1,13> = OCONV(MakeupQty_PSN_Tot,'MD0,')
colData<1,14> = '' ;* Dummy column
colData<1,15> = ''
colData<1,16> = ''
colData<1,17> = OCONV(DateArray_PSN_Tot<DAY1$>,'MD0,')
colData<1,18> = OCONV(DateArray_PSN_Tot<DAY2$>,'MD0,')
colData<1,19> = OCONV(DateArray_PSN_Tot<DAY3$>,'MD0,')
colData<1,20> = OCONV(DateArray_PSN_Tot<WEEK1$>,'MD0,')
colData<1,21> = OCONV(DateArray_PSN_Tot<WEEK2$>,'MD0,')
colData<1,22> = OCONV(DateArray_PSN_Tot<WEEK3$>,'MD0,')
colData<1,23> = OCONV(DateArray_PSN_Tot<WEEK4$>,'MD0,')
GOSUB PrintTable
END
* Add PSN Level Totals to the Report Grand Totals
DateArray_Grand_Tot = DateArray_Grand_Tot +++ DateArray_PSN_Tot
ReceivedQty_Grand_Tot += ReceivedQty_PSN_Tot
PreEpiQty_Grand_Tot += PreEpiQty_PSN_Tot
InProcessQty_Grand_Tot += InProcessQty_PSN_Tot
PostEpiQty_Grand_Tot += PostEpiQty_PSN_Tot
ReadyToShipQty_Grand_Tot += ReadyToShipQty_PSN_Tot
HoldQty_Grand_Tot += HoldQty_PSN_Tot
MakeupQty_Grand_Tot += MakeupQty_PSN_Tot
* And then reset PSN level totals
ReceivedQty_PSN_Tot = 0
PreEpiQty_PSN_Tot = 0
InProcessQty_PSN_Tot = 0
PostEpiQty_PSN_Tot = 0
ReadyToShipQty_PSN_Tot = 0
HoldQty_PSN_Tot = 0
MakeupQty_PSN_Tot = 0
DateArray_PSN_Tot<DAY1$> = 0
DateArray_PSN_Tot<DAY2$> = 0
DateArray_PSN_Tot<DAY3$> = 0
DateArray_PSN_Tot<WEEK1$> = 0
DateArray_PSN_Tot<WEEK2$> = 0
DateArray_PSN_Tot<WEEK3$> = 0
DateArray_PSN_Tot<WEEK4$> = 0
RETURN
* * * * * * *
Bail:
* * * * * * *
stat = Set_Printer('TERM',1)
RETURN
* * * * * * *
OIPrintErr:
* * * * * * *
ErrMsg(ErrorTitle:@SVM:ErrorMsg)
ErrMsg(ErrorTitle:@SVM:'Set_Printer returned errorcode ':stat)
stat = Set_Printer('TERM',1)
RETURN
* * * * * *
PrintTable:
* * * * * *
stat = Set_Printer('CALCTABLE',colFmt:@FM:colData)
TableSize = Get_Printer('CALCTABLE')
TableHeight = TableSize<2>
Test = Get_Printer('POS')<2>
fontSpacing = 150
IF Get_Printer('POS')<2> + TableHeight > 7.0 OR FirstLine THEN
IF NOT(FirstLine) THEN
stat = Set_Printer('PAGEBREAK')
END
FirstLine = 0
font<2> = 8
font<4> = 1 ;* Bold
stat = Set_Printer('FONT',font,'100')
stat = Set_Printer('ADDTABLE',colFmt,colHdr,'',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> = 8
font<4> = 0
stat = Set_Printer('FONT',font,fontSpacing)
stat = Set_Printer('ADDTABLE',colFmt,'',colData,LTGREY$,'',1,TB_ALL)
END
RETURN