Bonjour a tous.
je voudrais modifier une macro deja existente.
Cependant elle m'est incomprehensible car trop complique pour moi et mon niveau.
je vous explique rapidement, je colle dans le fichier excel des donnes a plusieurs colonnes etr lignes.
lors de lexecution de la macro, elle cree un fichier exvcel avec les donnes qui nous interessent jusquici tout va bien. J'effectue cette tache 4 fois par jour.(10h 13h30 18h et 18h15)
pour executer la macro, le createur de celle ci a mis en place un blotter qui apparait grqce q un raccourci clavier (ctrl + Q) et sur ce blotter, il y a 4 bouton pour les heures 10h 13h30 18h et 18h15. Donc je dois faire un copier coller et ensiuite appuyer sur le bon bouton qui cree un fichier avec lheure et les bonnes donnees. Tout cela se passe tres bien.
Moi ce que j'aimerais faire c'est de copier coller les donnees dans ce fichier qui contient la macro et faire tourner la macro automatiquement.
Ouvrir le fichier source et coller dans le fichier destination qui contient la macro je sais faire, mais je ne sais pas comment faire tourner la macro automatiquement surtout quil y a ce blotter avec les boutons qui sert a rien ...
je vous mets le code qui est tres long.... une recompense a la cle pour la personne qui me trouvera la reponse =)
Merci bcp Camille
Public Record_Count As Integer
Public Sub RunIt(TimeFrom As String, TimeTo As String, timeName As String)
'Set Variables
Dim Celldata As String
'Column position in the destination sheet
Dim BondPosition(1 To 100) As String
Dim BondPositionRow As Integer
'Column position in the source sheet
Dim Inputrow() As String
Dim Datecheck As Integer
Dim Tempno As String
Dim LastRowColA As Integer
Dim LastRowinDestination As Integer
Dim MyDateString As String
Dim RowCount As Integer
Dim MyVar As String
Dim icount As Integer
Dim OutputCSV As String
Dim LDate As String
Dim LTime As String
Dim MyDirectory As String
Dim MyTime As String
Dim AddTime As String
Dim MyDate As String
Dim Control As Integer
Dim InData As String
Dim BondCol() As Integer
Dim CDPosition() As String
Dim Arraysize As Integer
Dim AssetType As String
Dim InTime As Boolean
Dim TimeBoundary As String
Dim HeaderRec(1 To 144) As String
Dim BondCount As Integer
Dim CDCount As Integer
Dim TextLine1 As String
Dim TextLine2 As String
Dim TextLine3 As String
Dim HeaderRow As Integer
Dim TimeofFile As String
Dim CopyofCpty As String
Dim InfoDisplay(1 To 200) As String
Dim Net_Amount_Price As Double
Dim Net_Amount_Nominal As Double
Dim Net_Amount_Accrued As Double
Dim Net_Amount_Price_Factor As Integer
Dim OutApp As Object
Dim OutMail As Object
Dim d As Date
Dim today As Long
' Set Variables
BondPositionRow = 2 'We want the copy to destination to start on second row
MyVar = "" 'Temporary variable to do stuff
'Clear down the destination workbook before starting
LastRowinDestination = Sheets("Destination" ).Range("A65536" ).End(xlUp).Row
If LastRowDestination = 0 Then LastRowDestination = 1
'Sheets("Destination" ).Range("A2:EZ" & Trim(Str(LastRowinDestination))).ClearContents
Sheets("Destination" ).Range("A2:EZ50" ).ClearContents
'Go to the Source worksheet and find out how many rows
Sheets("Source" ).Activate
LastRowColA = Range("A65536" ).End(xlUp).Row
ReDim Inputrow(LastRowColA) 'now have an array than hold all the lines in the file
LDate = Date ' get todays date
LTime = Time ' get the current time
For i = 1 To 144 'Get the data in to the right size array
HeaderRec(i) = Cells(1, 2 + i).Text
Sheets("Destination" ).Cells(1, (i)) = Trim(HeaderRec(i))
Next i
BondCount = 0
CDCount = 0
Sheets("Source" ).Activate
TimeofFile = "00_00"
MyTimeBoundary = 0
Dim todaytext As String
Dim todaydbl As Double
todaydbl = CDbl(Year(d) * 10000 + Month(d) * 100 + Day(d))
todaytext = todaydbl
For RowCount = 2 To LastRowColA 'loop round the number of lines
AssetType = Cells(RowCount, 7).Text ' read in the asset type
MyDate = Cells(RowCount, 1).Text ' read in the date
MyTime = Cells(RowCount, 2).Text ' read in the time
'AddTime = Mid(MyTime, 1, 2) + 1
'MyTime = AddTime & Mid(MyTime, 3, 8)
InTime = False
Arraysize = 33
ReDim BondCol(Arraysize)
ReDim CDPosition(Arraysize)
BondCol(1) = 3
BondCol(2) = 4
BondCol(3) = 5
BondCol(4) = 7
BondCol(5) = 8
BondCol(6) = 12
BondCol(7) = 14
BondCol(8) = 21
BondCol(9) = 22
BondCol(10) = 23
BondCol(11) = 25
BondCol(12) = 29
BondCol(13) = 30
BondCol(14) = 31
BondCol(15) = 32
BondCol(16) = 34
BondCol(17) = 35
BondCol(18) = 36
BondCol(19) = 37
BondCol(20) = 47
BondCol(21) = 49
BondCol(22) = 50
BondCol(23) = 51
BondCol(24) = 55
BondCol(25) = 57
BondCol(26) = 61
BondCol(27) = 73
BondCol(28) = 74
BondCol(29) = 106
BondCol(30) = 141
BondCol(31) = 142
BondCol(32) = 143
BondCol(33) = 144
Control = 1
For i = 1 To Arraysize 'Get the data in to the right size array
CDPosition(i) = Cells(RowCount, BondCol(i)).Value
Next i
'MyTime is the time on the trade extract
'LTime is the time of the network server
'TimeNo() is just a function that allows you to evaluate time
'The time limit on LTime has been adjusted by 15 minutes to allow trades entered upto the cut off date being included
'if not custumized time then base the time frame on date of run
If TimeFrom = " " Then
MsgBox ("wrong predefined time frame" )
'If (TimeNo(MyTime) > TimeNo("18:01:00" ) And TimeNo(LTime) <= TimeNo("10:15:00" )) Then
' InTime = True
' MyTimeBoundary = "10_00"
'End If
'If (TimeNo(MyTime) <= TimeNo("10:00:00" ) And TimeNo(LTime) <= TimeNo("10:15:00" )) Then
' InTime = True
' MyTimeBoundary = "10_00"
'End If
'If (TimeNo(MyTime) <= TimeNo("12:00:00" ) And TimeNo(MyTime) > TimeNo("10:00:00" )) Then
' If (TimeNo(LTime) <= TimeNo("12:15:00" ) And TimeNo(LTime) > TimeNo("10:15:00" )) Then
' InTime = True '
' MyTimeBoundary = "12_00"
' End If
'End If
'If (TimeNo(MyTime) <= TimeNo("13:30:00" ) And TimeNo(MyTime) > TimeNo("12:00:00" )) Then
' If (TimeNo(LTime) <= TimeNo("13:45:00" ) And TimeNo(LTime) > TimeNo("12:15:00" )) Then
' InTime = True
' MyTimeBoundary = "13_30"
' End If
'
' End If
'If (TimeNo(MyTime) <= TimeNo("15:00:00" ) And TimeNo(MyTime) > TimeNo("13:30:00" )) Then
' If (TimeNo(LTime) <= TimeNo("15:15:00" ) And TimeNo(LTime) > TimeNo("13:45:00" )) Then
' InTime = True '
' MyTimeBoundary = "15_00"
' End If
'End If
'If (TimeNo(MyTime) <= TimeNo("18:10:00" ) And TimeNo(MyTime) > TimeNo("15:00:00" )) Then
' If (TimeNo(LTime) <= TimeNo("18:15:00" ) And TimeNo(LTime) > TimeNo("15:15:00" )) Then
' InTime = True
' MyTimeBoundary = "18_00"
' End If
'
'End If
'If (TimeNo(LTime) > TimeNo("18:15:00" )) Then
' InTime = True
' MyTimeBoundary = "18_15"
'End If
'use the customized time frame
Else
'MsgBox ("customized time frame" )
todaytext = Mid(LDate, 7, 4) & Mid(LDate, 4, 2) & Mid(LDate, 1, 2)
'if time from is after timeto we consider this is from yesterday
If TimeDo(TimeFrom) > TimeDo(TimeTo) Then
'then just check time for from
If MyDate < todaytext Then
If TimeDo(MyTime) > TimeDo(TimeFrom & ":00" ) Then
InTime = True
End If
Else
If (TimeDo(MyDate & MyTime) <= TimeDo(todaytext & TimeTo & ":00" )) Then
InTime = True
End If
End If
Else
If TimeDo(MyDate & MyTime) > TimeDo(todaytext & TimeFrom & ":00" ) And (TimeDo(MyDate & MyTime) <= TimeDo(todaytext & TimeTo & ":00" )) Then
InTime = True
End If
End If
End If
If InTime = True Then
' MyTimeBoundary = Replace(TimeFrom & "_" & TimeTo, ":", "_" )
MyTimeBoundary = Replace(timeName, ":", "_" )
' MsgBox (RowCount & " is in" )
Else
'MsgBox (RowCount & " is NOT in time" )
End If
TimeofFile = MyTimeBoundary
For icount = 1 To Arraysize
Celldata = CDPosition(icount) ' read in the value
Select Case icount ' Dependent upon position in array, no blanks
Case Is = 1
BondPosition(icount) = "A" 'TRN_NB - Trade Id
Case Is = 2
Select Case Celldata
Case Is = "New"
Celldata = "New"
Case Is = "Cancelled"
Celldata = "Delete"
Case Else
Celldata = "ERR"
End Select
BondPosition(icount) = "B" 'Last Action - New,Update,Cancel
InfoDisplay(RowCount) = Celldata
Case Is = 3
BondPosition(icount) = "C" 'Buy/Sell - Buy/Sell
InfoDisplay(RowCount) = InfoDisplay(RowCount) & " " & Celldata
Case Is = 4 ' determine Bond or CP
BondPosition(icount) = "E" 'Typology - Bond
MyVar = Celldata
Select Case MyVar
Case Is = "Bond"
Celldata = "Bond"
Case Is = "CP"
Celldata = "CP"
Case Else
Celldata = "CD"
End Select
Case Is = 5
BondPosition(icount) = "F" 'Client Investment ID
Select Case MyVar
Case Is = "Bond"
'BondPosition(icount) = "L" 'Security Code - ISIN
Celldata = ""
Case Else
End Select
Case Is = 6
BondPosition(icount) = "J" 'Exchange
Select Case MyVar
Case Is = "Bond"
'BondPosition(icount) = "S" 'Quantity - Notional
Celldata = ""
Case Else
End Select
Case Is = 7
BondPosition(icount) = "L" 'ISIN
Select Case MyVar
Case Is = "Bond"
'BondPosition(icount) = "T" 'Clean price - Price
'Celldata = ""
Case Else
End Select
Case Is = 8
BondPosition(icount) = "S" 'Quantity - Notional
Net_Amount_Nominal = Celldata
Select Case MyVar
Case Is = "Bond"
'BondPosition(icount) = "U" 'Accrued
Case Else
End Select
Case Is = 9
BondPosition(icount) = "T" 'Price
Net_Amount_Price = CDPosition(icount)
Select Case MyVar
Case Is = "Bond"
'BondPosition(icount) = "AB" 'Counterparty label - Broker
Case Else
End Select
Case Is = 10
BondPosition(icount) = "U" 'Accrued Interest
Net_Amount_Accrued = CDPosition(icount)
Select Case MyVar
Case Is = "Bond"
'BondPosition(icount) = "AC" 'Trade date - Transaction date
Case Else
End Select
Case Is = 11
BondPosition(icount) = "W" 'Commission Fees
Celldata = "0.0"
Case Is = 12
BondPosition(icount) = "AA" 'Net Amount
Net_Amount_Price_Factor = "100"
Celldata = Round(((Net_Amount_Nominal * Net_Amount_Price) / Net_Amount_Price_Factor) + Net_Amount_Accrued, 2)
Case Is = 13
BondPosition(icount) = "AB" 'Counterpart
Select Case MyVar
Case Is = "Bond"
'BondPosition(icount) = "AD" 'Settlement date - Settle date
Case Else
CopyofCpty = Celldata
End Select
Case Is = 14
BondPosition(icount) = "AC" 'Trade date - Transaction date
Select Case MyVar
Case Is = "Bond"
'BondPosition(icount) = "AG" 'Fixed field - Custodian Account - Fund-ID e.g.
'Celldata = "ESM1"
Case Else
End Select
Case Is = 15
BondPosition(icount) = "AD" 'Settle Date
Select Case MyVar
Case Is = "Bond"
'BondPosition(icount) = "AI" 'Strategy
'Celldata = "ESMDEFAULT"
Case Else
End Select
Case Is = 16
BondPosition(icount) = "AF" 'Settle Currency
Select Case MyVar
Case Is = "Bond"
'BondPosition(icount) = "EI" 'Contract Nb - Block ID
Case Else
End Select
Case Is = 17
BondPosition(icount) = "AG" 'Fixed field - Custodian Account - Fund-ID e.g. ESM1
If Celldata = "M_LBI" Or Celldata = "M_INVT_FEES" Then
Celldata = "ESM2"
Else
Celldata = "ESM1"
End If
Case Is = 18
BondPosition(icount) = "AI" 'Strategy
Celldata = "ESMDEFAULT"
Case Is = 19
BondPosition(icount) = "AN" 'Counterpart
If MyVar <> "Bond" Then
Celldata = CopyofCpty
End If
Case Is = 20
BondPosition(icount) = "AS" 'Maturity
If AssetType = "Bond" Then Celldata = ""
Case Is = 21
BondPosition(icount) = "AU" 'Interest Basis
'ACT/360,30/365,ACT/366,Actual/365,Actual/Actual
Select Case MyVar
Case Is = "Bond"
Celldata = ""
Case Else
MyDateString = Celldata
Select Case MyDateString
Case Is = "N A/A I"
Celldata = "ACT/ACT"
Case Is = "ACT/360"
Celldata = "ACT/360"
Case Is = "ACT/365"
Celldata = "Actual/365"
Case Is = "ACT/ACT"
Celldata = "Actual/Actual"
Case Else
Celldata = Celldata
End Select
End Select
Case Is = 22
BondPosition(icount) = "AV" 'Coupon Payment
'182DAYS,364DAYS,91DAYS,BI -ANNUAL,BI -MONTHLY,BI -MONTHLY,
'BI -WEEKLY,DAILY,IAM,LUNAR,MONTHLY,NONE,QUARTERLY,SEMI -ANNUAL,WEEKLY,YEARLY
Select Case MyVar
Case Is = "Bond"
Celldata = ""
Case Else
Select Case Celldata
Case Is = "1y"
Celldata = "YEARLY"
Case Is = "0od"
Celldata = "NONE"
Case Else
Celldata = Celldata
End Select
End Select
Case Is = 23
BondPosition(icount) = "AW" 'Interest Rate
If MyVar = "Bond" Then Celldata = ""
Case Is = 24
BondPosition(icount) = "BA" 'Spread
If MyVar = "Bond" Then Celldata = ""
Case Is = 25
BondPosition(icount) = "BC" 'Accrual Start date
Select Case MyVar
Case Is = "Bond"
Celldata = ""
Case Else
If InStr(1, Celldata, "/" ) <> 0 Then
MyDateString = Mid(Celldata, 7, 4)
MyDateString = MyDateString & Mid(Celldata, 4, 2) & Mid(Celldata, 1, 2)
Celldata = MyDateString
End If
End Select
Case Is = 26
BondPosition(icount) = "BG" 'First Coupon Date
Select Case MyVar
Case Is = "Bond"
Celldata = ""
Case Else
If InStr(1, Celldata, "/" ) <> 0 Then
MyDateString = Mid(Celldata, 7, 4)
MyDateString = MyDateString & Mid(Celldata, 4, 2) & Mid(Celldata, 1, 2)
Celldata = MyDateString
End If
End Select
Case Is = 27
BondPosition(icount) = "BS" 'Issue Date
Select Case MyVar
Case Is = "Bond"
Celldata = ""
Case Else
If InStr(1, Celldata, "/" ) <> 0 Then
MyDateString = Mid(Celldata, 7, 4)
MyDateString = MyDateString & Mid(Celldata, 4, 2) & Mid(Celldata, 1, 2)
Celldata = MyDateString
End If
End Select
Case Is = 28
BondPosition(icount) = "BT" 'Issue country
If MyVar = "Bond" Then Celldata = ""
Case Is = 29
BondPosition(icount) = "CZ" 'Reset Frequency
Select Case MyVar
Case Is = "Bond"
Celldata = ""
Case Else
MyDateString = Celldata
Select Case MyDateString
Case Is = "1y"
Celldata = "YEARLY"
Case Is = "0od"
Celldata = "NONE"
End Select
End Select
Case Is = 30
BondPosition(icount) = "EI" 'Block Id
Case Is = 31
BondPosition(icount) = "EJ" 'Security Description
If MyVar = "Bond" Then Celldata = ""
Case Is = 32
BondPosition(icount) = "EK" 'Issue Price
If MyVar = "Bond" Then Celldata = ""
Case Is = 33
BondPosition(icount) = "EL" 'Maturity Price
If MyVar = "Bond" Then Celldata = ""
End Select
If InTime Then
Sheets("Destination" ).Range(BondPosition(icount) & Trim(Str(BondPositionRow))) = Trim(Celldata)
End If
Next icount
If InTime Then
BondPositionRow = BondPositionRow + 1
If MyVar = "Bond" Then
BondCount = BondCount + 1
Else
CDCount = CDCount + 1
End If
End If
Next RowCount
'generate directory and filename from Date and Time - but this should be 10 12 15 18 files
'Check to see if the directory has been created for today, if not create it
OutputCSV = "M:\01_Murex\Citi\Citi Trade Extracts\" & Mid(LDate, 7, 4) & "_" & Mid(LDate, 4, 2) & "_" & Mid(LDate, 1, 2) 'This one
'OutputCSV = "H:\Citi Trade Extracts\" & Mid(LDate, 7, 4) & "_" & Mid(LDate, 4, 2) & "_" & Mid(LDate, 1, 2) 'For testing
' OutputCSV = "C:\" & Mid(LDate, 7, 4) & "_" & Mid(LDate, 4, 2) & "_" & Mid(LDate, 1, 2)
If Len(Dir(OutputCSV, vbDirectory)) = 0 Then
MkDir OutputCSV
End If
'Create the filename out of the time and append to the directory
If timeName = "18:15" Then
OutputCSV = OutputCSV & "\EFSFGCCA_EFSF_Summary_Trade_"
OutputCSV = OutputCSV & Mid(LDate, 7, 4)
OutputCSV = OutputCSV & Mid(LDate, 4, 2)
OutputCSV = OutputCSV & Mid(LDate, 1, 2) & ".csv"
Else
OutputCSV = OutputCSV & "\EFSFGCCA_EFSF_Trade_"
OutputCSV = OutputCSV & Mid(LDate, 7, 4)
OutputCSV = OutputCSV & Mid(LDate, 4, 2)
OutputCSV = OutputCSV & Mid(LDate, 1, 2) & "_" & TimeofFile & ".csv"
End If
Application.DisplayAlerts = False
'Now copy the trade file contents to a CSV file
'LastRowinDestination = Sheets("Destination" ).Range("A65536" ).End(xlUp).Row
If (BondCount > 0) Or (CDCount > 0) Then
LastRowinDestination = Sheets("Destination" ).Range("A1" ).End(xlDown).Row
Sheets("Destination" ).Range("A1:EO" & Trim(Str(LastRowinDestination))).Copy
Workbooks.Add
ActiveSheet.Paste
ActiveWorkbook.SaveAs Filename:= _
OutputCSV _
, FileFormat:=xlCSV, CreateBackup:=False
Application.DisplayAlerts = False
End If
' Display a message giving the user some feedback
If (BondCount > 0) Or (CDCount > 0) Then
TextLine1 = "A file has been created for " & MyTimeBoundary & ""
TextLine2 = "It contains " & Str(BondCount) & " Bonds and " & Str(CDCount) & " CD/CPs"
TextLine3 = "The file has been created - Press OK to continue"
ActiveWorkbook.Close ' Close the CSV file
Else
TextLine1 = "NO Trades so NO file created "
TextLine2 = "" & Str(BondCount) & " Bonds and " & Str(CDCount) & " CD/CPs" & "were found"
TextLine3 = "The file has NOT been created - Press OK to continue"
End If
If MsgBox(TextLine1 & vbCrLf & TextLine2 & vbCrLf & InfoDisplay(1) & vbCrLf & InfoDisplay(1) & vbCrLf & TextLine3, vbOKOnly, OutputCSV) = vbYes Then
InTime = False
Else
InTime = False
End If
Application.DisplayAlerts = True
End Sub
Public Function TimeNo(Time As String) As Long
TimeNo = CLng(Replace(Format(Time, "hhnnss" ), ":", "" ))
End Function
Public Function TimeDo(Time As String) As Double
TimeDo = CDbl(Replace(Time, ":", "" ))
End Function