Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations TouchToneTommy on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

order items in combobox in mid position

Status
Not open for further replies.

2009luca

Programmer
Jul 27, 2013
222
IT
i have a items in combobox, similar:

0100-(26.867)-AAA
0101-(6.155)-BBB
0102-(40)-CCC
0103-(5.048)-DDD
0143-(12.949)-AAA
0146-(9.677)-DDD
0149-(12.039)-FFF
...

i need to order items based number in (.....).

note:
the length value in braket are variable
 
Where do you get the items from? A table in the data base? If so, what's your Select statement to get these numbers?

Is the number like this one: [tt]0100-(26.867)-AAA[/tt] in one field in the DB?
Or:
[pre]
FieldA FieldB FieldC
0100 (26.867) AAA
0101 (6.155) BBB
0102 (40) CCC
[/pre]

Have fun.

---- Andy

A bus station is where a bus stops. A train station is where a train stops. On my desk, I have a work station.
 
TKS!
no... from a .txt file and i fill the combobox from a piece of line.
 
Some assumptions based on your example:[tt]
0100-([red]26.867[/red])-AAA[/tt]
your numbers always starts at the 7th position and the numbers are unique.

Code:
Option Explicit

Private Sub Command1_Click()
Dim i As Integer
Dim x As Integer
Dim ary(6) As String
Dim aryNew(6) As Single

ary(0) = "0100-(26.867)-AAA"
ary(1) = "0101-(6.155)-BBB"
ary(2) = "0102-(40)-CCC"
ary(3) = "0103-(5.048)-DDD"
ary(4) = "0143-(12.949)-AAA"
ary(5) = "0146-(9.677)-DDD"
ary(6) = "0149-(12.039)-FFF"

'Pick just the numbers from (xxx)
For i = LBound(ary) To UBound(ary)
    aryNew(i) = Mid(ary(i), 7, InStr(ary(i), ")") - 7)
Next i

'Show what we have
For i = LBound(aryNew) To UBound(aryNew)
    Debug.Print aryNew(i)
Next i

Call Sort(aryNew)

'Show sorted numbers
For i = LBound(aryNew) To UBound(aryNew)
    Debug.Print aryNew(i)
Next i

Combo1.Clear

For i = LBound(aryNew) To UBound(aryNew)
    For x = LBound(ary) To UBound(ary)
        If InStr(ary(x), aryNew(i)) Then
            Combo1.AddItem ary(x)
        End If
    Next x
Next i

End Sub

Private Sub Swap(a As Variant, b As Variant)
Dim t As Variant
    'Swap a and b
    t = a
    a = b
    b = t
End Sub

Private Sub Sort(arr As Variant)
Dim x As Long, Y As Long, Size As Long
On Error Resume Next
    'Get array size
    Size = UBound(arr)
    
    'Do the sorting.
    For x = 0 To Size
        For Y = x To Size
            If arr(Y) < arr(x) Then
                'Swap vals
                Call Swap(arr(x), arr(Y))
            End If
        Next Y
    Next x
End Sub

you get in the Combo1:
[tt]
0103-(5.048)-DDD
0101-(6.155)-BBB
0146-(9.677)-DDD
0149-(12.039)-FFF
0143-(12.949)-AAA
0100-(26.867)-AAA
0102-(40)-CCC
[/tt]

Have fun.

---- Andy

A bus station is where a bus stops. A train station is where a train stops. On my desk, I have a work station.
 
Tks!
But i think the value (40) is the the top of the list...
All value in basket are number...
 
Are you saying [tt]40 < 5.048[/tt] ???
That's not the math I know...

Have fun.

---- Andy

A bus station is where a bus stops. A train station is where a train stops. On my desk, I have a work station.
 
I would guess you are from Europe, or some other place where . (period) is the thousand separator and , (comma) is the ‘decimal’ separator.

So when you say: [tt]
5.048[/tt] for me is = [tt]5 + 0.048[/tt]
And what you would say:[tt]
5,048[/tt] is = [tt]5 + 0,048[/tt]

On my end [tt]5.048[/tt] is a little over 5.
I believe that’s where the confusion comes from... [ponder]


Have fun.

---- Andy

A bus station is where a bus stops. A train station is where a train stops. On my desk, I have a work station.
 
But if the regional setting are correctly set, then it shouldn't matter. Casting from string to single, as happens here:

aryNew(i) = Mid(ary(i), 7, InStr(ary(i), ")") - 7)

should follow the regional settings rules.
 
That isn't "casting" at all but instead coercion which involves conversion, a very different thing entirely. But coercion in VB6 is indeed locale-aware.

Unless you have a vast list of items, which is an absurd thing to jam into a ComboBox anyway, sorting doesn't buy a lot over simple insertion. To deal with the locale issue I use my VConvert Class:

VConvert.cls
Code:
Option Explicit
'
'VConvert
'--------
'
'A VB6 class used to convert between Variant types using a specific
'locale instead of the current program locale.
'
'This is most useful with LOCALE_INVARIANT for non-String typed data
'that is perisisted or communicated as String data.  This avoids
'cross-cultural factors related to language, the decimal point
'character, etc.
'
'It can also be used with conversions of data between a user
'interface and data where your code assumes a fixed locale and you
'want to insist users work in that locale even when the user locale
'is an entirely different one.  Note that this is not a recommended
'practice for most software!
'
'Example:
'
'    Program always expects dates to be entered in U.S. format,
'    i.e. mm/dd/yyyy but some users have U.K. settings which make
'    locale-aware conversions such as CDate() expect strings in
'    dd/mm/yyyy format.
'

