PDA

View Full Version : [SOLVED:] Problem With UK Postcode Format Check



kibl1
08-12-2018, 04:56 PM
So I understand there are probably far better solutions to this but I am attempting to teach myself VBA from scratch with no prior programming experience so am trying to find my own solutions to problems until I get stuck e.g. now.

I am trying to get a textbox on a userform to check if a postcode is in the correct format for a UK postcode. If it is then no action is needed. If it is correct but missing the space then a space should be added, and if it is wrong completely then a message box should prompt the user to check it.

The following are the rules for a UK postcode.

FORMAT ---------EXAMPLE
AN NAA---------- M1 1AA
ANN NAA--------- M60 1NW
AAN NAA ---------CR2 6XH
AANN NAA-------- DN55 1PT
ANA NAA ----------W1A 1HQ
AANA NAA ---------EC1A 1BB


-The letters Q, V and X are not used in the first position
-The letters I,J and Z are not used in the second position.
-The only letters to appear in the third position are A, B, C, D, E, F, G, H, J, K, S, T, U and W.
- The second half of the postcode is always consistent numeric, alpha, alpha format and the letters C, I, K, M, O and V are never used.
Postcodes should always be in BLOCK CAPITALS as the last line of an address. Do not underline the postcode or use any punctuation. Leave a clear space of one character between the two parts of the postcode and do not join the characters in any way.

The code I have used so far is below and has several problems.
1) I have no idea if the ? character will work or not.
2) I have another Sub_Change Event which is just 1 line ensuring all text is uppercase.
3) I just get an error when opening the userform "Compile Error: Procedure declaration does not match description of event or procedure having the same name". - I have no idea what this means.
4) Probably several other issues but I have not been able to test it so far since I just get the error.

I have tried various things, making this part of the change event mentioned above, making this a 'Lost Focus' event, altering the wording of various parts of the code etc. But, as I am not sure what the error is referring to I don't really know where to start in terms of trying to fix it. Anyway, here is what I have.





Private Sub TextBox8_Exit()

If TextBox8.Text = Len(0) Then Exit Sub

End If

Dim PC As String

PC = Trim(TextBox8.Text)

'Case 1 Correct AN NAA M1 1AA
If PC Like "[A-PR-U-WY-Z]#Chr(32)#[A-BD-H,J,L,N,P-UW-Z][A-BD-H,J,L,N,P-UW-Z]" Then

Exit Sub

'Case 2 Correct ANN NAA M60 1NW
ElseIf PC Like "[A-PR-U-WY-Z]##Chr(32)#[A-BD-H,J,L,N,P-UW-Z][A-BD-H,J,L,N,P-UW-Z]" Then

Exit Sub

'Case 3 Correct AAN NAA CR2 6XH
ElseIf PC Like "[A-PR-U-WY-Z][A-HK-Y]#Chr(32)#[A-BD-H,J,L,N,P-UW-Z][A-BD-H,J,L,N,P-UW-Z]" Then

Exit Sub

'Case 4 Correct AANN NAA DN55 1PT
ElseIf PC Like "[A-PR-U-WY-Z][A-HK-Y]##Chr(32)#[A-BD-H,J,L,N,P-UW-Z][A-BD-H,J,L,N,P-UW-Z]" Then

Exit Sub

'Case 5 Correct ANA NAA W1A 1HQ
ElseIf PC Like "[A-PR-U-WY-Z]#[A-HJ,K,S-U,W]Chr(32)#[A-BD-H,J,L,N,P-UW-Z][A-BD-H,J,L,N,P-UW-Z]" Then

Exit Sub

'Case 6 Correct AANA NAA EC1A 1BB
ElseIf PC Like "[A-PR-U-WY-Z][A-HK-Y]#[A-Z]Chr(32)#[A-BD-H,J,L,N,P-UW-Z][A-BD-H,J,L,N,P-UW-Z]" Then

Exit Sub



'Case 1 Incorrect AN NAA M1 1AA

ElseIf PC Like "[A-PR-U-WY-Z]##[A-BD-H,J,L,N,P-UW-Z][A-BD-H,J,L,N,P-UW-Z]" Then

TextBox8.Text = Format(PC, "??" & " " & "???")


'Case 2 Incorrect ANN NAA M60 1NW
ElseIf PC Like "[A-PR-U-WY-Z]###[A-BD-H,J,L,N,P-UW-Z][A-BD-H,J,L,N,P-UW-Z]" Then

