COMPILE FUNCTION obj_SAP_DEV(Method,Parms) /* Methods for Interfacing with SAP 11/10/2010 JCH - Initial Coding 11/20/2015 JCH & DKK Properties: Methods: GetOrder() ;* GetOrder from buffer */ DECLARE FUNCTION Get_Status, Msg, Utility, obj_Tables, Dialog_Box, obj_WO_Log, NextKey, obj_Shipment, obj_WO_Mat DECLARE SUBROUTINE Set_Status, Msg, obj_Tables, ErrMsg, Set_Property, obj_Order, Yield, Clear_Table, RList, obj_Notes DECLARE SUBROUTINE Send_Info, Send_Event, Post_Event, obj_Notes, SetInitDirOptions, Send_Info, obj_Shipment, obj_Post_Log $INSERT MSG_EQUATES $INSERT NOTIFICATION_EQU $INSERT WO_LOG_EQUATES $INSERT WO_MAT_EQUATES $INSERT COMPANY_EQUATES $INSERT SAP_BATCH_EQUATES $INSERT EPI_PART_EQUATES $INSERT RLIST_EQUATES $INSERT SAP_COMM_LOG_EQUATES EQU CRCRLF$ TO \0D0D0A\ EQU CRLF$ TO \0D0A\ EQU TAB$ TO \09\ *SAPEnviron = 'PRD' ;* Production SAPEnviron = 'QA' ;* Testing with the SAP test system ************************** *SAPEnviron = 'DEV' ;* IF SAPEnviron = 'QA' THEN DEBUG BEGIN CASE CASE SAPEnviron = 'PRD' TransFilePathIn = 'C:\FTP_IN' TransFilePathOut = 'C:\FTP_OUT' FTPScriptPath = 'C:\FTPScript\' *FTPServerIP = '172.23.28.185' ;* This is the new EU server FTPServerIP = 'sapnfs' ;* Current production server FTPUser = 'prdopeni' FTPPassWord = 'sapprdopeni' CASE SAPEnviron = 'QA' TransFilePathIn = 'C:\FTP_IN_TEST' TransFilePathOut = 'C:\FTP_OUT_TEST' FTPScriptPath = 'C:\FTPScript_Test\' FTPServerIP = '172.23.28.185' ;* FTP Server IP address or URL FTPUser = 'prdopeni' FTPPassword = 'sapprdopeni' *FTPUser = 'qasopeni' *FTPPassWord = 'sapqasopeni' CASE SAPEnviron = 'DEV' TransFilePathIn = 'C:\FTP_IN_TEST' TransFilePathOut = 'C:\FTP_OUT_TEST' FTPScriptPath = 'C:\FTPScript_Test\' FTPServerIP = '172.28.150.80' ;* FTP Server IP address or URL FTPUser = 'DEVOPENI' FTPPassWord = 'sapdevopeni' CASE 1 ErrMsg('Invalid SAPEnviron variable in obj_SAP') RETURN END CASE BaseFromSAPScript = 'open ':FTPServerIP:CRLF$ BaseFromSAPScript := 'user':CRLF$ BaseFromSAPScript := FTPUser:CRLF$ BaseFromSAPScript := FTPPassWord:CRLF$ BaseFromSAPScript := 'lcd ':TransFilePathIn:CRLF$ ;* Change local directory to C:\FTP_IN FromSAPScriptName = FTPScriptPath:'FromSAP.txt' BaseToSAPScript = 'open ':FTPServerIP:CRLF$ BaseToSAPScript := 'user':CRLF$ BaseToSAPScript := FTPUser:CRLF$ BaseToSAPScript := FTPPassword:CRLF$ BaseToSAPScript := 'lcd ':TransFilePathOut:CRLF$ ;* Change local directory to C:\FTP_OUT ToSAPScriptName = FTPScriptPath:'ToSAP.txt' ErrTitle = 'Error in Stored Procedure "obj_SAP"' ErrorMsg = '' IF NOT(ASSIGNED(Method)) THEN ErrorMsg = 'Unassigned parameter "Method" passed to subroutine' IF NOT(ASSIGNED(Parms)) THEN Parms = '' IF ErrorMsg NE '' THEN Set_Status(-1,ErrTitle:@SVM:ErrorMsg) RETURN '' END Result = '' BEGIN CASE CASE Method = 'GetInbound' ; GOSUB GetInbound CASE Method = 'AddTransaction' ; GOSUB AddTransaction CASE Method = 'SendOutbound' ; GOSUB SendOutbound CASE Method = 'SendReconcile' ; GOSUB SendReconcile CASE 1 ErrorMsg = 'Unknown Method ':QUOTE(Method):' passed to routine.' END CASE IF ErrorMsg NE '' THEN Set_Status(-1,ErrTitle:@SVM:ErrorMsg) RETURN '' END RETURN Result * * * * * * * SendReconcile: * * * * * * * IF SAPEnviron NE 'PRD' THEN RETURN ;* Belt and suspenders for production system OPEN 'WO_LOG' TO WOTable ELSE ErrorMsg = 'Unable to open WO_LOG table in obj_SAP' RETURN END Yesterday = OCONV(Date()-1,'D4/') CurrTime = OCONV(Time(),'MTS') YesterdayDTM = Yesterday:' ':CurrTime Set_Status(0) SelectSent = 'SELECT WO_LOG WITH PROD_ORD_NO NE "" ' RList(SelectSent,TARGET_ACTIVELIST$,'','','') IF Get_Status(errCode) THEN RETURN END SelectSent = 'SELECT WO_LOG WITH WO_STOP_DTM = "" OR WITH WO_STOP_DTM >= ':Quote(YesterdayDTM):' BY WO' RList(SelectSent,TARGET_ACTIVELIST$,'','','') IF Get_Status(errCode) THEN RETURN END TextOut = '' ;* Results go into this data structure Done = 0 LOOP READNEXT WONo ELSE Done = 1 UNTIL Done READ WORec FROM WOTable,WONo THEN Line = '' CurrStatus = obj_WO_Log('CurrStatus',WONo:@RM:WORec) Line<1> = WORec ;* ZAUFNR Line<2> = WORec ;* ZCHARG BEGIN CASE CASE WORec NE '' ; Line<3> = 'COMP' ;* ZSTTXT CASE CurrStatus = 'NORD' ; Line<3> = 'NORD' ;* ZSTTXT CASE CurrStatus = 'NEW' ; Line<3> = 'NEW' CASE CurrStatus = 'ASN' ; Line<3> = 'ASN' CASE CurrStatus = 'AWM' ; Line<3> = 'AWM' CASE CurrStatus = 'RTP' ; Line<3> = 'RTP' CASE CurrStatus = 'AWR' ; Line<3> = 'AWR' CASE CurrStatus = 'RX' ; Line<3> = 'RX' CASE CurrStatus = 'INPR' ; Line<3> = 'INPR' CASE CurrStatus = 'RTS' ; Line<3> = 'RTS' CASE CurrStatus = 'SHIP' ; Line<3> = 'SHIP' CASE CurrStatus = 'COMP' ; Line<3> = 'CL' ;* Changed from "COMP" to "CL" -dkk 3/21/14 CASE CurrStatus = 'CANC' ; Line<3> = 'CANC' CASE CurrStatus = 'CL' ; Line<3> = 'CL' CASE CurrStatus = 'INC' ; Line<3> = 'INC' CASE 1 ; Line<3> = 'INC' END CASE EPIPn = WORec SpecType = XLATE('EPI_PART',EpiPN,EPI_PART_SPEC_TYPE$,'X') CustCaptive = XLATE('COMPANY',WORec,COMPANY_CAPTIVE$,'X') BEGIN CASE * CASE SpecType = 'U' OR SpecType = 'Q' ; Line<4> = 'ZP03' ;* ZAUART - Qual ;* Eliminate ZP03 - dkk 3/21/14 CASE CustCaptive = '1' ; Line<4> = 'ZP01' ;* ZAUART - Captive CASE WORec NE '' ; Line<4> = 'ZP04' ;* ZAUART - Merchant CASE 1 ; Line<4> = 'ZP00' ;* ZAUART - Rx'd from SAP END CASE WOStartDt = WORec[1,'.'] WOStopDt = WORec[1,'.'] IF WOStartDt = '' THEN Line<5> = '00000000' END ELSE Line<5> = OCONV(WOStartDt,'[SAP_DT_FORMAT]') ;* GSTRP END Line<6> = OCONV(WOStopDt,'[SAP_DT_FORMAT]') ;* GLTRP ;******* Promise Ship Dt ******************* Line<7> = EpiPN ;* MATNR Line<8> = FMT(WORec,"R(0)#9") ;* GAMNG ;******* Total Good Wafers Completed ****** AllWOMatKeys = WORec RawBatch_WOMatKeys = XLATE('WO_MAT',AllWOMatKeys,WO_MAT_SAP_BATCH_NO$,'X') CompWOMatKeys = '' WOMatCnt = COUNT(AllWOMatKeys,@VM) + (AllWOMatKeys NE '') FOR I = 1 TO WOMatCnt IF RawBatch_WOMatKeys<1,I> NE '' THEN CompWOMatKeys<1,-1> = AllWOMatKeys<1,I> END NEXT I CassCompCnt = COUNT(CompWOMatKeys,@VM) + (CompWOMatKeys NE '') IF CassCompCnt > 0 THEN Line<9> = '0020' ;* VORNR /* BEGIN CASE CASE CassCompCnt > 0 ; Line<9> = '0020' ;* VORNR CASE WOStartDt NE '' ; Line<9> = '0010' ;* VORNR END CASE */ OrderQty = WORec TotCompQty = 0 TotScrapQty = 0 TotProdTWQty = 0 TotMUWfrQty = 0 FOR I = 1 TO CassCompCnt WOMatKey = CompWOMatKeys<1,I> GRProps = obj_WO_Mat('GetGRProps',WOMatKey:@RM:'') GRWfrQty = GRProps[1,@FM] ScrapQty = GRProps[COL2()+1,@FM] ProdTWQty = GRProps[COL2()+1,@FM] MUWfrQty = GRProps[COL2()+1,@FM] TotCompQty += GRWfrQty TotScrapQty += ScrapQty TotProdTWQty += ProdTWQty TotMUWfrQty += MUWfrQty NEXT I IF OrderQty <= 0 THEN Line<10> = FMT('0',"R(0)#9") END ELSE *Line<10> = FMT(OrderQty - TotCompQty,"R(0)#9") ;* MGVRG Line<10> = FMT(TotCompQty,"R(0)#9") ;* MGVRG END Line<11> = FMT(TotScrapQty + TotProdTWQty,"R(0)#9") ;* XMNGA *Line<12> = FMT(TotMUWfrQty,"R(0)#9") ;* MU Wafer Qty CurrDate = OCONV(Date(),'D4/') CurrTime = OCONV(Time(),'MTS') CurrDTM = ICONV(CurrDate:' ':CurrTime,'DT') TimeStamp = OCONV(CurrDTM,'[SAP_DTM_FORMAT]') Line<12> = TimeStamp ;* ZEXTDTE Line<13> = '1210' ;* ZMESYSS *Line<14> = WONo ;* ZWTFO END ;* End of WORec read CONVERT @FM TO '~' IN Line TextOut<-1> = Line REPEAT OutRec = TextOut SWAP @FM WITH CRLF$ IN OutRec CurrDate = OCONV(Date(),'D4/') CurrTime = OCONV(Time(),'MTS') CurrDTM = ICONV(CurrDate:' ':CurrTime,'DT') TimeStamp = OCONV(CurrDTM,'[SAP_DTM_FORMAT]') TransFileName = 'RECON_1210_':TimeStamp:'.txt' * This is the ftp code here ToSAPScript = 'open 172.28.150.80':CRLF$ ToSAPScript := 'user':CRLF$ BEGIN CASE CASE SAPEnviron = 'PRD' DosTable = 'C:\FTP_OUT\':TransFileName ToSAPScript := 'prdwiprcn':CRLF$ ToSAPScript := 'sapprdrcn':CRLF$ ToSAPScript := 'lcd c:\FTP_OUT':CRLF$ CASE SAPEnviron = 'QA' DosTable = 'C:\FTP_OUT_TEST\':TransFileName ToSAPScript := 'qaswiprcn':CRLF$ ToSAPScript := 'sapqasrcn':CRLF$ ToSAPScript := 'lcd c:\FTP_OUT_TEST':CRLF$ CASE SAPEnviron = 'DEV' DosTable = 'C:\FTP_OUT_TEST\':TransFileName ToSAPScript := 'devwiprcn':CRLF$ ToSAPScript := 'sapdevrcn':CRLF$ ToSAPScript := 'lcd c:\FTP_OUT_TEST':CRLF$ CASE 1 * Shouldn't ever get here END CASE OSWRITE OutRec ON DosTable ToSAPScript := 'cd inbound':CRLF$ ToSAPScript := 'put ':DosTable:CRLF$ ToSAPScript := 'get ':TransFileName:' WipVerify.txt':CRLF$ ToSAPScript := 'bye':CRLF$ OSWrite ToSAPScript ON 'c:\ToSAP.scr' StartTime = Time() stat = UTILITY('RUNWIN',"ftp -i -n -s:c:\ToSAP.scr",-1) StopTime = Time() IF StopTime - StartTime > 10 THEN ErrorMsg = 'FTP method "SendRecord" Execution Time > 10 seconds' ClearFlag = 0 RETURN END OSRead VerifyTxt FROM 'C:\FTP_OUT\verify.txt' THEN IF VerifyTxt = OutRec THEN ClearFlag = 1 END ELSE ClearFlag = 0 END END ELSE VerifyTxt = '' ClearFlag = 0 END OSDelete DosTable ;* Removes table from C: drive RETURN * * * * * * * AddTransaction: * * * * * * * TransAction = Parms[1,@RM] IF TransAction = '' THEN RETURN BEGIN CASE CASE TransAction = 'WO_HOLD' ;* * * Lot Hold, Lot off Hold, Start Lot, Lot Complete PP-I-423/524 * * * ProdOrdNo = Parms[COL2()+1,@RM] ;* Prod Order No Flag = Parms[COL2()+1,@RM] ;* Flag (might use a word instead) IF Flag = '' THEN Flag = 0 IF Flag = 1 THEN SAP_Parm = 'ON_HOLD' END ELSE SAP_Parm = 'OFF_HOLD' END TransRec = TransAction:@FM:ProdOrdNo:@FM:SAP_Parm ;* CASE TransAction = 'WO_START' OR TransAction = 'WO_STOP' ;* Function Spec : PP-I-521 ProdOrdNo = Parms[COL2()+1,@RM] ;* Prod Order No TransDate = Parms[COL2()+1,@RM] ;* Start or Stop Date TransDate = OCONV(TransDate,'D4/') *TransRec = TransAction:@FM:ProdOrdNo:@FM:Flag ;* Flag = 1 -> First Cassette into CleanRoom, = 0 Last Cassette out of Cleanroom TransRec = TransAction:@FM:ProdOrdNo:@FM:TransDate ;* First Cassette into CleanRoom is start, Last Cassette out is stop CASE TransAction = 'PROMISE_DT' ;* * * Change Scheduled CLOSE (Propmise) Date PP-I-526 * * * ProdOrdNo = Parms[COL2()+1,@RM] ;* Prod Order Number OrgPromiseDt = Parms[COL2()+1,@RM] ;* Original Scheduled Close (Promise) Date NewPromiseDt = Parms[COL2()+1,@RM] ;* New Scheduled Close (Promise) Date TransOrgPromiseDt = OCONV(OrgPromiseDt,'D4/') TransNewPromiseDt = OCONV(NewPromiseDt,'D4/') *TransOrgPromiseDt = OCONV(OrgPromiseDt,'[SAP_DT_FORMAT]') *TransNewPromiseDt = OCONV(NewPromiseDt,'[SAP_DT_FORMAT]') TransRec = Transaction:@FM:ProdOrdNo:@FM:TransOrgPromiseDt:@FM:TransNewPromiseDt CASE TransAction = 'WFR_REJECT' OR TransAction = 'PROD_TW' ;* * * Inventory SCRAP PP-I-527 * * * MB1A RETURN ;**************** ProdOrdNo = Parms[COL2()+1,@RM] ;* Source Inventory (WIP) Location WaferQty = Parms[COL2()+1,@RM] ;* Qty "+" => Qty Removed from WIP, "-" => Return Qty to WIP * MoveType = 551 ;* Movement type needed is always 551 * Plant = 1210 ;* Plant is always 1210 * SLoc = ;* Move from SLoc_ if MU box then 0400 else 0500 * CostC = 1105 ;* Cost Center always 1105 * EpiPN = ;* Epi part number * WaferQty = Parms[COL2()+1,@RM] ;* Qty "+" => Qty Removed from WIP, "-" => Return Qty to WIP * BatchNo = ;* BatchNo to reject from to perform MB1A IF NOT(NUM(WaferQty)) THEN ErrorMsg = 'Invalid parameter "WaferQty" ':QUOTE(WaferQty):' passed to routine. (':Method:" ":Transaction:')' RETURN END TransRec = Transaction:@FM:ProdOrdNo:@FM:WaferQty CASE TransAction = 'MU_WFR' ;* * * Inventory MOVE PP-I-520 * * * MB1B RETURN ;********* ProdOrdNo = Parms[COL2()+1,@RM] ;* Source Inventory Location (WIP) DestLocation = Parms[COL2()+1,@RM] ;* Dest Inventory Location (Makeup) WaferQty = Parms[COL2()+1,@RM] ;* Qty "+" => Source to Destination, "-" => Destination to Source * MoveType = 311 ;* Movement type needed is always 311 * Plant = 1210 ;* Plant is always 1210 * SLoc = 0400 ;* Move from SLoc 0400_MU * Rcvg_SLoc = 0500 ;* Receiving SLoc is always 0500_FGS * EpiPN = ;* Epi part number * MUBatchQty = Parms[COL2()+1,@RM] ;* Request MU Qty to pull from MU batch located in SLoc 0400 * MUBatchNo = Parms[COL2()+1,@RM] ;* MU batch ID to pull from in SLoc 0400 * Rcvg_BatchNo = Parms[COL2()+1,@RM] ;* Recieving batch ID IF NOT(NUM(WaferQty)) THEN ErrorMsg = 'Invalid parameter "WaferQty" ':QUOTE(WaferQty):' passed to routine. (':METHOD:')' RETURN END TransRec = TransAction:@FM:ProdOrdNo:@FM:DestLocation:@FM:WaferQty * TransRec = TransAction:@FM:CassID:@FM:MUBatchNo:@FM:MUBatchQty CASE TransAction = 'CUST_TW' ;* * * Inventory MOVE PP-I-520 * * * RETURN ;*********** ProdOrdNo = Parms[COL2()+1,@RM] ;* Source Inventory Location (In WIP) CustTWPartNo = Parms[COL2()+1,@RM] ;* Customer TW Identifier/Part_NO WaferQty = Parms[COL2()+1,@RM] ;* Qty "+" => Source to Destination, "-" => Destination to Source IF NOT(NUM(WaferQty)) THEN ErrorMsg = 'Invalid parameter "WaferQty" ':QUOTE(WaferQty):' passed to routine. (':METHOD:')' RETURN END TransRec = TransAction:@FM:ProdOrdNo:@FM:CustTWPartNo:@FM:WaferQty CASE TransAction = 'SET_MU_BOX' ; * * * Flag Makeup Inventory PP-I-528 * * * RETURN ;* Dead as 3/23/2011 per Dave Klotz - jch ProdOrdNo = Parms[COL2()+1,@RM] ;* Source Inventory Location (In WIP) CassNo = Parms[COL2()+1,@RM] ;* Cass No placed into MU Flag = Parms[COL2()+1,@RM] ;* Flag = '1' -> Cassette set to Makeup , = '0' -> Clear Cassette Makeup Flag TransRec = TransAction:@FM:ProdOrdNo:@FM:CassNo:@FM:Flag CASE TransAction = 'CASS_COMP' ;* Packages the Cassette Complete Transaction_Final QA Triggered -dkk 7/28/14 ProdOrdNo = Parms[COL2()+1,@RM] ; ParmList = ProdOrdNo ;* Production Order Number WorkOrdNo = Parms[COL2()+1,@RM] ; ParmList<2> = WorkOrdNo ;* Work Order No CassNo = Parms[COL2()+1,@RM] ; ParmList<3> = CassNo ;* Cass No GRWfrQty = Parms[COL2()+1,@RM] ; ParmList<4> = GrWfrQty ;* Good Wafers NOT INCLUDING MAKEUPS ScrapQty = Parms[COL2()+1,@RM] ; ParmList<5> = ScrapQty ;* Scrap (NCR'd wafers) ProdTWQty = Parms[COL2()+1,@RM] ; ParmList<6> = ProdTWQty ;* Product Test Wafers CassID = Parms[COL2()+1,@RM] ; ParmList<7> = CassID ;* Cass ID VendorLotNo = Parms[COL2()+1,@RM] ; ParmList<8> = VendorLotNo ;* Vendor Lot Number on substrate SubSupplier = Parms[COL2()+1,@RM] ; ParmList<9> = SubSupplier ;* Vendor Code SubSupplier CustPartRev = Parms[COL2()+1,@RM] ; ParmList<10> = CustPartRev ;* Cust Part Revision MakeupFlag = Parms[COL2()+1,@RM] ; ParmList<11> = MakeupFlag ;* Makeup Flag MUBatchNo = Parms[COL2()+1,@RM] ; ParmList<12> = MUBatchNo ;* Request MU to pull from in SLoc 0400 -dkk 7/28/14 MUBatchQty = Parms[COL2()+1,@RM] ; ParmList<13> = MUBatchQty ;* Request MU Qty to pull from MU batch located in SLoc 0400 -dkk 7/28/14 TransRec = Transaction:@FM:ParmList CASE 1 ErrorMsg = 'Unknown TransAction ':QUOTE(TransAction):' passed to routine. (':METHOD:')' RETURN END CASE NextTransNo = NextKey('SAP_COMM') oTParms = 'SAP_COMM':@RM:NextTransNo:@RM:@RM:TransRec obj_Tables('WriteRec',OtParms) ****************** ;* Added 1/15/2014 jch OPEN 'SAP_COMM' TO SAPCommTable THEN SELECT SAPCommTable Done = 0 KeyCnt = 0 LOOP READNEXT Key ELSE Done = 1 UNTIL Done KeyCnt += 1 REPEAT BufferLevelAlarmSetpoint = 9999 ;* Hi Dave, change the 3 to 9999 to stop the messaging during an outage **************************************** IF KeyCnt = BufferLevelAlarmSetpoint Then ;* Originally: IF KeyCnt > BufferLevelAlarmSetpoint THEN - This change limits the messages to only 1 -dkk 2/8/15 Recipients = 'DAN_CR' ; * XLATE('NOTIFICATION','ORDER_ENTRY',NOTIFICATION_USER_ID$,'X') SentFrom = @USER4 Subject = 'SAP Comm Buffer Overflow' Message = 'SAP Comm Buffer is filling up with ':KeyCnt:' records not sent. Check SAP interface.' AttachWindow = '' AttachKey = '' SendToGroup = '' Parms = Recipients:@RM:SentFrom:@RM:Subject:@RM:Message:@RM:AttachWindow:@RM:AttachKey:@RM:SendToGroup obj_Notes('Create',Parms) IF Get_Status(errCode) THEN ErrMsg(errCode) END END ;* End of Check for KeyCnt > BufferLevelAlarmSetpoint END ;* End of check for table open ******************************* RETURN * * * * * * * GetInbound: * * * * * * * * Start of SAP inbound code JCH TransLogOn = Parms[1,@RM] ;* Added 12/12/2011 Flag to turn on transaction logging IF TransLogOn = 1 THEN OPEN 'SAP_COMM_LOG' TO LogFile ELSE NULL END GOSUB ReadInbound ;* Copies files on FTP server FromSAP\ProdOrdRel directory into C:\FTP_IN directory IF ErrorMsg NE '' THEN RETURN ;* Had problem with ftp process ******* Production Order Releases Inbound ******* InboundPath = TransFilePathIn:'\ProdOrdRel\' InitDir InboundPath:'*.tsv' FileList = DirList() FileNames = '' LOOP FileName = FileList[1,@FM] FileList[1,Col2()] = "" LOCATE FileName IN FileNames BY 'AR' USING @FM SETTING Pos ELSE FileNames = INSERT(FileNames,Pos,0,0,FileName) END UNTIL FileList = "" REPEAT IF FileNames[-1,1] = @FM THEN FileNames[-1,1] = '' Test = '' FileCnt = COUNT(FileNames,@FM) + (FileNames NE '') FOR N = 1 TO FileCnt Send_Info('Processing ':N:' of ':FileCnt) FileName = FileNames StartTime = Time() OSREAD FileIn FROM InboundPath:FileName THEN IF TransLogOn = 1 THEN LTType = 'RX' Trans = 'ProdOrdRel' GOSUB LogTrans ;* Added 12/12/2011 JCH for transaction logging END SWAP TAB$ WITH @VM IN FileIn SWAP '|' WITH @VM IN FileIn ;* Incorrect delimiter SWAP CRLF$ WITH @FM IN FileIn LOOP LastChar = FileIn[-1,1] UNTIL LastChar NE @FM FileIn[-1,1] = '' REPEAT RetVal = obj_WO_LOG('SAPCreate',FileIn) *IF RetVal = 1 THEN OSDELETE InboundPath:Filename ;* Deletes local copy of inbound file SubDirectory = 'ProdOrdRel' GOSUB ClearInbound ;* Deletes file on FTP server FromSAP\ProdOrdRel directory * * * * * * * * * * * * * * *END ;* End of check for successful WO_LOG create END NEXT N * * * * * * * Cassette Batch Numbers Inbound * * * * * * * InboundPath = TransFilePathIn:'\Batch\' ;* Get any inbound Product Order Releases InitDir InboundPath:'*.tsv' FileList = DirList() FileNames = '' LOOP FileName = FileList[1,@FM] FileList[1,Col2()] = "" LOCATE FileName IN FileNames BY 'AR' USING @FM SETTING Pos ELSE FileNames = INSERT(FileNames,Pos,0,0,FileName) END UNTIL FileList = "" REPEAT IF FileNames[-1,1] = @FM THEN FileNames[-1,1] = '' Test = '' FileCnt = COUNT(FileNames,@FM) + (FileNames NE '') FOR N = 1 TO FileCnt Send_Info('Processing ':N:' of ':FileCnt) FileName = FileNames StartTime = Time() OSREAD FileIn FROM InboundPath:FileName THEN IF TransLogOn = 1 THEN LTType = 'RX' Trans = 'SetBatch' GOSUB LogTrans ;* Added 12/12/2011 JCH for transaction logging END SWAP TAB$ WITH @VM IN FileIn SWAP CRCRLF$ WITH @FM IN FileIn LOOP LastChar = FileIn[-1,1] UNTIL LastChar NE @FM FileIn[-1,1] = '' REPEAT RetVal = obj_WO_Mat('SetSAPBatch',FileIn) IF RetVal = 1 THEN OSDELETE InboundPath:Filename ;* Deletes local copy of inbound file SubDirectory = 'Batch' GOSUB ClearInbound ;* Deletes file on FTP server FromSAP\Batch directory END ;* End of check for successful WO_LOG create END NEXT N * * * * * * * Shipment Releases Inbound * * * * * * * InboundPath = TransFilePathIn:'\ShipRel\' ;* Get any inbound Product Order Releases InitDir InboundPath:'*.tsv' FileList = DirList() FileNames = '' LOOP FileName = FileList[1,@FM] FileList[1,Col2()] = "" LOCATE FileName IN FileNames BY 'AR' USING @FM SETTING Pos ELSE FileNames = INSERT(FileNames,Pos,0,0,FileName) END UNTIL FileList = "" REPEAT IF FileNames[-1,1] = @FM THEN FileNames[-1,1] = '' Test = '' FileCnt = COUNT(FileNames,@FM) + (FileNames NE '') FOR N = 1 TO FileCnt Send_Info('Processing ':N:' of ':FileCnt) FileName = FileNames StartTime = Time() OSREAD FileIn FROM InboundPath:FileName THEN SWAP TAB$ WITH @VM IN FileIn SWAP CRCRLF$ WITH @FM IN FileIn SWAP CRLF$ WITH @FM IN FileIn LOOP LastChar = FileIn[-1,1] UNTIL LastChar NE @FM FileIn[-1,1] = '' REPEAT RetVal = obj_Shipment('SAPCreate',FileIn) IF RetVal = 1 THEN OSDELETE InboundPath:Filename ;* Deletes local copy of inbound file SubDirectory = 'ShipRel' GOSUB ClearInbound ;* Deletes file on FTP server FromSAP\ProdOrdRel directory END ;* End of check for successful WO_LOG create END NEXT N RETURN * * * * * * * SendOutbound: * * * * * * * TransLogOn = Parms[1,@RM] ;* Added 12/12/2011 Flag to turn on transaction logging TransLimit = Parms[COL2()+1,@RM] IF TransLogOn = 1 THEN OPEN 'SAP_COMM_LOG' TO LogFile ELSE NULL END OPEN 'SAP_COMM' TO Buffer THEN SELECT 'SAP_COMM' BY 'SEQ' SETTING Cursor ELSE ErrMsg("Select failure in obj_SAP('SendOutBound'...") RETURN END Done = 0 TransQty = 0 LOOP READNEXT TxSeqNo USING Cursor ELSE Done = 1 UNTIL Done Or TransQty = TransLimit ClearFlag = 0 TransQty += 1 READ Transaction FROM Buffer,TxSeqNo THEN TransType = Transaction<1> Transaction = DELETE(Transaction,1,0,0) BEGIN CASE CASE TransType = 'CASS_COMP' OutBoundDir = 'CassComp' OutRec = Transaction CONVERT @FM TO TAB$ IN OutRec OutRec := CRLF$ *ProdOrdNo = Transaction[1,@FM] *WONo = Transaction[COL2()+1,@FM] *CassNo = Transaction[COL2()+1,@FM] *GRWfrQty = Transaction[COL2()+1,@FM] *ScrapQty = Transaction[COL2()+1,@FM] *ProdTWQty = Transaction[COL2()+1,@FM] *CassID = Transaction[COL2()+1,@FM] *VendorLotNo = Transaction[COL2()+1,@FM] *SubSupplier = Transaction[COL2()+1,@FM] *CustPartRev = Transaction[COL2()+1,@FM] *MakeupFlag = Transaction[COL2()+1,@FM] *MUBatchNo = Transaction[COL2()+1,@FM] *MUBatchQty = Transaction[COL2()+1,@FM] *OutRec = ProdOrdNo:TAB$:WONo:TAB$:CassNo:TAB$:GRWfrQty:TAB$:ScrapQty:TAB$:ProdTWQty:TAB$:CassID:TAB$:VendorLotNo:TAB$:SubSupplier:TAB$:CustPartRev:TAB$:MakeupFlag:TAB$:MUBatchNo:TAB$:MUBatchQty:CRLF$ GOSUB SendRecord CASE TransType = 'CUST_TW' OR TransType = 'MU_WFR' OutBoundDir = 'InvMove' IF TransType = 'CUST_TW' THEN ProdOrdNo = Transaction[1,@FM] CustTWPartNo = Transaction[COL2()+1,@FM] WfrQty = Transaction[COL2()+1,@FM] IF CustTWPartNo = '' THEN CustTWPartNo = '{Cust TW Part No}' OutRec = 'CUST_TW':TAB$:ProdOrdNo:TAB$:CustTWPartNo:TAB$:WfrQty:CRLF$ END IF TransType = 'MU_WFR' THEN ProdOrdNo = Transaction[1,@FM] MUProdOrdNo = Transaction[COL2()+1,@FM] WfrQty = Transaction[COL2()+1,@FM] OutRec = 'MU_WFR':TAB$:ProdOrdNo:TAB$:MUProdOrdNo:TAB$:WfrQty:CRLF$ END GOSUB SendRecord CASE TransType = 'PROD_TW' OR TransType = 'WFR_REJECT' OutBoundDir = 'Scrap' ProdOrdNo = Transaction[1,@FM] WfrQty = Transaction[COL2()+1,@FM] IF TransType = 'PROD_TW' THEN OutRec = 'PROD_TW':TAB$:ProdOrdNo:TAB$:WfrQty:CRLF$ END IF TransType = 'WFR_REJECT' THEN OutRec = 'WFR_REJECT':TAB$:ProdOrdNo:TAB$:WfrQty:CRLF$ END GOSUB SendRecord CASE TransType = 'WO_HOLD' ProdOrdNo = Transaction[1,@FM] HoldOnOff = Transaction[COL2()+1,@FM] IF HoldOnOff = 'ON_HOLD' THEN OutBoundDir = 'WOHoldOn' OutRec = ProdOrdNo:TAB$:'1':CRLF$ END IF HoldOnOff = 'OFF_HOLD' THEN OutBoundDir = 'WOHoldOff' OutRec = ProdOrdNo:TAB$:'1':CRLF$ END GOSUB SendRecord CASE TransType = 'WO_START' OutBoundDir = 'WOStart' ProdOrdNo = Transaction[1,@FM] StartDt = Transaction[COL2()+1,@FM] OutRec = ProdOrdNo:TAB$:StartDt:CRLF$ GOSUB SendRecord CASE TransType = 'WO_STOP' OutBoundDir = 'WOStop' ProdOrdNo = Transaction[1,@FM] StopDt = Transaction[COL2()+1,@FM] OutRec = ProdOrdNo:TAB$:StopDt:CRLF$ GOSUB SendRecord CASE TransType = 'PROMISE_DT' ;* * * Change Scheduled CLOSE (Promise) Date PP-I-526 * * * OutBoundDir = 'PromiseDt' ProdOrdNo = Transaction[1,@FM] OrgPromiseDt = Transaction[COL2()+1,@FM] NewPromiseDt = Transaction[COL2()+1,@FM] OutRec = ProdOrdNo:TAB$:OrgPromiseDt:TAB$:NewPromiseDt:CRLF$ GOSUB SendRecord CASE TransType = 'SET_MU_BOX' OutBoundDir = 'MUCass' ProdOrdNo = Transaction[1,@FM] CassNo = Transaction[COL2()+1,@FM] Flag = Transaction[COL2()+1,@FM] OutRec = ProdOrdNo:TAB$:CassNo:TAB$:Flag:CRLF$ GOSUB SendRecord CASE 1 END CASE IF ErrorMsg NE '' THEN RETURN ;* Set by SendRecord if there is a problem IF ClearFlag = 1 THEN DELETE Buffer,TxSeqNo ELSE Null END END REPEAT * * * Added 10/20/2015 JCH * * * If Not(Done) Then ClearSelect Cursor ;* Clear remaining SELECT list if READNEXT loop doesn't finish End END ELSE ErrorMsg = 'Unable to open "VISION_COMM" for transmission' RETURN END RETURN * * * * * * * * * * * * * * * * * * * * * * * * Private Methods * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * SendRecord: * * * * * * * GOSUB DirNextSeq IF ErrorMsg NE '' THEN RETURN TransFileName = 'TX':FMT(DirNextSeqNo,"R(0)#6"):'.tsv' DosTable = TransFilePathOut:'\':TransFileName IF TransLogOn = 1 THEN LTType = 'TX' GOSUB LogTrans ;* Added 12/12/2011 JCH for transaction logging END OSWRITE OutRec ON DosTable * This is the ftp code here ToSAPScript = BaseToSAPScript ToSAPScript := 'cd ToSAP':CRLF$ ToSAPScript := 'cd ':OutBoundDir:CRLF$ ToSAPScript := 'put ':DosTable:CRLF$ ToSAPScript := 'get ':TransFileName:' verify.txt':CRLF$ ToSAPScript := 'bye':CRLF$ OSWrite ToSAPScript ON ToSAPScriptName StartTime = Time() stat = UTILITY('RUNWIN',"ftp -i -n -s:":ToSAPScriptName,-1) StopTime = Time() IF StopTime - StartTime > 10 THEN ErrorMsg = 'FTP method "SendRecord" Execution Time > 10 seconds' ClearFlag = 0 RETURN END OSRead VerifyTxt FROM TransFilePathOut:'\verify.txt' THEN IF VerifyTxt = OutRec THEN ClearFlag = 1 END ELSE ClearFlag = 0 END END ELSE VerifyTxt = '' ClearFlag = 0 END OSDelete DosTable ;* Removes table from C: drive RETURN * * * * * * * ReadInbound: * * * * * * * * * * * * * Production Orders Released -> Create Work Orders * * * * * * FromSAPScript = BaseFromSAPScript FromSAPScript := 'lcd ProdOrdRel':CRLF$ ;* Change local directory to EnvPath:ProdOrdRel FromSAPScript := 'cd FromSAP':CRLF$ ;* Change remote directory to FromSAP FromSAPScript := 'cd ProdOrdRel':CRLF$ ;* Change remote directory to FromSAP\ProdOrdRel FromSAPScript := 'mget *.tsv':CRLF$ ;* Copy files from remote to local directory FromSAPScript := CRLF$ ;* FTP expects a CRLF for each file transferred FromSAPScript := CRLF$ FromSAPScript := 'bye':CRLF$ OSWrite FromSAPScript ON FromSAPScriptName StartTime = Time() stat = UTILITY('RUNWIN',"ftp -i -n -s:":FromSAPScriptName,-1) StopTime = Time() IF StopTime - StartTime > 30 Then ;* Changed from 20 seconds to 30 - dkk 7/27/14 ErrorMsg = 'FTP method "ReadInbound" Execution Time > 30 seconds' END * * * * * SAP Batch Numbers returned * * * * * FromSAPScript = BaseFromSAPScript FromSAPScript := 'lcd Batch':CRLF$ ;* Change local directory to \Batch subdirectory FromSAPScript := 'cd FromSAP':CRLF$ ;* Change remote directory to FromSAP FromSAPScript := 'cd Batch':CRLF$ ;* Change remote directory to FromSAP\Batch FromSAPScript := 'mget *.tsv':CRLF$ ;* Copy files from remote to local directory FromSAPScript := CRLF$ ;* FTP expects a CRLF for each file transferred FromSAPScript := CRLF$ FromSAPScript := 'bye':CRLF$ OSWrite FromSAPScript ON FromSAPScriptName StartTime = Time() stat = UTILITY('RUNWIN',"ftp -i -n -s:":FromSAPScriptName,-1) StopTime = Time() IF StopTime - StartTime > 30 Then ;* Changed from 20 seconds to 30 -dkk 7/27/14 ErrorMsg = 'FTP method "ReadInbound" Execution Time > 30 seconds' END * * * * * * Shipment Release * * * * * * * FromSAPScript = BaseFromSAPScript FromSAPScript := 'lcd ShipRel':CRLF$ ;* Change local directory to C:\FTP_IN\ShipRel FromSAPScript := 'cd FromSAP':CRLF$ ;* Change remote directory to FromSAP FromSAPScript := 'cd ShipRel':CRLF$ ;* Change remote direcotry to FromSAP\ShipRel FromSAPScript := 'mget *.tsv':CRLF$ ;* Copy files from remote to local directory FromSAPScript := 'bye':CRLF$ OSWrite FromSAPScript ON FromSAPScriptName StartTime = Time() stat = UTILITY('RUNWIN',"ftp -i -n -s:":FromSAPScriptName,-1) StopTime = Time() IF StopTime - StartTime > 30 Then ;* Changed from 20 to 30 seconds - dkk 7/27/14 ErrorMsg = 'FTP method "ReadInbound" Execution Time > 30 seconds' END RETURN * * * * * * * ClearInbound: * * * * * * * FromSAPScript = BaseFromSAPScript FromSAPScript := 'lcd ':SubDirectory:CRLF$ FromSAPScript := 'cd FromSAP':CRLF$ FromSAPScript := 'cd ':SubDirectory:CRLF$ FromSAPScript := 'delete ':Filename:CRLF$ FromSAPScript := 'bye':CRLF$ OSWrite FromSAPScript ON FromSAPScriptName OSWrite FromSAPScript ON FTPScriptPath:'InboundDelScript.TXT' StartTime = Time() stat = UTILITY('RUNWIN',"ftp -i -n -s:":FromSAPScriptName,-1) ;******************************************************************** TESTING StopTime = Time() /* IF SAPEnviron = 'PRD' THEN OSWrite ToSAPScript ON SAPScriptName OSWrite ToSAPScript ON 'C:JCH_SCR.TXT' StartTime = Time() stat = UTILITY('RUNWIN',"ftp -i -n -s:":SAPScriptName,-1) StopTime = Time() END */ IF StopTime - StartTime > 10 THEN ErrorMsg = 'FTP Process Exceeded 10 seconds in ClearInbound' RETURN END RETURN * * * * * * * DirNextSeq: * * * * * * * * Expects Variable 'OutBoundDir' to be set ToSAPScript = BaseToSAPScript ToSAPScript := 'lcd ':TransFilePathOut:CRLF$ ToSAPScript := 'cd ToSAP':CRLF$ ToSAPScript := 'cd ':OutBoundDir:CRLF$ ToSAPScript := 'mls *.tsv OutDir.txt':CRLF$ ToSAPScript := 'bye':CRLF$ OSWrite ToSAPScript ON ToSAPScriptName StartTime = Time() stat = UTILITY('RUNWIN',"ftp -i -n -s:":ToSAPScriptName,-1) StopTime = Time() IF StopTime - StartTime > 10 THEN ErrorMsg = 'FTP Process Exceeded 10 seconds in DirNextSeq' RETURN END OSRead FileNames FROM TransFilePathOut:'\OutDir.txt' THEN SWAP \0D0D0A\ WITH @FM IN FileNames ;* FTP delimiter has extra CR FileNames[-1,1] = '' ;* Trailing delimiter LastSeq = '' Pos = 1 Flag = "" LOOP REMOVE FileName FROM FileNames AT Pos SETTING Flag IF FileName[1,8] MATCHES "'TX'0N" THEN SeqNo = ABS(FileName[3,'.']) IF SeqNo > LastSeq THEN LastSeq = SeqNo END END WHILE Flag REPEAT DirNextSeqNo = LastSeq + 1 END ELSE DirNextSeqNo = 1 END RETURN * * * * * * * LogTrans: * * * * * * * LTKey = NextKey('SAP_COMM_LOG') LogRec = '' LogRec = ICONV(OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS'),'DT') IF LTType = 'TX' THEN LogRec = LTType LogRec = DOSTable LogRec = TransFileName LogDosFile = OutRec CONVERT 'CRLF$' TO '' IN LogDosFile LogRec = LogDosFile LogRec = TransType END ELSE LogRec = LTType LogRec = InboundPath LogRec = FileName LogDosFile = FileIn CONVERT 'CRLF$' TO '' IN LogDosFile LogRec = LogDosFile LogRec = Trans END WRITE LogRec ON LogFile,LTKey ELSE NULL RETURN