2022-03-31 17:39:08 -04:00
Attribute VB_Name = "PriceLists"
2022-04-01 16:31:23 -04:00
Option Explicit
2022-04-07 12:39:00 -04:00
Sub test_full20 ( )
2022-03-31 17:39:08 -04:00
'------------------------------------setup-------------------------------------------------
Dim wapi As New Windows_API
Dim x As New TheBigOne
Dim tbl ( ) As Variant
2022-04-01 16:31:23 -04:00
Dim lists ( ) As String
Dim pcol ( ) As Long
2022-03-31 17:39:08 -04:00
Dim unp ( ) As String
Dim unv ( ) As Variant
2022-04-01 16:31:23 -04:00
Dim onelist ( ) As String
Dim i As Long
Dim l As Long
Dim j As Long
2022-03-31 17:39:08 -04:00
Dim unps ( ) As String
Dim sql As String
Dim error As String
Dim orig As Range
Dim ini As Range
Dim cms_pl ( ) As String
Dim pw As String
Dim new_sh As Worksheet
Dim ws As Worksheet
Dim cp As CustomProperty
2022-04-01 16:31:23 -04:00
2022-03-31 17:39:08 -04:00
Set ini = Application . Selection
Selection . CurrentRegion . Select
Set orig = Application . Selection
2022-04-01 16:31:23 -04:00
unp = unpivot_current_sheet ( lists , pcol )
2022-03-31 17:39:08 -04:00
login . Show
If Not login . proceed Then Exit Sub
If Not x . ADOp_OpenCon ( 0 , PostgreSQLODBC , "usmidlnx01" , False , login . tbU . text , login . tbP . text , "Port=5030;Database=ubm" ) Then
MsgBox ( "not able to connect to CMS" & vbCrLf & x . ADOo_errstring )
Exit Sub
End If
With orig . Interior
. Pattern = xlNone
. TintAndShade = 0
. PatternTintAndShade = 0
End With
2022-04-01 16:31:23 -04:00
For l = 1 To UBound ( lists )
'----------filter the main data set for each price lists (due to json_from_table taking forever on big tables)--------
onelist = unp
Call x . TBLp_FilterSingle ( onelist , 9 , lists ( l ) , True )
onelist = x . TBLp_Transpose ( onelist )
unv = x . TBLp_StringToVar ( onelist )
2022-03-31 17:39:08 -04:00
2022-04-01 16:31:23 -04:00
'-------------------------prepare sql to upload---------------------------------------------------------------
'sql = x.SQLp_build_sql_values(unp, False, True, Db2, False)
sql = x . json_from_table ( unv , "" , False )
sql = "SELECT * FROM rlarp.plcore_fullcode_inq($$" & sql & "$$::jsonb)"
Call wapi . ClipBoard_SetData ( sql )
'If MsgBox(sql, vbOKCancel, "continue with build?") = vbCancel Then Exit Sub
'Exit Sub
cms_pl = x . ADOp_SelectS ( 0 , sql , True , 50000 , True )
'--------------------------setup an output sheet if necessary-------------------------------
For Each ws In Application . Worksheets
For Each cp In ws . CustomProperties
If cp . Name = "spec_name" And cp . value = "price_list" Then
Set new_sh = ws
Exit For
2022-03-31 17:39:08 -04:00
End If
2022-04-01 16:31:23 -04:00
Next cp
Next ws
If new_sh Is Nothing Then
Set new_sh = Application . Worksheets . Add
Call new_sh . CustomProperties . Add ( "spec_name" , "price_list" )
new_sh . Name = "Price Build"
End If
'-------------------------dump contents------------------------------------------------------
Call x . SHTp_Dump ( cms_pl , new_sh . Name , 1 , 1 , True , True )
new_sh . Select
ActiveSheet . Cells ( 1 , 1 ) . CurrentRegion . Select
Selection . Columns . AutoFit
Rows ( "1:1" ) . Select
With ActiveWindow
. SplitColumn = 0
. SplitRow = 1
End With
ActiveWindow . FreezePanes = True
'--------------------------format source cells for any build issues--------------------------------
orig . Worksheet . Select
'if a cell has even one valid hit, don't show an error
'create a copy of tbl
'the default value for cell is error, if any good values are found, they stay
2022-03-31 17:39:08 -04:00
j = 0
2022-04-01 16:31:23 -04:00
For i = 1 To UBound ( cms_pl , 1 )
Select Case cms_pl ( i , 15 )
Case ""
orig . Worksheet . Cells ( orig . row + cms_pl ( i , 13 ) , orig . column + cms_pl ( i , 14 ) ) . Interior . ThemeColor = xlThemeColorAccent6
Case "No UOM Conversion"
If orig . Worksheet . Cells ( orig . row + cms_pl ( i , 13 ) , orig . column + cms_pl ( i , 14 ) ) . Interior . ThemeColor < > xlThemeColorAccent6 Then
orig . Worksheet . Cells ( orig . row + cms_pl ( i , 13 ) , orig . column + cms_pl ( i , 14 ) ) . Interior . Color = RGB ( 255 , 255 , 161 )
End If
Case "Inactive"
If orig . Worksheet . Cells ( orig . row + cms_pl ( i , 13 ) , orig . column + cms_pl ( i , 14 ) ) . Interior . ThemeColor < > xlThemeColorAccent6 Then
orig . Worksheet . Cells ( orig . row + cms_pl ( i , 13 ) , orig . column + cms_pl ( i , 14 ) ) . Interior . Color = RGB ( 255 , 20 , 161 )
End If
Case "No SKU"
If orig . Worksheet . Cells ( orig . row + cms_pl ( i , 13 ) , orig . column + cms_pl ( i , 14 ) ) . Interior . ThemeColor < > xlThemeColorAccent6 Then
orig . Worksheet . Cells ( orig . row + cms_pl ( i , 13 ) , orig . column + cms_pl ( i , 14 ) ) . Interior . Color = RGB ( 20 , 255 , 161 )
End If
End Select
'if the current row/column is OK, advance to the next row/column
j = 0
Do Until cms_pl ( i , 13 ) < > cms_pl ( i + j , 13 ) Or cms_pl ( i , 14 ) < > cms_pl ( i + j , 14 )
j = j + 1
If i + j > = UBound ( cms_pl , 1 ) Then Exit Do
Loop
i = i + j - 1 '-1 becuase the "next i" will increment by 1 again
Next i
Dim cell As Range
Next l
2022-03-31 17:39:08 -04:00
2022-04-01 16:31:23 -04:00
Call x . ADOp_CloseCon ( 0 )
2022-03-31 17:39:08 -04:00
For Each cell In Application . Selection . Cells
'if the cell fill is green, then a known good part was found, so cell to blank
If cell . Interior . ThemeColor = xlThemeColorAccent6 Then
2022-04-07 12:39:00 -04:00
'flag any cells that have prices that are not a formula
If IsNumeric ( cell . value ) And Mid ( cell . Formula , 1 , 1 ) < > "=" And cell . row > 3 And cell . column > 6 Then
'cell.Interior.Color = RGB(186, 85, 211)
' With cell.Borders(xlEdgeLeft)
' .LineStyle = xlContinuous
' .Color = -6279056
' .TintAndShade = 0
' .Weight = xlThick
' End With
' With cell.Borders(xlEdgeTop)
' .LineStyle = xlContinuous
' .Color = -6279056
' .TintAndShade = 0
' .Weight = xlThick
' End With
' With cell.Borders(xlEdgeRight)
' .LineStyle = xlContinuous
' .Color = -6279056
' .TintAndShade = 0
' .Weight = xlThick
' End With
' With cell.Borders(xlEdgeBottom)
' .LineStyle = xlContinuous
' .Color = -6279056
' .TintAndShade = 0
' .Weight = xlThick
' End With
End If
2022-03-31 17:39:08 -04:00
cell . Interior . Pattern = xlNone
Else
If cell . Interior . Pattern = xlNone And cell . value < > "" Then
2022-04-07 12:39:00 -04:00
'---yellow-------
2022-03-31 17:39:08 -04:00
cell . Interior . Color = RGB ( 255 , 255 , 161 )
End If
End If
Next cell
Selection . Columns ( 1 ) . Interior . Pattern = xlNone
Selection . Columns ( 2 ) . Interior . Pattern = xlNone
Selection . Columns ( 3 ) . Interior . Pattern = xlNone
Selection . Columns ( 4 ) . Interior . Pattern = xlNone
Selection . Columns ( 5 ) . Interior . Pattern = xlNone
Selection . Columns ( 6 ) . Interior . Pattern = xlNone
Selection . Rows ( 1 ) . Interior . Pattern = xlNone
2022-04-01 16:31:23 -04:00
For i = 1 To UBound ( pcol )
Selection . Columns ( pcol ( i ) + 1 ) . Interior . Pattern = xlNone
Next i
2022-03-31 17:39:08 -04:00
'----------------------------cleanup-------------------------------------------------------------
Set x = Nothing
ini . Select
End Sub
Sub price_load_plcore ( )
Dim x As New TheBigOne 'function library
Dim load ( ) As String 'individual price list to be loaded
Dim pcol ( ) As Long 'hold the positions of each price list
2022-04-07 12:39:00 -04:00
Dim plist ( ) As String
2022-03-31 17:39:08 -04:00
Dim i As Long 'walks through each price list
Dim j As Long 'walks through each original row
Dim k As Long 'creates new rows for each price break
Dim m As Long 'row position in the new table
Dim sql As String
2022-04-07 12:39:00 -04:00
'---current setup takes 2 minutes. need to break into smaller uploads, one price list per round--
2022-03-31 17:39:08 -04:00
'-------identify the active sheet and load the contents to an array-----------
2022-04-07 12:39:00 -04:00
load = unpivot_current_sheet ( plist , pcol )
2022-03-31 17:39:08 -04:00
2022-04-07 12:39:00 -04:00
'------if no columns are labeled plist then exit------------------------------
2022-03-31 17:39:08 -04:00
2022-04-07 12:39:00 -04:00
If UBound ( pcol ) = 0 Then Exit Sub
2022-03-31 17:39:08 -04:00
2022-04-07 12:39:00 -04:00
'------clear out overlapping price lists--------------------------------------
2022-03-31 17:39:08 -04:00
2022-04-07 12:39:00 -04:00
sql = ""
For i = 1 To UBound ( plist )
If i > 1 Then
sql = sql & ",'" & plist ( i ) & "'"
Else
sql = sql & "'" & plist ( i ) & "'"
End If
Next i
sql = "DELETE FROM rlarp.plcore WHERE listcode in (" & sql & ");"
sql = sql & vbCrLf & "INSERT INTO rlarp.plcore"
sql = sql & vbCrLf & x . SQLp_build_sql_values ( load , True , True , PostgreSQL , False , "S" , "S" , "S" , "S" , "S" , "S" , "S" , "N" , "N" , "S" , "N" , "N" ) & ";"
2022-03-31 17:39:08 -04:00
2022-04-07 12:39:00 -04:00
If Not x . ADOp_Exec ( 0 , sql , 1 , True , PostgreSQLODBC , "usmidlnx01" , False , login . tbU , login . tbP , "Port=5030;Database=ubm" ) Then
MsgBox ( x . ADOo_errstring )
2022-03-31 17:39:08 -04:00
Exit Sub
End If
2022-04-07 12:39:00 -04:00
If Not x . ADOp_Exec ( 1 , sql , 1 , True , ADOinterface . SqlServer , "mid-sql02" , True ) Then
MsgBox ( x . ADOo_errstring )
Exit Sub
End If
2022-03-31 17:39:08 -04:00
Call x . ADOp_CloseCon ( 0 )
2022-04-07 12:39:00 -04:00
Call x . ADOp_CloseCon ( 1 )
2022-03-31 17:39:08 -04:00
End Sub
2022-04-07 12:39:00 -04:00
Sub build_upload ( )
2022-03-31 17:39:08 -04:00
Dim x As New TheBigOne
Dim pl ( ) As String
Dim plv ( ) As Variant
Dim i As Long
Dim j As Long
Dim ul ( ) As String
Dim pl_code As String
Dim pl_action As String
Dim dtl_action As String
Dim pl_d1 As String
Dim pl_d2 As String
Dim pl_d3 As String
Dim fd As FileDialog
Dim ulsql As String
Dim temp ( ) As String
Dim wapi As New Windows_API
pl = x . SHTp_GetString ( Selection )
ReDim ul ( 11 , UBound ( pl , 2 ) )
PRICELIST_SHOW:
Call pricelist . load_lists
pricelist . Show
If Not pricelist . proceed Then Exit Sub
pl_code = pricelist . cbLIST . value
pl_d1 = pricelist . tbD1 . text
pl_d2 = pricelist . tbD2 . text
pl_d3 = pricelist . tbD3 . text
pl_action = Mid ( pricelist . cbHDR . value , 1 , 1 )
dtl_action = Mid ( pricelist . cbDTL . value , 1 , 1 )
If Len ( pricelist . cbLIST . value ) > 5 Then
MsgBox ( "price code must be 5 or less characters" )
GoTo PRICELIST_SHOW
End If
'--------------remove any lines with errors-------------
If Not pricelist . cbInactive Then
Call x . TBLp_FilterSingle ( pl , 16 , "" , True )
End If
'--------------remove empty price lines-----------------
Call x . TBLp_FilterSingle ( pl , 13 , "" , False )
If Not pricelist . cbNonStocked Then
Call x . TBLp_FilterSingle ( pl , 8 , "A" , True )
End If
'need to get the current list of products and if they already exist for the target price list
'target price list
'target part
'target volume level
'ulsql = FL.x.SQLp_build_sql_values(pl, True, True, PostgreSQL, False)
'pl = x.TBLp_Transpose(pl)
'plv = x.TBLp_StringToVar(pl)
'ulsql = x.json_from_table(plv, "")
'ulsql = "DECLARE GLOBAL TEMPORARY TABLE session.plb AS (" & ulsql & ") WITH DATA"
' If login.tbP.Text = "" Then
' login.Show
' If Not login.proceed Then
' Exit Sub
' End If
' End If
'Call wapi.ClipBoard_SetData(ulsql)
'Exit Sub
'If Not FL.x.ADOp_Exec(0, ulsql, 1, True, ISeries, "S7830956", False, "PTROWBRIDG", "QQQX53@041") Then
' MsgBox (FL.x.ADOo_errstring)
' Exit Sub
'End If
'pl = FL.x.ADOp_SelectS(0, "SELECT p.*, CASE WHEN COALESCE(c.jcpart,'') = '' THEN '1' ELSE '2' END flag FROM Session.plb P LEFT OUTER JOIN lgdat.iprcc c ON c.jcpart = P.Item AND c.JCPLCD = '" & pl_code & "' AND c.JCVOLL = p.vbqty * cast(p.num as float) / cast(p.den as float)", True, 10000, True)
'If Not FL.x.ADOp_Exec(0, "DROP TABLE SESSION.PLB", 1, True, ISeries, "S7830956", False, login.tbU.Text, login.tbP.Text) Then
' MsgBox (FL.x.ADOo_errstring)
' Exit Sub
'End If
'Call FL.x.ADOp_CloseCon(0)
ul ( 0 , 0 ) = "HDR"
ul ( 1 , 0 ) = pl_action
ul ( 2 , 0 ) = pl_code
ul ( 3 , 0 ) = Left ( pl_d1 , 30 )
ul ( 4 , 0 ) = Left ( pl_d2 , 30 )
ul ( 5 , 0 ) = Left ( pl_d3 , 30 )
ul ( 6 , 0 ) = "Y"
ul ( 7 , 0 ) = "N"
j = 0
For i = LBound ( pl , 2 ) + 1 To UBound ( pl , 2 )
'if there is no [uom, part#, price], don't create a row
If pl ( 11 , i ) < > "" And pl ( 7 , i ) < > "" And pl ( 6 , i ) < > "" And pl ( 13 , i ) < > "" Then
j = j + 1
ul ( 0 , j ) = "DTL" 'DTL
ul ( 1 , j ) = pl_code 'Price list code
ul ( 2 , j ) = pl ( 6 , i ) 'part number
ul ( 3 , j ) = pl ( 12 , i ) 'price unit
ul ( 4 , j ) = Format ( pl ( 11 , i ) , "0.00000" ) 'volume break in price uom
ul ( 5 , j ) = Format ( pl ( 13 , i ) , "0.00000" ) 'price
ul ( 11 , j ) = dtl_action 'add, update, delete
End If
Next i
ReDim Preserve ul ( 11 , j )
'--------Open file-------------
If Not x . FILEp_CreateCSV ( pricelist . tbPATH . text & "\" & Replace ( pl_code , "." , "_" ) & ".csv" , ul ) Then
MsgBox ( "error" )
End If
'Excel.Workbooks.Open (pricelist.tbPATH.Text & "\" & Replace(pl_code, ".", "_") & ".csv")
'---------------------header row---------------------------------
End Sub
2022-04-01 16:31:23 -04:00
Function unpivot_current_sheet ( ByRef lists ( ) As String , ByRef pcol ( ) As Long ) As String ( )
Dim x As New TheBigOne 'function library
Dim sh As Worksheet 'target worksheet
Dim big ( ) As String 'all price lists in one array
Dim unpivot ( ) As String 'unwrap the columns into volume level rows
Dim load ( ) As String 'individual price list to be loaded
Dim pcount As Long 'count of price list
'Dim pcol() As Long 'hold the positions of each price list
ReDim pcol ( 30 ) 'size the array starting with 30 and trim later
ReDim lists ( 30 )
Dim dcol ( ) As Integer 'columns to be deleted
Dim typeflag ( ) As String 'array of column types
Dim i As Long 'walks through each price list
Dim j As Long 'walks through each original row
Dim k As Long 'creates new rows for each price break
Dim m As Long 'row position in the new table
Dim sql As String
'-------identify the active sheet and load the contents to an array-----------
Set sh = ActiveSheet
big = x . SHTp_Get ( sh . Name , 3 , 1 , True )
'------iterate through the column headers to identify the price lists---------
pcount = 0
For i = 0 To UBound ( big , 1 )
If big ( i , 0 ) = "plist" Then
pcount = pcount + 1
pcol ( pcount ) = i
lists ( pcount ) = big ( i , 1 )
End If
Next i
'------if no columns are labeled plist then exit------------------------------
If pcount = 0 Then Exit Function
ReDim Preserve pcol ( pcount )
ReDim Preserve lists ( pcount )
ReDim typeflag ( 9 )
'----since there are 3 price columns, those will need transformed to 3 price rows per each original-----
ReDim load ( 11 , UBound ( big , 2 ) * 3 * pcount )
m = 1
'----set headers-----
load ( 0 , 0 ) = "stlc"
load ( 1 , 0 ) = "coltier"
load ( 2 , 0 ) = "branding"
load ( 3 , 0 ) = "accs"
load ( 4 , 0 ) = "suffix"
load ( 5 , 0 ) = "uomp"
load ( 6 , 0 ) = "vol_uom"
load ( 7 , 0 ) = "vol_qty"
load ( 8 , 0 ) = "vol_price"
load ( 9 , 0 ) = "listcode"
load ( 10 , 0 ) = "orig_row"
load ( 11 , 0 ) = "orig_col"
For pcount = 1 To UBound ( pcol )
'-----populate------------
For i = 1 To UBound ( big , 2 )
'-----hard coded to number of price breaks (3)-------
For k = 0 To 2
load ( 0 , m ) = big ( 0 , i )
load ( 1 , m ) = big ( 1 , i )
load ( 2 , m ) = big ( 2 , i )
load ( 3 , m ) = big ( 3 , i )
load ( 4 , m ) = big ( 4 , i )
'----position 3 is a bulk pallet so the default UOM needs hard coded to PLT-----
If k = 2 Then
load ( 5 , m ) = "PLT"
Else
load ( 5 , m ) = big ( 5 , i )
End If
'----(3-k) should work out to 1st 2nd 3rd price colum----------------------------
'----the first column UOM is the default package, everything else is a pallet----
If k = 0 Then
load ( 6 , m ) = big ( 5 , i )
Else
load ( 6 , m ) = "PLT"
End If
'----for now the volumes are always 1 of the unit of measure in colunm 6 above
load ( 7 , m ) = "1"
load ( 8 , m ) = Format ( big ( pcol ( pcount ) - ( 3 - k ) , i ) , "####0.00" )
load ( 9 , m ) = big ( pcol ( pcount ) - 0 , i )
load ( 10 , m ) = i
load ( 11 , m ) = pcol ( pcount ) - ( 3 - k )
m = m + 1
Next k
Next i
Next pcount
If Not x . TBLp_TestNumeric ( load , 8 ) Then
MsgBox ( "price is text" )
Exit Function
End If
unpivot_current_sheet = load
End Function