Выписать число «5» как «Пять» в VB Script? - PullRequest
3 голосов
/ 16 марта 2012

возможно ли выписать целое число, которое я получаю с буквами в классическом asp?

, например, если мой результат равен 5, я хочу вывести "Five"

или, если это двадцать, мне нужно, чтобы оно показывало "Twenty"

результаты могли быть бесконечными, поэтому написание массива для целей поиска не сработало бы.

есть ли обходной путь дляэто?

Ответы [ 2 ]

5 голосов
/ 16 марта 2012

Я украл это из статьи MS KB много лун назад, она вроде как делает свое дело, может использовать несколько настроек в своей грамматике.

response.Write ConvertCurrencyToEnglish("213123")


Function ConvertCurrencyToEnglish (ByVal MyNumber)
   Dim Temp
   Dim Dollars, Cents
   Dim DecimalPlace, Count

   ReDim Place(9)

   Place(2) = " Thousand "
   Place(3) = " Million "
   Place(4) = " Billion "
   Place(5) = " Trillion "

   'Convert MyNumber to a string, trimming extra spaces.
   MyNumber = Trim(CStr(MyNumber))

   'Find decimal place.
   DecimalPlace = InStr(MyNumber, ".")

   'If we find decimal place...
   If DecimalPlace > 0 Then
      'Convert cents
      Temp = Left(Mid(MyNumber, DecimalPlace + 1) & "00", 2)
      Cents = ConvertTens(Temp)
      'Strip off cents from remainder to convert.
      MyNumber = Trim(Left(MyNumber, DecimalPlace - 1))
   End If

   Count = 1

   Do While MyNumber <> ""
      'Convert last 3 digits of MyNumber to English dollars.
      Temp = ConvertHundreds(Right(MyNumber, 3))
      If Temp <> "" Then Dollars = Temp & Place(Count) & Dollars
      If Len(MyNumber) > 3 Then
         'Remove last 3 converted digits from MyNumber.
         MyNumber = Left(MyNumber, Len(MyNumber) - 3)
      Else
         MyNumber = ""
      End If
      Count = Count + 1
   Loop

   'Clean up dollars.
   Select Case Dollars
      Case ""
         Dollars = "No Dollars"
      Case "One"
         Dollars = "One Dollar"
      Case Else
         Dollars = Dollars & " Dollars"
   End Select

   'Clean up cents.
   Select Case Cents
      Case ""
         Cents = " And No Cents"
      Case "One"
         Cents = " And One Cent"
      Case Else
         Cents = " And " & Cents & " Cents"
   End Select

   'ConvertCurrencyToEnglish = Dollars & Cents
   ConvertCurrencyToEnglish = Dollars & Cents
End Function

Private Function ConvertHundreds (ByVal MyNumber)
   Dim Result

   'Exit if there is nothing to convert.
   If CInt(MyNumber) = 0 Then Exit Function

   'Append leading zeros to number.
   MyNumber = Right("000" & MyNumber, 3)

   'Do we have a hundreds place digit to convert?
   If Left(MyNumber, 1) <> "0" Then
      Result = ConvertDigit(Left(MyNumber, 1)) & " Hundred "
   End If

   'Do we have a tens place digit to convert?
   If Mid(MyNumber, 2, 1) <> "0" Then
      Result = Result & ConvertTens(Mid(MyNumber, 2))
   Else
      'If not, then convert the ones place digit.
      Result = Result & ConvertDigit(Mid(MyNumber, 3))
   End If

   ConvertHundreds = Trim(Result)
End Function