Private Const S_OK As Long = 0
Private Const VARIANT_ALPHABOOL As Long = &H2&
Private Const VARIANT_LOCALBOOL As Long = &H10&

Public Enum LOCALE_VALUES
    'Add more as you need them here:
    LOCALE_INVARIANT = &H7F&
    LOCALE_USER = &H100&
    LOCALE_SYSTEM = &H200&
    
    LOCALE_GERMANY = &H407&
End Enum

Private Declare Function VariantChangeTypeEx Lib "oleaut32" ( _
    ByRef vargDest As Variant, _
    ByRef varSrc As Variant, _
    ByVal desiredlcid As Long, _
    ByVal wFlags As Integer, _
    ByVal vt As VbVarType) As Long

Public LCID As LOCALE_VALUES

'Default property:
Public Property Get Convert(ByVal Value As Variant, ByVal ToType As VbVarType) As Variant
    If VariantChangeTypeEx(Convert, _
                           Value, _
                           LCID, _
                           VARIANT_ALPHABOOL _
                        Or VARIANT_LOCALBOOL, _
                           ToType) <> S_OK Then
        Err.Raise 5, TypeName(Me), "Conversion failed"
    End If
End Property

Private Sub Class_Initialize()
    LCID = LOCALE_INVARIANT
End Sub

The O.P. won't need that and could just rely on [tt]CLng()[/tt] or text coercion to [tt]Long[/tt] variables.

Then I'd probably use a class like:

ComboBuilder.cls
Code:
Option Explicit

Private VConvert As VConvert
Private List As Collection

Public Sub AddItem(ByVal Value As String)
    'Value: String of the form "xxx(dot-grouped-long-number)xxx"
    '       i.e. a Long value that may have period as a "digit
    '       group separator char" i.e. the German convention.
    Dim PosStart As Long
    Dim PosEnd As Long
    Dim OrderBy As Variant 'String, then Long.
    Dim I As Long

    If List Is Nothing Then Set List = New Collection

    'This code assumes valid input:
    PosStart = InStr(Value, "(")
    PosEnd = InStr(PosStart, Value, ")")
    OrderBy = Mid$(Value, PosStart + 1, PosEnd - PosStart - 1)
    OrderBy = VConvert.Convert(OrderBy, vbLong)

    'Fancy searching isn't warranted, since a ComboBox with a huge
    'number of items is beyond absurd.
    With List
        For I = 1 To .Count
            If .Item(I)(1) > OrderBy Then Exit For
        Next
        If I <= .Count Then
            .Add Array(Value, CLng(OrderBy)), , I
        Else
            .Add Array(Value, CLng(OrderBy))
        End If
    End With
End Sub

Public Sub Populate(ByVal Combo As ComboBox)
    Dim Item As Variant

    For Each Item In List
        Combo.AddItem Item(0)
    Next
    Set List = Nothing 'Clean out List for possible reuse.
End Sub

Private Sub Class_Initialize()
    Set VConvert = New VConvert
    VConvert.LCID = LOCALE_GERMANY
End Sub

Then the Form code becomes pretty simple:

Form1.frm
Code:
Option Explicit

Private Sub Form_Load()
    Dim F As Integer
    Dim Text As String
    Dim Parts() As String
    
    With New ComboBuilder
        F = FreeFile(0)
        Open "some.txt" For Input As #F
        Do Until EOF(F)
            Line Input #F, Text
            Parts = Split(Text, "|") 'Pipe-delimited fields.
            .AddItem Parts(1)        'Use 2nd field.
        Loop
        Close #F
        .Populate Combo1
    End With
End Sub

For input I'm using pipe-delimited text:

some.txt
Code:
A|0100-(26.867)-AAA
B|0101-(6.155)-BBB
C|0102-(40)-CCC
D|0103-(5.048)-DDD
E|0143-(12.949)-AAA
F|0146-(9.677)-DDD
G|0149-(12.039)-FFF

Seems to work just fine and even with 200 items I don't see any performance issues to worry about. If I had over 1000 items to put into the ComboBox I'd probably use a binary search to locate insertion points though. That should still be far faster than sorting an array. But how users are suppose to pick values in a 1000 item ComboBox escapes me!
 
>That isn't "casting" at all but instead coercion which involves conversion, a very different thing entirely.

Depends when and where you learned the terms, frankly. Casting in K&R 2 (from which I learned the term) explicitly involves type conversion.
 
What he has there doesn't involve casting at all, any more than it would in C. VB doesn't even have syntax for casting, as in C for example. Whether a requested cast also does a conversion varies with the types involved.

What we have here is coercion, which always involves conversion. It is most certainly not casting in any sense of the term in any common compiled language.
 
Casting in K&R C always involved type conversion. And that coercion and casting were pretty much the same thing

K&R2 said:
... explicitly coerce the pointer into the desired type with a cast

K&R2 said:
A unary expression preceded by the parenthesized name of a type causes conversion of the
value of the expression to the named type. This construction is called a cast.

30 odd years ago or so, the terms casting, coercion and conversion were pretty much synonymous in C. At least they were in my university.
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top