User Tools

Site Tools


vba:functions:trims

This is an old revision of the document!


[VBA] trims()

trims() ist eine Trim-Funktion für Strings. Im Gegensatz zu trim() entfernt trims() auch NewLines und Tabulatoren

Definition

Public Function trims( _
        ByVal iString As String, _
        Optional ByVal iDirection As trDirection = trBoth _
) As String

Beispiele

Für die Ausgabe der Resultate verwendete ich die Funktion [VBA] print_r()
'Ein normaler VBA.trim() entfernt nur Leerzeichen
print_r trim("  Der Hund " & vbtab & vbcrlf & "   ")
<String> 'Der Hund \t\r\n'
 
'tims() entfernt elle White-Space Characters. New Line, Form Feeds, Tabluatoren, Leerzeichen etc
print_r trims("  Der Hund " & vbtab & vbcrlf & "   ")
<String> 'Der Hund'
 
'Oder nur links trimmen
print_r trims("  Der Hund " & vbtab & vbcrlf & "   ", trLeft)
<String> 'Der Hund \t\r\n   '
 
'und nur rechts
print_r trims("  Der Hund " & vbtab & vbcrlf & "   ", trRight)
<String> '  Der Hund'

Code

udf_trims.bas
Attribute VB_Name = "udf_trims"
'-------------------------------------------------------------------------------
'File         : udf_trims.bas
'               Copyright mpl by ERB software
'               All rights reserved
'               http://wiki.yaslaw.info/dokuwiki/doku.php/vba/
'Environment  : VBA 2007 +
'Version      : 1.0.0
'Name         : trims
'Author       : Stefan Erb (ERS)
'History      : 22.07.2014 - ERS - Creation
'-------------------------------------------------------------------------------
Option Explicit
 
' Entfernt alle Spaces vor und nach dem Text mittels RegExp.
' Das s am Ende des Namens steht dann auch für \s. ALso alle Spaces
' Die RegExp werden während ded ganzen Session gehalten um. Das beschleunigt die Funktion beim EInsatz in SQL
 
Public Enum trDirection
    trBoth = 0    'TRIM()
    trLeft = 1      'LTRIM()
    trRight = 2    'RTRIM()
End Enum
 
Private Const C_PATTERN = "^\s*([\S\s]*\b)\s*$"
Private Const C_L_PATTERN = "^\s*([\S\s]*)$"
Private Const C_R_PATTERN = "^([\S\s]*\b)\s*$"
 
'Cache der RegExp
Private rxTrim(2) As Object
 
'/**
' * trim \s:    Entfernt im Gegensatz zu trim() auch Zeilenumbrüche, Tabulatoren etc. Alles was regexp \s ist
' *
' *     string = trims(string [,direction][,clearCache])
' *
' * @param  String
' * @param  trDirection     Angabe, auf welcher Seite getrimmt werden soll
' * @param  Boolean         Leehrt den Cache. Wird nur während der entwicklung gebraucht
' * @return String
' */
Public Function trims(ByVal iString As String, Optional ByVal iDirection As trDirection = trBoth, Optional ByVal iReset As Boolean = False) As String
    If rxTrim(iDirection) Is Nothing Or iReset Then
        Set rxTrim(iDirection) = CreateObject("VBScript.RegExp")
        rxTrim(iDirection).pattern = Choose(iDirection + 1, C_PATTERN, C_L_PATTERN, C_R_PATTERN)
    End If
    trims = rxTrim(iDirection).Replace(iString, "$1")
End Function
vba/functions/trims.1408954727.txt.gz · Last modified: 25.08.2014 10:18:47 by yaslaw