Private Function ConvertTens (ByVal MyTens)
   Dim Result

   'Is value between 10 and 19?
   If CInt(Left(MyTens, 1)) = 1 Then
      Select Case CInt(MyTens)
         Case 10: Result = "Ten"
         Case 11: Result = "Eleven"
         Case 12: Result = "Twelve"
         Case 13: Result = "Thirteen"
         Case 14: Result = "Fourteen"
         Case 15: Result = "Fifteen"
         Case 16: Result = "Sixteen"
         Case 17: Result = "Seventeen"
         Case 18: Result = "Eighteen"
         Case 19: Result = "Nineteen"
         Case Else
      End Select
   Else
      '... otherwise it's between 20 and 99.
      Select Case CInt(Left(MyTens, 1))
         Case 2: Result = "Twenty "
         Case 3: Result = "Thirty "
         Case 4: Result = "Forty "
         Case 5: Result = "Fifty "
         Case 6: Result = "Sixty "
         Case 7: Result = "Seventy "
         Case 8: Result = "Eighty "
         Case 9: Result = "Ninety "
         Case Else
      End Select
      'Convert ones place digit.
      Result = Result & ConvertDigit(Right(MyTens, 1))
   End If

   ConvertTens = Result
End Function

Private Function ConvertDigit (ByVal MyDigit)
   Select Case CInt(MyDigit)
      Case 1: ConvertDigit = "One"
      Case 2: ConvertDigit = "Two"
      Case 3: ConvertDigit = "Three"
      Case 4: ConvertDigit = "Four"
      Case 5: ConvertDigit = "Five"
      Case 6: ConvertDigit = "Six"
      Case 7: ConvertDigit = "Seven"
      Case 8: ConvertDigit = "Eight"
      Case 9: ConvertDigit = "Nine"
      Case Else: ConvertDigit = ""
   End Select
End Function
3 голосов
/ 16 марта 2012

Этот скрипт может быть сохранен в num2txt.vbs для тестирования:

Option Explicit

'-------------------------------------------------------------------------'
' Numbers to words -- proof of concept, nerfed to serve up to a trillion  '
'-------------------------------------------------------------------------'

Dim i, j, a, b, c, d, e, f, s

a = array( _
    "zero", _
    "one", _
    "two", _
    "three", _
    "four", _
    "five", _
    "six", _
    "seven", _
    "eight", _
    "nine", _
    "ten", _
    "eleven", _
    "twelve", _
    "thirteen", _
    "fourteen", _
    "fifteen", _
    "sixteen", _
    "seventeen", _
    "eighteen", _
    "nineteen" _
)

b = array( _
    "twenty", _
    "thirty", _
    "forty", _
    "fifty", _
    "sixty", _
    "seventy", _
    "eighty", _
    "ninety" _
)

c = array( _
    "hundred", _
    "thousand", _
    "million", _
    "billion", _
    "trillion" _
)

