diff options
Diffstat (limited to 'vba/corp cdo prices.vba')
| -rw-r--r-- | vba/corp cdo prices.vba | 357 |
1 files changed, 357 insertions, 0 deletions
diff --git a/vba/corp cdo prices.vba b/vba/corp cdo prices.vba new file mode 100644 index 00000000..08ac023b --- /dev/null +++ b/vba/corp cdo prices.vba @@ -0,0 +1,357 @@ +Option Explicit + +Function questionmarks(size) As String + Dim qarray() As String + ReDim qarray(1 To size) + Dim i As Integer + For i = 1 To size + qarray(i) = "?" + Next i + questionmarks = Join(qarray, ",") +End Function + +Sub getdata() + 'cusipRange = Range(ActiveCell, ActiveCell.End(xlDown)) + Dim cn As New ADODB.Connection + Dim cmd As New ADODB.Command + + Dim rs As New ADODB.Recordset + + Dim Notional As Variant + Dim DisableReinv As Variant + Dim Cusip As Object + + Notional = Selection.Offset(0, 4).Value + DisableReinv = Selection.Offset(0, 7).Value + Set cn = DBConn() + + Application.EnableEvents = False + + With cmd + .ActiveConnection = cn + .CommandType = adCmdText + For Each Cusip In Selection + .Parameters.Append .CreateParameter(, adChar, adParamInput, 13, Trim(Cusip)) + Next Cusip + .CommandText = "SELECT * FROM et_cusip_details(" & questionmarks(Selection.Count) & ")" + End With + + Set rs = cmd.Execute + ActiveCell.Offset(0, 2).CopyFromRecordset rs + rs.Close + cn.Close + Selection.Offset(0, 4).Value = Notional + Selection.Offset(0, 7).Value = DisableReinv + Application.EnableEvents = True +End Sub +Sub savecolor() + 'cusipRange = Range(ActiveCell, ActiveCell.End(xlDown)) + Dim cn As New ADODB.Connection + Dim cmd As New ADODB.Command + + Dim Cusip As Object + Set cn = DBConn() + + Application.EnableEvents = False + + With cmd + .ActiveConnection = cn + .CommandType = adCmdText + .Parameters.Append .CreateParameter("ListDate", adDate, adParamInput) + .Parameters.Append .CreateParameter("ListInfo", adVarChar, adParamInput, 20) + .Parameters.Append .CreateParameter("Cusip", adChar, adParamInput, 9) + .Parameters.Append .CreateParameter("Notional", adDouble, adParamInput) + .Parameters.Append .CreateParameter("Indications", adVarChar, adParamInput, 100) + .Parameters.Append .CreateParameter("Cover", adVarChar, adParamInput, 100) + .Parameters.Append .CreateParameter("ListColor", adVarChar, adParamInput, 100) + .Parameters.Append .CreateParameter("Bid", adVarChar, adParamInput, 100) + .Parameters.Append .CreateParameter("BidNote", adVarChar, adParamInput, 100) + For Each Cusip In Selection + .Parameters("ListDate") = Cusip.Offset(0, -2) + .Parameters("ListInfo") = Cusip.Offset(0, -1) + .Parameters("Cusip") = Trim(Cusip) + .Parameters("Notional") = Cusip.Offset(0, 4) + .Parameters("Indications") = Cusip.Offset(0, 31) + .Parameters("Cover") = Cusip.Offset(0, 32) + .Parameters("ListColor") = Cusip.Offset(0, 33) + .Parameters("Bid") = Cusip.Offset(0, 29) + .Parameters("BidNote") = Cusip.Offset(0, 30) + .CommandText = "INSERT INTO color VALUES(" & questionmarks(cmd.Parameters.Count) & ")" + .Execute + Next Cusip + End With + cn.Close + Application.EnableEvents = True +End Sub +Sub getcolor() + 'cusipRange = Range(ActiveCell, ActiveCell.End(xlDown)) + Dim cn As New ADODB.Connection + Dim cmd As New ADODB.Command + + Dim rs As New ADODB.Recordset + + Dim Cusip As Object + + Set cn = DBConn() + + Application.EnableEvents = False + + With cmd + .ActiveConnection = cn + .CommandType = adCmdText + .Parameters.Append .CreateParameter("Cusip", adChar, adParamInput, 9) + For Each Cusip In Selection + .Parameters("Cusip") = Trim(Cusip) + .CommandText = "select max(listdate), string_agg(listinfo, ',') as listinfo, string_agg(bid,',') as bid," & _ + "string_agg(bid_note,',') as bid_note, sum(notional) as notional," & _ + "string_agg(indications,',') as indications, string_agg(cover,',') as cover, " & _ + "string_agg(listcolor,',') as listcolor from latest_color where cusip=?" + Set rs = cmd.Execute + Cusip.Offset(0, 37).CopyFromRecordset rs + Next Cusip + End With + rs.Close + cn.Close + Application.EnableEvents = True +End Sub + +Sub getintexdealnames() + Dim cn As New ADODB.Connection + Dim cmd As New ADODB.Command + + Dim rs As New ADODB.Recordset + Dim Clip As New DataObject + + Dim firsttime As Boolean + Set cn = DBConn() + Dim dealnameArray As Variant + Dim cliptext As String + Dim Cusip As Object + Dim i As Integer + + Application.EnableEvents = False + With cmd + .ActiveConnection = cn + .CommandType = adCmdText + For Each Cusip In Selection + .Parameters.Append .CreateParameter(, adChar, adParamInput, 10, Trim(Cusip)) + Next Cusip + .CommandText = "SELECT * FROM dealname_from_cusip(" & questionmarks(Selection.Count) & ")" + End With + + Set rs = cmd.Execute + dealnameArray = rs.GetRows() + + For i = 0 To Selection.Count - 1 + cliptext = cliptext & dealnameArray(0, i) & vbNewLine + Next + Clip.SetText cliptext + Clip.PutInClipboard + rs.Close + cn.Close + Application.EnableEvents = True +End Sub + +Sub getallcusips() + Dim cn As New ADODB.Connection + Dim cmd As New ADODB.Command + + Dim rs As New ADODB.Recordset + Dim Clip As New DataObject + + Set cn = DBConn() + Dim cusipArray, dealnameArray As Variant + Dim cliptext As String + Dim Cusip As Object + Dim i As Integer + + Application.EnableEvents = False + With cmd + .ActiveConnection = cn + .CommandType = adCmdText + For Each Cusip In Selection + .Parameters.Append .CreateParameter(, adChar, adParamInput, 10, Trim(Cusip)) + Next Cusip + .CommandText = "SELECT * FROM dealname_from_cusip(" & questionmarks(Selection.Count) & ")" + End With + + Set rs = cmd.Execute + dealnameArray = rs.GetRows() + + Set cmd = New ADODB.Command + With cmd + .ActiveConnection = cn + .CommandType = adCmdText + For i = 0 To Selection.Count - 1 + .Parameters.Append .CreateParameter(, adChar, adParamInput, 10, dealnameArray(0, i)) + Next i + .CommandText = "SELECT DISTINCT cusip FROM latest_cusip_universe where dealname IN (" & questionmarks(Selection.Count) & ")" + End With + + Set rs = cmd.Execute + cusipArray = rs.GetRows() + + For i = 0 To UBound(cusipArray, 2) + cliptext = cliptext & cusipArray(0, i) & vbNewLine + Next + Clip.SetText cliptext + Clip.PutInClipboard + rs.Close + cn.Close + Application.EnableEvents = True + +End Sub + +Sub savedeals_to_price() + + 'Just showing where the input data are + Dim cn As New ADODB.Connection + Dim cmd As New ADODB.Command + Dim rs As New ADODB.Recordset + Set cn = DBConn() + Dim cusipArray, dealnameArray, dealnameArrayuniq As Variant + Dim sqlstr, Data As String + Dim dealname As Variant + Dim i As Integer + Dim key As Variant + + Dim filename As String + Dim fh As Integer + Dim Cusip As Object + Dim noreinvindex As New Scripting.Dictionary + Dim noreinvdeal As New Scripting.Dictionary + Application.EnableEvents = False + + filename = "\\WDSENTINEL\share\CorpCDOs\scripts\deals_to_price.txt" + + 'Get an unused file number + fh = FreeFile + 'Create a new file (or overwrite an existing one) + Open filename For Output As fh + + key = 0 + With cmd + .ActiveConnection = cn + .CommandType = adCmdText + For Each Cusip In Selection + .Parameters.Append .CreateParameter(, adChar, adParamInput, 10, Trim(Cusip)) + If Cusip.Offset(0, 7) = "Y" Then + noreinvindex.Add key, 1 + End If + key = key + 1 + Next Cusip + .CommandText = "SELECT * FROM dealname_from_cusip(" & questionmarks(Selection.Count) & ")" + End With + + Set rs = cmd.Execute + dealnameArray = rs.GetRows() + + For Each key In noreinvindex.Keys() + noreinvdeal.Add dealnameArray(0, key), 1 + Next + + cmd.CommandText = "SELECT distinct * FROM dealname_from_cusip(" & questionmarks(Selection.Count) & ")" + Set rs = cmd.Execute + dealnameArrayuniq = rs.GetRows() + For Each dealname In dealnameArrayuniq + If Not IsNull(dealname) Then + If Not noreinvdeal.Exists(dealname) Then + sqlstr = "Select ""Reinv End Date"" from latest_clo_universe where dealname = '" & dealname & "'" + Set rs = cn.Execute(sqlstr) + Data = rs.GetString() + If Len(Data) > 1 Then + Print #fh, dealname & vbTab & "TRUE" + Else + Print #fh, dealname & vbTab & "FALSE" + End If + Else + Print #fh, dealname & vbTab & "FALSE" + End If + End If + Next dealname + + 'Close the file + Close #fh +End Sub + +Sub generate_intex_portfolio() + Dim cn As New ADODB.Connection + Dim cmd As New ADODB.Command + + Dim rs As New ADODB.Recordset + Dim Clip As New DataObject + + Set cn = DBConn() + Dim cusipArray, dealnameArray, dealnameArrayuniq As Variant + Dim cliptext As String + Dim Cusip As Object + Dim sqlstr, Data As String + Dim dealname As Variant + Dim i As Integer + Dim key As Variant + + Dim noreinvindex As New Scripting.Dictionary + Dim noreinvdeal As New Scripting.Dictionary + Application.EnableEvents = False + + key = 0 + With cmd + .ActiveConnection = cn + .CommandType = adCmdText + For Each Cusip In Selection + .Parameters.Append .CreateParameter(, adChar, adParamInput, 10, Trim(Cusip)) + If Cusip.Offset(0, 7) = "Y" Then + noreinvindex.Add key, 1 + End If + key = key + 1 + Next Cusip + .CommandText = "SELECT * FROM dealname_from_cusip(" & questionmarks(Selection.Count) & ")" + End With + + Set rs = cmd.Execute + dealnameArray = rs.GetRows() + + For Each key In noreinvindex.Keys() + noreinvdeal.Add dealnameArray(0, key), 1 + Next + + cmd.CommandText = "SELECT distinct * FROM dealname_from_cusip(" & questionmarks(Selection.Count) & ")" + Set rs = cmd.Execute + dealnameArrayuniq = rs.GetRows() + For Each dealname In dealnameArrayuniq + If Not IsNull(dealname) Then + If Not noreinvdeal.Exists(dealname) Then + sqlstr = "Select ""Reinv End Date"" from latest_clo_universe where dealname = '" & dealname & "'" + Set rs = cn.Execute(sqlstr) + Data = rs.GetString() + If Len(Data) > 1 Then + cliptext = cliptext & UCase(dealname) & "," & "COLLAT_INITIAL" & vbTab + cliptext = cliptext & dealname & ".sss" & vbNewLine + cliptext = cliptext & UCase(dealname) & "," & "COLLAT_REINVEST" & vbTab + cliptext = cliptext & dealname & ".sss" & vbNewLine + Else + cliptext = cliptext & UCase(dealname) & "," & "COLLAT" & vbTab + cliptext = cliptext & dealname & ".sss" & vbNewLine + End If + Else + cliptext = cliptext & UCase(dealname) & "," & "COLLAT" & vbTab + cliptext = cliptext & dealname & ".sss" & vbNewLine + End If + End If + Next dealname + + i = 1 + For Each Cusip In Selection + If Not IsNull(dealnameArray(0, i - 1)) Then + cliptext = cliptext & Cusip & vbTab & dealnameArray(0, i - 1) & ".sss" & vbNewLine + End If + i = i + 1 + Next Cusip + + Clip.SetText cliptext + Clip.PutInClipboard + rs.Close + cn.Close + Application.EnableEvents = True + +End Sub |