TextBox8.Text = Format(PC, "???" & " " & "???")


'Case 3 Incorrect AAN NAA CR2 6XH
ElseIf PC Like "[A-PR-U-WY-Z][A-HK-Y]##[A-BD-H,J,L,N,P-UW-Z][A-BD-H,J,L,N,P-UW-Z]" Then

TextBox8.Text = Format(PC, "???" & " " & "???")


'Case 4 Incorrect AANN NAA DN55 1PT
ElseIf PC Like "[A-PR-U-WY-Z][A-HK-Y]###[A-BD-H,J,L,N,P-UW-Z][A-BD-H,J,L,N,P-UW-Z]" Then

TextBox8.Text = Format(PC, "????" & " " & "???")


'Case 5 Incorrect ANA NAA W1A 1HQ
ElseIf PC Like "[A-PR-U-WY-Z]#[A-HJ,K,S-U,W]#[A-BD-H,J,L,N,P-UW-Z][A-BD-H,J,L,N,P-UW-Z]" Then

TextBox8.Text = Format(PC.Text, "???" & " " & "???")


'Case 6 Incorrect AANA NAA EC1A 1BB
ElseIf PC Like "[A-PR-U-WY-Z][A-HK-Y]#[A-Z]#[A-BD-H,J,L,N,P-UW-Z][A-BD-H,J,L,N,P-UW-Z]" Then

TextBox8.Text = Format(PC.Text, "????" & " " & "???")

Else: MsgBox "Invalid format for UK Postcode entered." & vbCrLf & _
"Please check and try again.", vbOKOnly + vbExclamation, "Invalid Format!"

End If


End Sub

gmayor
08-12-2018, 10:41 PM
The compile error occurs because you have made up your own syntax. The textbox exit macro name is invalid. The 'Like' strings are also invalid. What you need is something like the following. I have not checked it exhaustively but it looks OK.



Private Sub TextBox8_Exit(ByVal Cancel As MSForms.ReturnBoolean)
Const strFirst As String = "A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,R,S,T,U,W,Y,Z"
Const strSecond As String = "A,B,C,D,E,F,G,H,K,L,M,N,O,P,Q,R,S,T,U,V,W,X,Y"
Const strThird As String = "A,B,C,D,E,F,G,H,J,K,S,T,U,W"
Const strLast As String = "A,B,D,E,F,G,H,J,L,N,P,Q,R,S,T,U,W,X,Y,Z"
Dim vChar As Variant
Dim iChar As Integer
Dim strPC As String
Dim bFound As Boolean


strPC = Trim(TextBox8.Text)
TextBox8.Text = Trim(UCase(strPC))

If Len(strPC) = 0 Then
TextBox8.BackColor = &H80000005
Exit Sub
End If

'Too few characters
If Len(strPC) > 0 And Len(strPC) < 6 Then
MsgBox "Post code is invalid - too few characters!"
TextBox8.SetFocus: TextBox8.BackColor = &HC993FF
Exit Sub
End If
'Too many characters
If Len(strPC) > 8 Then
MsgBox "Post code is invalid - too many characters!"
TextBox8.SetFocus: TextBox8.BackColor = &HC993FF
Exit Sub
End If

'Correct for no space in post code
If InStr(1, strPC, Chr(32)) = 0 Then
TextBox8.Text = UCase(Left(strPC, Len(strPC) - 3) & Chr(32) & Right(strPC, 3))
End If