'-------------------------------------------------------------------------'
' Returns the text for numbers; this can definitely be optimised further  '
'-------------------------------------------------------------------------'
Function WhatAmI(i)
    Dim s

    If i >= 1000000000000 Then
        If Len(i) = 15 Then s = WhatAmI(Left(i, 3)) & " " & c(4)
        If Len(i) = 14 Then s = WhatAmI(Left(i, 2)) & " " & c(4)
        If Len(i) = 13 Then s = WhatAmI(Left(i, 1)) & " " & c(4)

        If Right(i, 12) <> "000000000000" Then
            d = Mid(Right(i, 12), 1, 1)
            e = Mid(Right(i, 12), 2, 1)
            f = Mid(Right(i, 12), 3, 1)

            If d <> 0 Then
                s = s & ", "
                s = s & WhatAmI(d & e & f) & " " & c(3)
            ElseIf e <> 0 Then
                s = s & " and " & WhatAmI(e & f)
            ElseIf f <> 0 Then
                s = s & " and " & WhatAmI(f)
            End If
        End If

        If Right(i, 9) <> "000000000" Then
            d = Mid(Right(i, 9), 1, 1)
            e = Mid(Right(i, 9), 2, 1)
            f = Mid(Right(i, 9), 3, 1)

            If d <> 0 Then
                s = s & ", "
                s = s & WhatAmI(d & e & f) & " " & c(2)
            ElseIf e <> 0 Then
                s = s & " and " & WhatAmI(e & f)
            ElseIf f <> 0 Then
                s = s & " and " & WhatAmI(f)
            End If
        End If

        If Right(i, 6) <> "000000" Then
            d = Mid(Right(i, 6), 1, 1)
            e = Mid(Right(i, 6), 2, 1)
            f = Mid(Right(i, 6), 3, 1)

            If d <> 0 Then
                s = s & ", "
                s = s & WhatAmI(d & e & f) & " " & c(1)
            ElseIf e <> 0 Then
                s = s & " and " & WhatAmI(e & f)
            ElseIf f <> 0 Then
                s = s & " and " & WhatAmI(f)
            End If
        End If

        If Right(i, 3) <> "000" Then
            d = Mid(Right(i, 3), 1, 1)
            e = Mid(Right(i, 3), 2, 1)
            f = Mid(Right(i, 3), 3, 1)

            If d <> 0 Then
                s = s & ", "
                s = s & WhatAmI(d & e & f)
            ElseIf e <> 0 Then
                s = s & " and " & WhatAmI(e & f)
            ElseIf f <> 0 Then
                s = s & " and " & WhatAmI(f)
            End If
        End If
    ElseIf i >= 1000000000 Then
        If Len(i) = 12 Then s = WhatAmI(Left(i, 3)) & " " & c(3)
        If Len(i) = 11 Then s = WhatAmI(Left(i, 2)) & " " & c(3)
        If Len(i) = 10 Then s = WhatAmI(Left(i, 1)) & " " & c(3)

        If Right(i, 9) <> "000000000" Then
            d = Mid(Right(i, 9), 1, 1)
            e = Mid(Right(i, 9), 2, 1)
            f = Mid(Right(i, 9), 3, 1)

            If d <> 0 Then
                s = s & ", "
                s = s & WhatAmI(d & e & f) & " " & c(2)
            ElseIf e <> 0 Then
                s = s & " and " & WhatAmI(e & f)
            ElseIf f <> 0 Then
                s = s & " and " & WhatAmI(f)
            End If
        End If

        If Right(i, 6) <> "000000" Then
            d = Mid(Right(i, 6), 1, 1)
            e = Mid(Right(i, 6), 2, 1)
            f = Mid(Right(i, 6), 3, 1)

            If d <> 0 Then
                s = s & ", "
                s = s & WhatAmI(d & e & f) & " " & c(1)
            ElseIf e <> 0 Then
                s = s & " and " & WhatAmI(e & f)
            ElseIf f <> 0 Then
                s = s & " and " & WhatAmI(f)
            End If
        End If

        If Right(i, 3) <> "000" Then
            d = Mid(Right(i, 3), 1, 1)
            e = Mid(Right(i, 3), 2, 1)
            f = Mid(Right(i, 3), 3, 1)

            If d <> 0 Then
                s = s & ", "
                s = s & WhatAmI(d & e & f)
            ElseIf e <> 0 Then
                s = s & " and " & WhatAmI(e & f)
            ElseIf f <> 0 Then
                s = s & " and " & WhatAmI(f)
            End If
        End If
    ElseIf i >= 1000000 Then
        If Len(i) = 9 Then s = WhatAmI(Left(i, 3)) & " " & c(2)
        If Len(i) = 8 Then s = WhatAmI(Left(i, 2)) & " " & c(2)
        If Len(i) = 7 Then s = WhatAmI(Left(i, 1)) & " " & c(2)

        If Right(i, 6) <> "000000" Then
            d = Mid(Right(i, 6), 1, 1)
            e = Mid(Right(i, 6), 2, 1)
            f = Mid(Right(i, 6), 3, 1)

            If d <> 0 Then
                s = s & ", "
                s = s & WhatAmI(d & e & f) & " " & c(1)
            ElseIf e <> 0 Then
                s = s & " and " & WhatAmI(e & f)
            ElseIf f <> 0 Then
                s = s & " and " & WhatAmI(f)
            End If
        End If

        If Right(i, 3) <> "000" Then
            d = Mid(Right(i, 3), 1, 1)
            e = Mid(Right(i, 3), 2, 1)
            f = Mid(Right(i, 3), 3, 1)

            If d <> 0 Then
                s = s & ", "
                s = s & WhatAmI(d & e & f)
            ElseIf e <> 0 Then
                s = s & " and " & WhatAmI(e & f)
            ElseIf f <> 0 Then
                s = s & " and " & WhatAmI(f)
            End If
        End If
    ElseIf i >= 1000 Then
        If Len(i) = 6 Then s = WhatAmI(Left(i, 3)) & " " & c(1)
        If Len(i) = 5 Then s = WhatAmI(Left(i, 2)) & " " & c(1)
        If Len(i) = 4 Then s = WhatAmI(Left(i, 1)) & " " & c(1)

        If Right(i, 3) <> "000" Then
            d = Mid(Right(i, 3), 1, 1)
            e = Mid(Right(i, 3), 2, 1)
            f = Mid(Right(i, 3), 3, 1)

            If d <> 0 Then
                s = s & ", "
                s = s & WhatAmI(d & e & f)
            ElseIf e <> 0 Then
                s = s & " and " & WhatAmI(e & f)
            ElseIf f <> 0 Then
                s = s & " and " & WhatAmI(f)
            End If
        End If
    ElseIf i >= 100 Then
        s = a(Left(i, 1)) & " " & c(0)
        If Right(i, 2) <> "00" Then s = s & " and " & WhatAmI(Right(i, 2))
    ElseIf i >= 90 Then
        s = b(7)
        If Right(i, 1) > 0 Then s = s & "-" & a(Right(i, 1))
    ElseIf i >= 80 Then
        s = b(6)
        If Right(i, 1) > 0 Then s = s & "-" & a(Right(i, 1))
    ElseIf i >= 70 Then
        s = b(5)
        If Right(i, 1) > 0 Then s = s & "-" & a(Right(i, 1))
    ElseIf i >= 60 Then
        s = b(4)
        If Right(i, 1) > 0 Then s = s & "-" & a(Right(i, 1))
    ElseIf i >= 50 Then
        s = b(3)
        If Right(i, 1) > 0 Then s = s & "-" & a(Right(i, 1))
    ElseIf i >= 40 Then
        s = b(2)
        If Right(i, 1) > 0 Then s = s & "-" & a(Right(i, 1))
    ElseIf i >= 30 Then
        s = b(1)
        If Right(i, 1) > 0 Then s = s & "-" & a(Right(i, 1))
    ElseIf (i >= 20) Then
        s = b(0)
        If Right(i, 1) > 0 Then s = s & "-" & a(Right(i, 1))
    ElseIf (i > 9) Then
        s = a(i)
    ElseIf (i >= 0 AND i <= 9) Then
        s = a(i)
    End If
    WhatAmI = s
