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

484 lines
11 KiB
Plaintext

COMPILE ROUTINE BUILD_SAP_COMM_DATA(Dummy)
ROWDEF(CHARSTR)
DECLARE SUBROUTINE ErrMsg, Send_Info, SetInitDirOptions, Send_Dyn, Set_Status
DECLARE FUNCTION Get_Status,Security_Check, Set_Status
DECLARE FUNCTION Repository, Send_Dyn
$INSERT WO_LOG_EQUATES
$INSERT WO_MAT_EQUATES
$INSERT PART_EQUATES
$INSERT COC_EQUATES
EQU CRLF$ TO \0D0A\
EQU TAB$ TO \09\
* Build Inbound Production Order records
CurrPath = Drive()
dummy = CurrPath[-1,'B\'] ;* Position of OpenInsight directory
CurrPath = CurrPath[1,COL1()] ;* Path to level above OI directory
InBufferPath = CurrPath:'SAPComm\FromSAP\'
OutBufferPath = CurrPath:'SAPComm\ToSAP\'
OutBoundDirs = 'WOCreate':@FM
OutBoundDirs := 'PromiseDt':@FM
OutBoundDirs := 'WfrReject':@FM
OutBoundDirs := 'CustTW':@FM
OutBoundDirs := 'MUWafer':@FM
OutBoundDirs := 'ProdTW':@FM
OutBoundDirs := 'WOHold':@FM
OutBoundDirs := 'WOStart':@FM
OutBoundDirs := 'WOStop'
WONos = 148411:@FM ;* EpiPro
WONos := 148406:@FM ;* Delphi 2 step 40 boxes
WONos := 148381 ;* Captive
WOCnt = COUNT(WONos,@FM) + (WONos NE '')
ProdOrdSeq = 1
FOR I = 1 TO WOCnt
WONo = WONos<I>
WORec = XLATE('WO_LOG',WONo,'','X')
OrderNo = WORec<WO_LOG_ORDER_NO$>
CustPONo = XLATE('ORDER',OrderNo,41,'X') ;* 41 is PO_NO field
WORelRec = ''
GoodsRecRec = ''
ShipDocRec = ''
CloseOrdRec = ''
ProdOrdNo = 'M':FMT(ProdOrdSeq, "R(0)#6"):'.1'
WOMatKeys = WORec<WO_LOG_WO_MAT_KEY$>
Pos = 1
LOOP
REMOVE WOMatKey FROM WOMatKeys AT Pos SETTING Flag
WHILE Flag
CassNo = WOMatKey[-1,'B*']
WOMatRec = XLATE('WO_MAT',WOMatKey,'','X')
PartNo = XLATE('WO_MAT',WOMatKey,'PART_NO_SAP','X')
WORelLine = ProdOrdNo ;* Production Order No
WORelLine<1,2> = CustPONo ;* Customer PO No
WORelLine<1,3> = OCONV(WORec<WO_LOG_PROMISE_SHIP_DT$>,'D4/') ;* Promise Ship Dt
WORelLine<1,4> = PartNo ;* Mesa Part No
WORelLine<1,5> = WOMatRec<WO_MAT_SUB_PART_NO$> ;* Substrate Part No
WORelLine<1,6> = '{Substrate Revision No}' ;* Replace {Substrate Revision No} from SAP
WORelLine<1,7> = WORec<WO_LOG_WO_QTY$> ;* Total Prod Order wafer qty
WORelRec<-1> = WORelLine
ShipDocLine = ProdOrdNo ;* Production Order No
ShipDocLine<1,2> = '{SAP Ship No}' ;* Replace {SAP Ship No} with SAP Shipment No
ShipDocLine<1,3> = CassNo ;* Cassette number
ShipDocLine<1,4> = '{SAP Batch No}' ;* Replace {SAP Batch No} with SAP Batch No
ShipDocRec<-1> = ShipDocLine
GoodsRecLine = ProdOrdNo ;* Production Order No
GoodsRecLine<1,2> = CassNo ;* Cassette number
GoodsRecLine<1,3> = '{SAP Batch No}' ;* SAP Batch No
GoodsRecLine<1,4> = WOMatRec<WO_MAT_LOT_NO$> ;* Cassette Substrate Lot No
GoodsRecRec<-1> = GoodsRecLine
Send_Dyn(ProdOrdNo:' -> ':WOMatKey)
REPEAT
ProdOrdCloseFlag = 1
ProdOrdRec = ProdOrdNo:@VM:ProdOrdCloseFlag
PartRec = XLATE('PART',PartNo,'','X')
InPartRec = PartNo
InPartRec<1,2> = PartRec<PART_DESC$>
InPartRec<1,3> = PartRec<PART_CUST_NO$>
InPartRec<1,4> = XLATE('PART',PartNo,'CUST_NAME','X')
InPartRec<1,5> = XLATE('PART',PartNo,'CUST_TYPE','X')
InPartRec<1,6> = PartRec<PART_CUST_PART_NO$>
InPartRec<1,7> = PartRec<PART_SUB_PART_NO$>
InPartRec<1,8> = PartRec<PART_SUB_TYPE$>
InPartRec<1,9> = PartRec<PART_SUB_SUPPLIER$>
InPartRec<1,10> = PartRec<PART_PURCH_SPEC$>
InPartRec<1,11> = PartRec<PART_PURCH_SPEC_REV$>
InPartRec<1,12> = PartRec<PART_REACT_TYPE$>
* * * * Write Work Order Release * * * *
SWAP @FM WITH CRLF$ IN WORelRec
SWAP @VM WITH TAB$ IN WORelRec
FullPath = InBufferPath:'ProdOrdRel\'
FileName = 'PR':FMT(ProdOrdSeq,"R(0)#5"):'.tsv'
Set_Status(0)
OSWRITE WORelRec TO FullPath:FileName
* * * * Write Goods Receipt * * * *
SWAP @FM WITH CRLF$ IN GoodsRecRec
SWAP @VM WITH TAB$ IN GoodsRecRec
FullPath = InBufferPath:'GoodsRec\'
FileName = 'GR':FMT(ProdOrdSeq,"R(0)#5"):'.tsv'
Set_Status(0)
OSWRITE GoodsRecRec TO FullPath:FileName
* * * * Write Shipping Document Request * * * *
SWAP @FM WITH CRLF$ IN ShipDocRec
SWAP @VM WITH TAB$ IN ShipDocRec
FullPath = InBufferPath:'ShipDoc\'
FileName = 'SD':FMT(ProdOrdSeq,"R(0)#5"):'.tsv'
Set_Status(0)
OSWRITE ShipDocRec TO FullPath:FileName
* * * * Write Order Close * * * *
SWAP @FM WITH CRLF$ IN ProdOrdRec
SWAP @VM WITH TAB$ IN ProdOrdRec
FullPath = InBufferPath:'CloseOrder\'
FileName = 'OC':FMT(ProdOrdSeq,"R(0)#5"):'.tsv'
Set_Status(0)
OSWRITE ProdOrdRec TO FullPath:FileName
* * * * Write Part No * * * *
SWAP @FM WITH CRLF$ IN InPartRec
SWAP @VM WITH TAB$ IN InPartRec
FullPath = InBufferPath:'PartNo\'
FileName = 'PN':FMT(ProdOrdSeq,"R(0)#5"):'.tsv'
Set_Status(0)
OSWRITE InPartRec TO FullPath:FileName
FOR D = 1 TO 10
OutBoundDir = OutBoundDirs<D>
BEGIN CASE
CASE OutBoundDir = 'WOCreate'
FullPath = OutBufferPath:OutBoundDir:'\'
FileName = 'WOK':FMT(ProdOrdSeq,"R(0)#5"):'.tsv'
OutRec = ProdOrdNo:TAB$:WONo:TAB$:'1':CRLF$
Set_Status(0)
OSWRITE OutRec TO FullPath:FileName
CASE OutBoundDir = 'PromiseDt'
FullPath = OutBufferPath:OutBoundDir:'\'
FileName = 'PD':FMT(ProdOrdSeq,"R(0)#5"):'.tsv'
OutRec = ProdOrdNo:TAB$:OCONV(Date(),'D4/'):TAB$:OCONV(Date() + 10,'D4/'):CRLF$
Set_Status(0)
OSWRITE OutRec TO FullPath:FileName
*****************************************************************************
* Inventory to Scrap WIP Prod Ord No : Qty (+/-) + => From WIP to Scrap, - => From Scrap to WIP
CASE OutBoundDir = 'WfrReject'
FullPath = OutBufferPath:OutBoundDir:'\'
FileName = 'WR':FMT(ProdOrdSeq,"R(0)#5"):'.tsv'
IF ProdOrdSeq = 1 THEN TestQty = '+3' ;* Remove from Production
IF ProdOrdSeq = 2 THEN TestQty = '-13' ;* Add to Production (cancelled NCR)
IF ProdOrdSeq = 3 THEN TestQty = '+25'
OutRec = ProdOrdNo:TAB$:TestQty:CRLF$
Set_Status(0)
OSWRITE OutRec TO FullPath:FileName
CASE OutBoundDir = 'ProdTW'
FullPath = OutBufferPath:OutBoundDir:'\'
FileName = 'PT':FMT(ProdOrdSeq,"R(0)#5"):'.tsv'
IF ProdOrdSeq = 1 THEN UseQty = '+1' ;* This is a usage in production
IF ProdOrdSeq = 2 THEN UseQty = '-1' ;* This is a return from production to WIP
IF ProdOrdSeq = 3 THEN UseQty = '+2'
OutRec = ProdOrdNo:TAB$:UseQty:CRLF$
Set_Status(0)
OSWRITE OutRec TO FullPath:FileName
************************************************************************************
* Inventory Move transactions WIP Prod Ord No : MU Prod Ord NO : Qty (+/-) + => From WIP to MU, - => From MU to WIP
CASE OutBoundDir = 'CustTW'
FullPath = OutBufferPath:OutBoundDir:'\'
FileName = 'CT':FMT(ProdOrdSeq,"R(0)#5"):'.tsv'
IF ProdOrdSeq = 1 THEN UseQty = '+1' ;* This is a usage in production
IF ProdOrdSeq = 2 THEN UseQty = '-1' ;*This is a return from production to Cust Test Wafer Inentory
IF ProdOrdSeq = 3 THEN UseQty = '+2'
*OutRec = 'CUST':TAB$:To:TAB$:From:TAB$:Qty
*OutRec = 'MU' :TAB$:To:TAB$:From:TAB$:Qty
OutRec = ProdOrdNo:TAB$:'{Cust TW Part No}':TAB$:UseQty:CRLF$
Set_Status(0)
OSWRITE OutRec TO FullPath:FileName
CASE OutBoundDir = 'MUWafer'
FullPath = OutBufferPath:OutBoundDir:'\'
FileName = 'MW':FMT(ProdOrdSeq,"R(0)#5"):'.tsv'
IF ProdOrdSeq = 1 THEN UseQty = '+3' ;* This is Production to Makeup
IF ProdOrdSeq = 2 THEN UseQty = '-5' ;* This is Unflag box OR use makeup in production cassette
IF ProdOrdSeq = 3 THEN UseQty = '+6'
OutRec = ProdOrdNo:TAB$:'M':FMT(ProdOrdSeq+200, "R(0)#6"):'.1':TAB$:UseQty:CRLF$
Set_Status(0)
OSWRITE OutRec TO FullPath:FileName
CASE OutBoundDir = 'WOHold'
FullPath = OutBufferPath:OutBoundDir:'\'
FileName = 'HLD':FMT(ProdOrdSeq,"R(0)#5"):'.tsv'
IF ProdOrdSeq = 1 THEN Flag = '1' ;* WO Placed on Hold
IF ProdOrdSeq = 2 THEN Flag = '0' ;* WO Removed from Hold
IF ProdOrdSeq = 3 THEN Flag = '1' ;* WO Placed on Hold
OutRec = ProdOrdNo:TAB$:Flag:CRLF$
Set_Status(0)
OSWRITE OutRec TO FullPath:FileName
CASE OutBoundDir = 'WOStart'
FullPath = OutBufferPath:OutBoundDir:'\'
FileName = 'STR':FMT(ProdOrdSeq,"R(0)#5"):'.tsv'
OutRec = ProdOrdNo:TAB$:'1':CRLF$
Set_Status(0)
OSWRITE OutRec TO FullPath:FileName
CASE OutBoundDir = 'WOStop'
FullPath = OutBufferPath:OutBoundDir:'\'
FileName = 'STP':FMT(ProdOrdSeq,"R(0)#5"):'.tsv'
OutRec = ProdOrdNo:TAB$:'1':CRLF$
Set_Status(0)
OSWRITE OutRec TO FullPath:FileName
END CASE
NEXT D
ProdOrdSeq += 1
NEXT I
ShipNos = 97500:@VM:97600:@VM:96100
ShipCnt = 3
FOR I = 1 TO ShipCnt
ShipNo = ShipNos<1,I>
ShipRec = XLATE('COC',ShipNo,'','X')
WONo = ShipRec<COC_WO$>
CassNos = ShipRec<COC_CASS_NO$>
ProdOrdNo = 'M':FMT(WONo, "R(0)#6"):'.1'
CassWfrQtys = XLATE('COC',ShipNo,'CASS_WAFER_CNT','X')
ShipRelease = ''
CassCnt = COUNT(CassNos,@VM) + (CassNos NE '')
FOR Cass = 1 TO CassCnt
ShipRelLine = ShipNos<1,I>
ShipRelLine<1,2> = ProdOrdNo
ShipRelLine<1,3> = WONo
ShipRelLine<1,4> = CassNos<1,Cass>
ShipRelLine<1,5> = 'B':RND(1945)
ShipRelLine<1,6> = CassWfrQtys<1,I>
ShipRelease<-1> = ShipRelLine
NEXT Cass
* * * * Write Work Order Release * * * *
SWAP @FM WITH CRLF$ IN ShipRelease
SWAP @VM WITH TAB$ IN ShipRelease
FullPath = CurrPath:'SAPComm\FromSAP\ShipRel\'
FileName = 'SR':FMT(I,"R(0)#5"):'.tsv'
Set_Status(0)
OSWRITE ShipRelease TO FullPath:FileName
NEXT I
GOTO Bail
CurrPath = Drive()
dummy = CurrPath[-1,'B\'] ;* Position of OpenInsight directory
CurrPath = CurrPath[1,COL1()] ;* Path to level above OI directory
OutBufferPath = CurrPath:'SAPComm\ToSAP\'
InBufferPath = CurrPath:'SAPComm\FromSAP\'
SetInitDirOptions('D-R-H')
InitDir InBufferPath:"*.*"
InFolders = FIELD(DirList(),@FM,3,99)
InFoldCnt = COUNT(Infolders,@FM) + (Infolders NE '')
FOR I = 1 TO InfoldCnt
InFolder = InFolders<I>
InitDir InBufferPath:Infolder:'*.*'
LOOP
FileList = DirList()
UNTIL List = ""
LOOP
FileName = List[1,@FM]
FileList[1,Col2()] = ""
IF FileName[1,3] = 'ME1' THEN
LOCATE FileName IN FileNames BY 'AR' USING @FM SETTING Pos ELSE
FileNames = INSERT(FileNames,Pos,0,0,FileName)
END
END
UNTIL List = ""
REPEAT
REPEAT
NEXT I
IF FileNames[-1,1] = @FM THEN FileNames[-1,1] = ''
Test = ''
FileCnt = COUNT(FileNames,@FM) + (FileNames NE '')
FOR I = 1 TO FileCnt
Send_Info('Processing ':I:' of ':FileCnt)
FileName = FileNames<I>
StartTime = Time()
OSREAD FileIn FROM Path:FileName THEN
SWAP TAB$ WITH @VM IN FileIn
SWAP CRLF$ WITH @FM IN FileIn
DEBUG
END
NEXT I
* * * * * * *
Bail:
* * * * * * *
RETURN