'Check the strings according to their length
Select Case Len(TextBox8.Text)
Case 6
vChar = Split(strFirst, Chr(44))
bFound = False
For iChar = 0 To UBound(vChar)
If Left(TextBox8.Text, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
If Not bFound Then
MsgBox "PostCode first character is invalid"
Exit Sub
End If
bFound = False
If Not IsNumeric(Mid(TextBox8.Text, 2, 1)) Then
MsgBox "PostCode second character should be a number"
TextBox8.SetFocus: TextBox8.BackColor = &HC993FF
Exit Sub
End If
If Not IsNumeric(Mid(TextBox8.Text, 4, 1)) Then
MsgBox "PostCode fourth character should be a number"
Exit Sub
TextBox8.SetFocus: TextBox8.BackColor = &HC993FF
End If
bFound = False
vChar = Split(strLast, Chr(44))
For iChar = 0 To UBound(vChar)
If Mid(TextBox8.Text, 5, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
If Not bFound Then
MsgBox "PostCode penultimate character is invalid"
TextBox8.SetFocus: TextBox8.BackColor = &HC993FF
Exit Sub
End If
bFound = False
vChar = Split(strLast, Chr(44))
For iChar = 0 To UBound(vChar)
If Mid(TextBox8.Text, 6, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
If Not bFound Then
MsgBox "PostCode last character is invalid"
TextBox8.SetFocus: TextBox8.BackColor = &HC993FF
Exit Sub
End If

Case 7
vChar = Split(strFirst, Chr(44))
bFound = False
For iChar = 0 To UBound(vChar)
If Left(TextBox8.Text, 1) = vChar(iChar) Then
bFound = True
TextBox8.SetFocus: TextBox8.BackColor = &HC993FF
Exit For
End If
Next iChar
If Not bFound Then
MsgBox "PostCode first character is invalid"
TextBox8.SetFocus: TextBox8.BackColor = &HC993FF
Exit Sub
End If
bFound = False
If Not IsNumeric(Mid(TextBox8.Text, 2, 1)) Then
vChar = Split(strSecond, Chr(44))
For iChar = 0 To UBound(vChar)
If Mid(TextBox8.Text, 2, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
Else
bFound = True
End If
If Not bFound Then
MsgBox "PostCode second character is invalid"
Exit Sub
End If
bFound = False
If Not IsNumeric(Mid(TextBox8.Text, 3, 1)) Then
vChar = Split(strThird, Chr(44))
For iChar = 0 To UBound(vChar)
If Mid(TextBox8.Text, 3, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
Else
bFound = True
End If
If Not bFound Then
MsgBox "PostCode third character is invalid"
Exit Sub
End If
If Not IsNumeric(Mid(TextBox8.Text, 5, 1)) Then
MsgBox "PostCode fourth character should be a number"
TextBox8.SetFocus: TextBox8.BackColor = &HC993FF
Exit Sub
End If
bFound = False
vChar = Split(strLast, Chr(44))
For iChar = 0 To UBound(vChar)
If Mid(TextBox8.Text, 6, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
If Not bFound Then
MsgBox "PostCode penultimate character is invalid"
TextBox8.SetFocus: TextBox8.BackColor = &HC993FF
Exit Sub
End If
bFound = False
vChar = Split(strLast, Chr(44))
For iChar = 0 To UBound(vChar)
If Mid(TextBox8.Text, 7, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
If Not bFound Then
MsgBox "PostCode last character is invalid"
TextBox8.SetFocus: TextBox8.BackColor = &HC993FF
Exit Sub
End If

Case 8
vChar = Split(strFirst, Chr(44))
bFound = False
For iChar = 0 To UBound(vChar)
If Left(TextBox8.Text, 1) = vChar(iChar) Then
bFound = True
TextBox8.SetFocus: TextBox8.BackColor = &HC993FF
Exit For
End If
Next iChar
If Not bFound Then
MsgBox "PostCode first character is invalid"
TextBox8.SetFocus: TextBox8.BackColor = &HC993FF
Exit Sub
End If
bFound = False
vChar = Split(strSecond, Chr(44))
For iChar = 0 To UBound(vChar)
If Mid(TextBox8.Text, 2, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
If Not bFound Then
MsgBox "PostCode second character is invalid"
Exit Sub
End If

If Not IsNumeric(Mid(TextBox8.Text, 3, 1)) Then
MsgBox "PostCode third character should be a number"
TextBox8.SetFocus: TextBox8.BackColor = &HC993FF
Exit Sub
End If

bFound = False

If Not IsNumeric(Mid(TextBox8.Text, 4, 1)) Then
vChar = Split(strThird, Chr(44))
For iChar = 0 To UBound(vChar)
If Mid(TextBox8.Text, 4, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
Else
bFound = True
End If
If Not bFound Then
MsgBox "PostCode fourth character is invalid"
Exit Sub
End If
If Not IsNumeric(Mid(TextBox8.Text, 6, 1)) Then
MsgBox "PostCode sixth character should be a number"
TextBox8.SetFocus: TextBox8.BackColor = &HC993FF
Exit Sub
End If
bFound = False
vChar = Split(strLast, Chr(44))
For iChar = 0 To UBound(vChar)
If Mid(TextBox8.Text, 7, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
If Not bFound Then
MsgBox "PostCode penultimate character is invalid"
TextBox8.SetFocus: TextBox8.BackColor = &HC993FF
Exit Sub
End If
bFound = False
vChar = Split(strLast, Chr(44))
For iChar = 0 To UBound(vChar)
If Mid(TextBox8.Text, 8, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
If Not bFound Then
MsgBox "PostCode last character is invalid"
TextBox8.SetFocus: TextBox8.BackColor = &HC993FF
Exit Sub
End If
End Select
TextBox8.BackColor = &HC0F799
End Sub

gmayor
08-13-2018, 02:43 AM
The following is a more flexible versions of the code:

Option Explicit

Private Type Settings
Code As String
Color As String
Msg As String
Valid As Boolean
End Type

Private Sub TextBox8_Exit(ByVal Cancel As MSForms.ReturnBoolean)
With ValidatePostCode(TextBox8.Text)
TextBox8.Text = .Code
If .Valid = False Then
MsgBox .Msg
TextBox8.SetFocus
End If
TextBox8.BackColor = .Color
End With
lbl_Exit:
Exit Sub
End Sub

Private Function ValidatePostCode(strPostCode As String) As Settings
Const strFirst As String = "A,B,C,D,E,F,G,H,I,J,K,L,M,N,O,P,R,S,T,U,W,Y,Z"
Const strSecond As String = "A,B,C,D,E,F,G,H,K,L,M,N,O,P,Q,R,S,T,U,V,W,X,Y"
Const strThird As String = "A,B,C,D,E,F,G,H,J,K,S,T,U,W"
Const strLast As String = "A,B,D,E,F,G,H,J,L,N,P,Q,R,S,T,U,W,X,Y,Z"

Dim oSets As Settings
Dim vChar As Variant
Dim iChar As Integer
Dim strPC As String
Dim bFound As Boolean

'Empty string
If Len(strPostCode) = 0 Then
oSets.Color = &H80000005
oSets.Valid = True
GoTo lbl_Exit
End If

'Remove spaces from post code
strPostCode = Replace(strPostCode, Chr(32), "")

strPC = UCase(strPostCode)

'Too few characters
If Len(strPC) > 0 And Len(strPC) < 6 Then
oSets.Msg = "Post code is invalid - too few characters!"
GoTo lbl_Invalid
End If

'Too many characters
If Len(strPC) > 8 Then
oSets.Msg = "Post code is invalid - too many characters!"
GoTo lbl_Invalid
End If

strPC = UCase(Left(strPC, Len(strPC) - 3) & Chr(32) & Right(strPC, 3))


'Check the strings according to their length
Select Case Len(strPC)
Case 6
'Char1
vChar = Split(strFirst, Chr(44))
bFound = False
For iChar = 0 To UBound(vChar)
If Left(strPC, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
If Not bFound Then
oSets.Msg = "PostCode first character is invalid"
GoTo lbl_Invalid
End If

'Char2
bFound = False
If Not IsNumeric(Mid(strPC, 2, 1)) Then
oSets.Msg = "PostCode second character should be a number"
GoTo lbl_Invalid
End If

'Char3 is a space
'Char4
If Not IsNumeric(Mid(strPC, 4, 1)) Then
oSets.Msg = "PostCode fourth character should be a number"
GoTo lbl_Invalid
End If

'Char5
bFound = False
vChar = Split(strLast, Chr(44))
For iChar = 0 To UBound(vChar)
If Mid(strPC, 5, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
If Not bFound Then
oSets.Msg = "PostCode penultimate character is invalid"
GoTo lbl_Invalid
End If

'Char6
bFound = False
vChar = Split(strLast, Chr(44))
For iChar = 0 To UBound(vChar)
If Mid(strPC, 6, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar

If Not bFound Then
oSets.Msg = "PostCode last character is invalid"
GoTo lbl_Invalid
End If

Case 7
'Char1
vChar = Split(strFirst, Chr(44))
bFound = False
For iChar = 0 To UBound(vChar)
If Left(strPC, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
If Not bFound Then
oSets.Msg = "PostCode first character is invalid"
GoTo lbl_Invalid
End If

'Char2
bFound = False
If Not IsNumeric(Mid(strPC, 2, 1)) Then
vChar = Split(strSecond, Chr(44))
For iChar = 0 To UBound(vChar)
If Mid(strPC, 2, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
Else
bFound = True
End If
If Not bFound Then
oSets.Msg = "PostCode second character is invalid"
GoTo lbl_Invalid
End If

'Char3
bFound = False
If Not IsNumeric(Mid(strPC, 3, 1)) Then
vChar = Split(strThird, Chr(44))
For iChar = 0 To UBound(vChar)
If Mid(strPC, 3, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
Else
bFound = True
End If
If Not bFound Then
oSets.Msg = "PostCode third character is invalid"
GoTo lbl_Invalid
End If

'Char4 is a space
'Char5
If Not IsNumeric(Mid(strPC, 5, 1)) Then
oSets.Msg = "PostCode fourth character should be a number"
GoTo lbl_Invalid
End If

'Char6
bFound = False
vChar = Split(strLast, Chr(44))
For iChar = 0 To UBound(vChar)
If Mid(strPC, 6, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
If Not bFound Then
oSets.Msg = "PostCode penultimate character is invalid"
GoTo lbl_Invalid
End If

'Char7
bFound = False
vChar = Split(strLast, Chr(44))
For iChar = 0 To UBound(vChar)
If Mid(strPC, 7, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
If Not bFound Then
oSets.Msg = "PostCode last character is invalid"
GoTo lbl_Invalid
End If

Case 8
'Char1
vChar = Split(strFirst, Chr(44))
bFound = False
For iChar = 0 To UBound(vChar)
If Left(strPC, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar

If Not bFound Then
oSets.Msg = "PostCode first character is invalid"
GoTo lbl_Invalid
End If

'Char2
bFound = False
vChar = Split(strSecond, Chr(44))
For iChar = 0 To UBound(vChar)
If Mid(strPC, 2, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar

If Not bFound Then
oSets.Msg = "PostCode second character is invalid"
GoTo lbl_Invalid
End If

'Char3
If Not IsNumeric(Mid(strPC, 3, 1)) Then
oSets.Msg = "PostCode third character should be a number"
GoTo lbl_Invalid
End If

bFound = False

'Char4
If Not IsNumeric(Mid(strPC, 4, 1)) Then
vChar = Split(strThird, Chr(44))
For iChar = 0 To UBound(vChar)
If Mid(strPC, 4, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
Else
bFound = True
End If
If Not bFound Then
oSets.Msg = "PostCode fourth character is invalid"
GoTo lbl_Invalid
End If

'Char5 is a space
'Char6
If Not IsNumeric(Mid(strPC, 6, 1)) Then
oSets.Msg = "PostCode sixth character should be a number"
GoTo lbl_Invalid
End If

'Char7
bFound = False
vChar = Split(strLast, Chr(44))
For iChar = 0 To UBound(vChar)
If Mid(strPC, 7, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
If Not bFound Then
oSets.Msg = "PostCode penultimate character is invalid"
GoTo lbl_Invalid
End If

'Char8
bFound = False
vChar = Split(strLast, Chr(44))
For iChar = 0 To UBound(vChar)
If Mid(strPC, 8, 1) = vChar(iChar) Then
bFound = True
Exit For
End If
Next iChar
If Not bFound Then
oSets.Msg = "PostCode last character is invalid"
GoTo lbl_Invalid
End If
End Select
With oSets
.Code = strPC
.Color = &HC0F799
.Valid = True
.Msg = ""
End With
lbl_Exit:
ValidatePostCode = oSets
Exit Function
lbl_Invalid:
With oSets
.Code = strPC
.Valid = False
.Color = &HC993FF
End With
GoTo lbl_Exit
End Function

Paul_Hossler
08-13-2018, 10:25 AM
Not as fancy, and only returns True or False for Valid

I decided to 'help' the inputter by trimming and making it UC in the function, and ignoring too many spaces

The sub drv I used to test combinations





Option Explicit
Sub drv()

'valid
MsgBox ValidPostCode("m1 1aa")
MsgBox ValidPostCode("m60 1nw")
MsgBox ValidPostCode("CR2 6XH")
MsgBox ValidPostCode("dn55 1pt")
MsgBox ValidPostCode("W1A 1HQ")
MsgBox ValidPostCode("EC1A 1BB")
MsgBox ValidPostCode("m1 1aa") ' too many spaces


'not valid
MsgBox ValidPostCode("91 1aa") ' starts with number
MsgBox ValidPostCode("m11aa") ' no space
MsgBox ValidPostCode("m60") ' too short
MsgBox ValidPostCode("QR2 6XH") ' Q in first
MsgBox ValidPostCode("dn55 Cpt") ' C in first of second part
MsgBox ValidPostCode("WZA 1HQ")
MsgBox ValidPostCode("EZ1A 1BB")
MsgBox ValidPostCode("EC1A 1BBABC")
End Sub

Function ValidPostCode(PC As String) As Boolean

Dim s As String
Dim v As Variant

ValidPostCode = False
s = UCase(Trim(PC))

'too short
If Len(PC) < 6 Then Exit Function

Do While InStr(s, " ") > 0
s = Replace(s, " ", " ")
Loop

'split at space
v = Split(s, " ")

'no space
If LBound(v) <> 0 And UBound(v) <> 1 Then Exit Function

'quick check -- first has to start with A-Z, second must be NAA
If Not v(0) Like "[A-Z]*" Then Exit Function
If Not v(1) Like "[0-9][A-Z][A-Z]" Then Exit Function

Select Case Len(v(0))

Case 2
'2 - AN NAA---------- M1 1AA
'The letters Q, V and X are not used in the first position
If Not v(0) Like "[!QVX][0-9]" Then Exit Function

Case 3
'3 - ANN NAA--------- M60 1NW
'3 - AAN NAA ---------CR2 6XH
'3 - ANA NAA ----------W1A 1HQ
'The letters I,J and Z are not used in the second position.
'The only letters to appear in the third position are A, B, C, D, E, F, G, H, J, K, S, T, U and W.
If Not v(0) Like "[!QVX][0-9][0-9]" And _
Not v(0) Like "[!QVX][!IJZ][0-9]" And _
Not v(0) Like "[!QVX][0-9][ABCDEFGHJKSTUW]" Then Exit Function

Case 4
'4 - AANN NAA-------- DN55 1PT
'4 - AANA NAA ---------EC1A 1BB
If Not v(0) Like "[!QVX][!IJZ][0-9][0-9]" And _
Not v(0) Like "[!QVX][!IJZ][0-9][A-Z]" Then Exit Function ' ??? Fourth char ???

Case Else
Exit Function
End Select

'The second half of the postcode is always consistent numeric, alpha, alpha
' format and the letters C, I, K, M, O and V are never used.
Select Case Len(v(1))
Case 3
'The letters I,J and Z are not used in the second piece
If Not v(1) Like "[0-9][!CIKMOV][!CIKMOV]" Then Exit Function
Case Else
Exit Function
End Select

ValidPostCode = True


End Function

gmayor
08-13-2018, 09:18 PM
Paul
UK postcodes should be in upper case, so assuming the rest of your logic is correct you should change


's = UCase(Trim(PC))to
s = PC

It would be easy enough to block lowercase letters in the text box e.g.


Private Sub TextBox8_KeyPress(ByVal KeyAscii As MSForms.ReturnInteger)
Dim bTest As Boolean
bTest = IsAllowed(CStr(KeyAscii))
If bTest = False Then
Beep
KeyAscii = 0
End If
lbl_Exit:
Exit Sub
End Sub

Private Function IsAllowed(ByVal i As String) As Boolean
Select Case Val(i)
Case 48 To 57
IsAllowed = True
Case 65 To 90
IsAllowed = True
Case 32
IsAllowed = True
Case Else
IsAllowed = False
End Select
lbl_Exit:
Exit Function
End Function
or to convert to upper case automatically e.g.


Private Sub TextBox8_KeyPress(ByVal KeyAscii As MSForms.ReturnInteger)
Dim bTest As Boolean
bTest = IsAllowed(CStr(KeyAscii))
If bTest = False Then
If KeyAscii >= 97 And KeyAscii <= 122 Then
KeyAscii = KeyAscii - 32
Else
Beep
KeyAscii = 0
End If
End If
lbl_Exit:
Exit Sub
End Sub

Paul_Hossler
08-14-2018, 05:24 AM
Graham -- all true

Depends on how fancy/error proofing you wanted to add

You could also allow only a single space to be added between the pieces as well as only in allowed positions




Since the OP took a 'KISS' approach to notify the user ...




Else: MsgBox "Invalid format for UK Postcode entered." & vbCrLf & _
"Please check and try again.", vbOKOnly + vbExclamation, "Invalid Format!"




… I kept it that way and if the PC is valid, I left the final formatting/use to the OP (UCase, Trim, etc.)

kibl1
08-18-2018, 06:23 PM
Thanks very much. Feel like this is way over my head but seems to work perfectly so it has been implemented now. :yes