End Function

'-------------------------------------------------------------------------'
' Ensure input is really numeric                                          '
'-------------------------------------------------------------------------'
Function is_numeric(s)
    Dim i, c

    is_numeric = True

    If IsNull(s) OR s = "" Then
        is_numeric = False
        Exit Function
    End If

    If s = "" Then
        is_numeric = False
        Exit Function
    End If

    For i = 1 To Len(s)
        c = Mid(s, i, 1)
            If Asc(c) < 48 OR Asc(c) > 57 Then
            is_numeric = False
            Exit For
        End If
    Next
End Function

i = InputBox("Enter the number you wish to convert:", "Numbers to Text")

If i <> "" Then i = Replace(i, ",", "") ' In case input was 1,100 or something '

If Len(i) > 15 Then
    MsgBox "Sorry, numbers larger than a trillion aren't supported", 0, "Fail"
End If

If NOT is_numeric(i) Then
    MsgBox "That is not a valid number... Integers only, please", 0, "Fail"
Else
    i = CDbl(i)

    MsgBox FormatNumber(i, 0) & " = " & WhatAmI(i), 0, "Converted"
End If


Пример выходных данных:

110,314 = one hundred and ten thousand, three hundred and fourteen

540,610,333 = five hundred and forty million, six hundred and ten thousand, three hundred and thirty-three
Добро пожаловать на сайт PullRequest, где вы можете задавать вопросы и получать ответы от других членов сообщества.
...