User Tools

Site Tools


vba:functions:increment

This is an old revision of the document!


[VBA] Increment/Decrement (i++ etc)

In vielen Sprachen kennt man PostIncrement und PreIncrement. Also i'' und ''i++''. Leider kennt VBA das nicht. Somit muss bei einer Manuellen Schleife dies immer von Hand mittels ''i = i+1'' durchgeführt werden.// \\ Mit den folgenden Funktionen kann man das umgehen. ==Version 1.0.0 - 25.11.2014== {{lib_increment.bas i ==== Ohne Incement-Funktion sieht meine Lösung so aus <code vb> Public Sub withoutPreIncrement() Dim i As Integer Dim arr() As Integer i = -1 Do While (i + 1) ^ 2 < 30 i = i + 1 ReDim Preserve arr(i) arr(i) = i ^ 2 Loop print_r arr End Sub </code> Mit inc() oder preInc() vereinfacht sich das ganze <code vb> Public Sub withPreIncrement() Dim i As Integer Dim arr() As Integer i = -1 Do While inc(i) ^ 2 < 30 ReDim Preserve arr(i) arr(i) = i ^ 2 Loop print_r arr End Sub </code> ==== PostIncrement i++ ==== Umsetzung ohne meine Funktion <code vb> Public Sub withoutPostIncrement() Dim i As Integer Dim arr() As Integer Do While (i) ^ 2 < 30 ReDim Preserve arr(i) arr(i) = i ^ 2 i = i + 1 Loop print_r arr End Sub </code> umsetzung mit postInc() oder inc(#,itPostIncrement) <code vb> Public Sub withPostIncrement() Dim i As Integer Dim arr() As Integer Do While i ^ 2 < 30 ReDim Preserve arr(i) 'Die Formel wird zuerst ausgeführt. Dann erst kommt der Teil vor dem = 'Darum ist postInc() vor dem = arr(postInc(i)) = i ^ 2 Loop print_r arr End Sub </code> ==== Resultat ==== Achja, alle Test haben natürlich dieselbe Ausgabe: <code><Integer()> ( [0] ⇒ <Integer> 0 [1] ⇒ <Integer> 1 [2] ⇒ <Integer> 4 [3] ⇒ <Integer> 9 [4] ⇒ <Integer> 16 [5] ⇒ <Integer> 25 )</code> ===== Code =====

lib_increment.bas
Attribute VB_Name = "lib_increment"
'-------------------------------------------------------------------------------
'File         : lib_increment.bas
'               Copyright mpl by ERB software
'               All rights reserved
'               http://wiki.yaslaw.info/dokuwiki/doku.php/vba/functions/increment
'Environment  : VBA 2007 +
'Version      : 1.1.0
'Name         : lib_increment
'Author       : Stefan Erb (ERS)
'History      : 25.11.2014 - ERS - Creation
'               11.01.2016 - ERS - inc() verkürzt
'-------------------------------------------------------------------------------
Option Explicit
 
Public Enum incType
    itPreIncrement = 0    '++1
    itPostIncrement = 1   'i++
    itPreDecrement = 2    '--i
    itPostDecrement = 3   'i--
End Enum
 
'/**
' * @param  Number
' * @param  incType     Type der Encrementation. Default ist i++
' * @retrun Number
'*/
Public Function inc(ByRef i As Variant, Optional ByVal iIncType As incType = itPreIncrement) As Variant
    Select Case iIncType
        Case itPreIncrement:    i = i + 1:  inc = i     '++i
        Case itPostIncrement:   inc = i:    i = i + 1   'i++
        Case itPreDecrement:    i = i - 1:  inc = i     '--i
        Case itPostDecrement:   inc = i:    i = i - 1   'i--
    End Select
End Function
 
'/**
' * PreIncrement    ++i
' * Zählt i eins hoch und gibt den Wert zurück
' * @param  Number
' * @retrun Number
'*/
Public Function preInc(ByRef i As Variant) As Variant:  preInc = inc(i, itPreIncrement):    End Function
 
'/**
' * PostIncrement   i++
' * Gibt den Wert zurück und zählt dann i eins hoch
' * @param  Number
' * @retrun Number
'*/
Public Function postInc(ByRef i As Variant) As Variant: postInc = inc(i, itPostIncrement):  End Function
 
'/**
' * PreDecrement    --i
' * Zählt i eins hoch und gibt den Wert zurück
' * @param  Number
' * @retrun Number
'*/
Public Function preDec(ByRef i As Variant) As Variant: preDec = inc(i, itPreDecrement):     End Function
 
'/**
' * PostDecrement   i--
' * Gibt den Wert zurück und zählt dann i eins hoch
' * @param  Number
' * @retrun Number
'*/
Public Function postDec(ByRef i As Variant) As Variant: postDec = inc(i, itPostDecrement):  End Function
 
vba/functions/increment.1430297716.txt.gz · Last modified: 29.04.2015 10:55:16 by yaslaw