sort data


Posted by emma on March 26, 2001 3:23 AM

all my data is on the one column, i.e all dates are in a list and I want a different column for each month, how do I do this

Posted by Dave on March 26, 2001 3:48 AM

I would presume the quickest way would be to sort all data in date order & then drag & drop each months data into a new column

Posted by emma on March 26, 2001 4:29 AM




Posted by bj on March 27, 2001 6:58 PM


If the dates are in column A starting in A2, try this :-

Sub Columns_By_Month()
Dim dates As Range, lastRow%
Dim theDates As Variant, months As Variant
Dim m#, d#, c%, x%
Set dates = Range(Range("A2"), Range("A65536").End(xlUp))
lastRow = dates.Rows.Count + 1
Application.ScreenUpdating = False
Columns("A:A").Insert Shift:=xlToRight
Rows("2:" & lastRow).Sort Key1:=Range("B2")
dates.Offset(0, -1).FormulaR1C1 = _
"=TEXT(RC[1],""mmm"") & ""-"" & RIGHT(YEAR(RC[1]),2)"
theDates = Application.Transpose(dates.Offset(0, -1))
m = 0
For d = LBound(theDates) To UBound(theDates)
If m = 0 Then
m = 1
ReDim months(1 To 1)
months(1) = theDates(d)
Else
If theDates(d) <> theDates(d - 1) Then
m = m + 1
ReDim Preserve months(1 To m)
months(m) = theDates(d)
End If
End If
Next
Rows("1:1").NumberFormat = "@"
Range(Range("C1"), Cells(1, UBound(months) + 2)).Value = months
With Range(Range("C2"), Cells(lastRow, UBound(months) + 2))
.FormulaR1C1 = "=IF(ISNA(VLOOKUP(R1C,RC1:RC2,2,FALSE))" & _
","""",VLOOKUP(R1C,RC1:RC2,2,FALSE))"
.Copy
.PasteSpecial Paste:=xlValues
.NumberFormat = "m/d/yy"
End With
x = 3
c = Range(Range("C1"), Cells(1, UBound(months) + 2)).Cells.Count + 2
For x = 3 To c
Columns(x).Sort Key1:=Cells(1, x), Header:=xlYes
Next
Columns("A:A").Select
Selection.Delete Shift:=xlToLeft
End Sub