Results 1 to 3 of 3

Thread: Excel VBA comma point thousand decimal separator number problem.

  1. #1
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,270
    Rep Power
    10

    Excel VBA comma point thousand decimal separator number problem.

    Excel VBA comma point thousand decimal separator number problem.


    Hi,
    This Tip is an answer and partial solution to my first Excel Forum Question a few years ago.
    https://www.mrexcel.com/forum/questi...l-problem.html
    I have been using it myself in the meantime for over a year and have found it very useful, so I thought I would share it for the benefit of others. Also, as I expect that it is not a very efficient code, I would welcome any comments or improved or more efficient versions if anyone has any.
    ( If anyone can give a better solution , then that would be very interesting. I am sure there must be a much better way. )
    ( No combination of internal settings has ever consistently solved this problem )

    I expect this solution only to be useful to people who like me are not doing particularly precise calculations but who are continually annoyed by Excel interchanging the comma , and point . as decimal and Thousand separators.
    In this and the next Post I explain in detail the solution with an extended code. In the over next post is a shortened simplified version )

    The problem Brief details
    As Simple Example: I want things like on the left hand column to become, or to be recognised , as that on the right hand column ( with the . as the decimal separator )
    What I Might Have What I want
    ”Before” ”After”
    001,456 1.456 ( This number is almost one and a half )
    1.00007 1.00007 ( This number is slightly more than one (It is approximately one) )
    123,456.2 123456.2 ( This number has a fractional part of 2/10 ( 0.2 ) )
    0023.345,0 23345 ( This number is 23 Thousand 3 Hundred and forty-five )
    -0023.345,0 -23345
    1.007 1.007
    1.3456 1.3456
    1,2345 1.2345
    01,0700000 1.07
    1.3456 1.3456
    1,2345 1.2345
    .2345 0.2345
    ,4567 0.4567
    -,340 -0.34
    00.04 0.04
    -0,56000000 -0.56
    -,56000001 -0.56000001
    Note: If you attempt to copy those numbers from the left hand column into a spreadsheet you may experience the sort of problems that I often experience: You may notice that many of the formats will change : (Adjusting various internal Excel settings will effect different numbers differently) . This is how those numbers come out when I paste into a spreadsheet. As you can see, some numbers on the left hand column are clearly not representing the numbers that I want
    MessedUpNumberFormatCommaPoint.jpg https://imgur.com/D1BSwAa
    MessedUpNumberFormatCommaPoint.JPG
    So I would apply my solution to those numbers before I pasted them in : They may appear then in different formats depending on Excel internal settings, but they are being held in the magnitude that I wish. (In my particular case my Excel spreadsheet is using the point . as decimal separator )


    More detail to problem
    The problem arises because I use both English and German Excel and also handle data, ( for example copied form Internet sources or different types of data files ) , that may come from, or be wanted to be outputted in, the conventions of either language. It has often proved to be a nightmare to keep track of whether a comma , or point . is being used or wanted finally as decimal and Thousand separators.
    So the end effect is that a number may be being recognised as a magnitude other than I want. As a simple example, say this number, 1.00 , is intended by me to represent the number One. It may arise that Excel will at some point choose to consider the . as a thousand separator and recognise the number as representing One Hundred.
    No combination of internal settings has ever consistently solved this problem

    The main issue that this solution attempt to address is that when a number is typed or pasted into a cell , then it will be taken as the number of the correct magnitude regardless of how it looks ( with some restrictions**) . Actually the point is that a “number” can be taken by or given to my solution so it is not really limited to what is typed into a cell. In fact I often use this solution in various parts of a code to consider a number at any point and check that it is being recognised as the correct magnitude number

    What the solution does ( What the code I present does ) ( or effect of )
    The final result is to have a number held in a variable of Double type which is a number of the correct magnitude I want, that is to say (regardless of how it may “look” in any situation, ( whether it has a comma or point or neither in it) ) , it is recognised by further coding as the number that I want. The initial requirement is that the number “looks” like a number with certain restrictions ** as explained in the next section

    ** This solution is limited:
    It does not work on scientific number format.
    It assumes that looking from the right of a number any first comma or point “seen” is the decimal separator.
    A Number such as 123,456 or 123.456 will be returned as whole part 123 and decimal fraction part of 456 ( If that is not required then the workaround is to ensure that the number should be given in this form 123,456.0 or 123.456,0 or 123.456,00000 etc. )

    This is how it works
    Summary

    A Number given is initially considered as a string. It is split into two parts, that before, and that after the last separator. The separator used is the first separator looking from the right.
    The before part is then treated as a whole number. As such it has exactly the same magnitude and meaning as it did in the original Number
    The part after is similarly treated as a number, but is then divided by some magnitude of 10 mathematically to give the magnitude as a decimal. This part then also represents the same magnitude that it did in the original Number.
    Example: A number of 10.45 is given or taken in As String
    ____”10.45” ‘ Taken/ held as string
    ___= ”10.45” ‘ Is String variable
    ___ =”10”
    ___ & “45” ‘ Considered as two string variables
    _ = 10 _+_ (45/100)
    _ = 10 _+_ .45 ‘ The two string variables are converted to the numbers they represent, and then added mathematically
    __ = 10.45

    This is what the solution does briefly
    A number is “taken in” / considered by us, As a String. It must “look” like a number and not be in scientific format.
    It is treated initially as a string.
    It does not matter if there are leading or trailing 0s , but they will not be returned
    It can be given in any recognised form, like: _ .23 _ -0,34 _ -00089 _ -.23000000 _ 002340 _ 123,456,5.9806 _ etc.. etc..
    This is how it works
    Full Description

    I am doing this with a Function code. Here is the Full version:
    Function CStrSepDbl : http://www.excelfox.com/forum/showth...0502#post10502
    https://pastebin.com/1kq6h9Bn

    I go on to explain that now in detail, so it is probably best to copy that to a code module and follow through it as you read the explanations.

    Pseudo Declaration Function signature line
    The first line of our Function code says a lot about what we are actually doing. This will be explained again later. But briefly for now: This is approximately our Signature line: It pseudo “Declares” what I am doing:
    Function CStrSepDbl(strNumber As String) As Double
    This is very similar to a simple variable declaration , Diming . So pseudo I have:
    _ Dim __ CStrSepDbl( _¬¬¬ ) ______ As Double
    or
    _ Dim VariableFunctionCStrSepDbl( _ ) As Double
    In fact VBA is holding the CStrSepDbl as just that: variable CStrSepDbl is a Double type variable, held in memory somewhere, god knows where, probably, I don’t know.
    The only difference is that in code lines like_..
    _Dim Retun As Double
    ___ Retun = CStrSepDbl()
    _.. what will usually happen in the last code line above is that the Function code will be carried out before that code line is completed. The completion of the code line then does pseudo
    Retun = current value held by the VBA variable CStrSepDbl
    If the Function code does not do anything to the VBA variable CStrSepDbl , then Retun will become 0. ( 0 is the default value for a non filled Double variable ).
    But we want the function to function such as to put the final number in the correct format into Retun, using a code line such as
    __ Retun = CStrSepDbl(HereTheStringNumber)
    The purposed of the Function code will be to arrange for that to happen….. somehow…… So we want it to function in such a way.

    2 things a lot of people probably know, but maybe did not realise
    The key to how to do this is probably in a couple of things that Factually are, but that I have never seen clearly documented or explained, .. that being ..
    _1: Once I have syntaxly correctly written a Function code (named in this case CStrSepDbl), then VBA recognises CStrSepDbl as a Function in any other code. Because of that we can do a code line of _...
    __ Retun = CStrSepDbl(HereTheStringNumberInAnyOfTheIndicatedFormats)
    _... in any code ( even in the function CStrSepDbl, in which case another copy of the code is made available to run. This is called recursion )
    In passing that code line, the Function code is completed before the code line is completed. In other words the main code in which the code line _ Retun = CStrSepDbl(HereTheStringNumberInAnyOfTheIndicatedFormats) _ is in will pause in the middle of this code line whilst the Function code Function CStrSepDbl is carried out.

    _2: However, importantly in addition, within the Function CStrSepDbl, the use of a code line like _..
    __ CStrSepDbl = 9.3
    _.. will result in assigning the value 9.3 into the VBA variable CStrSepDbl
    ( Such a code line will error in any other code ). This would have the effect that in completion of this Main code code line _...
    _ Retun = CStrSepDbl(HereTheStringNumberInAnyOfTheIndicatedFormats) ,
    _.... the value of 9.3 would be copied from the VBA variable CStrSepDbl into Retun. In other words Retun would become 9.3 at the completion of that main code code line.
    This is because, the pseudo code of that line, as mentioned is
    _ Retun = the VBA variable CStrSepDbl

    Function code strategy
    So the strategy is to write a code which “takes in” at the first ( signature ) line the string variable ( HereTheStringNumberInAnyOfTheIndicatedFormats ) and turns this into a number of the required magnitude, and then , for example , puts that in a variable, _ NumberInCorrectMagnitude _ , and then finally just before the End of the Function CStrSepDbl places this in the VBA variable CStrSepDbl . The latter can be done, for example , using within the function code and towards the End of the code such a code line
    _ CStrSepDbl = NumberInCorrectMagnitude


    So a walk through the code, Function CStrSepDbl

    In next Post:



    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA
    Last edited by DocAElstein; 06-10-2023 at 04:16 PM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  2. #2
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,270
    Rep Power
    10
    To recap from the last Post…

    This is how it works
    Full Description

    I am doing this with a Function code. Here is the Full version:
    Function CStrSepDbl : http://www.excelfox.com/forum/showth...0502#post10502
    https://pastebin.com/1kq6h9Bn

    I go on to explain that now in detail, so it is probably best to copy that to a code module and follow through it as you read the explanations.

    Pseudo Declaration Function signature line
    The first line of our Function code says a lot about what we are actually doing. This will be explained again later. But briefly for now: This is approximately our Signature line: It pseudo “Declares” what I am doing:
    Function CStrSepDbl(strNumber As String) As Double
    This is very similar to a simple variable declaration , Diming . So pseudo I have:
    _ Dim __ CStrSepDbl( _¬¬¬ ) ______ As Double
    or
    _ Dim VariableFunctionCStrSepDbl( _ ) As Double
    In fact VBA is holding the CStrSepDbl as just that: variable CStrSepDbl is a Double type variable, held in memory somewhere, god knows where, probably, I don’t know.
    The only difference is that in code lines like_..
    _Dim Retun As Double
    ___ Retun = CStrSepDbl()
    _.. what will usually happen in the last code line above is that the Function code will be carried out before that code line is completed. The completion of the code line then does pseudo
    Retun = current value held by the VBA variable CStrSepDbl
    If the Function code does not do anything to the VBA variable CStrSepDbl , then Retun will become 0. ( 0 is the default value for a non filled Double variable ).
    But we want the function to function such as to put the final number in the correct format into Retun, using a code line such as
    __ Retun = CStrSepDbl(HereTheStringNumber)
    The purposed of the Function code will be to arrange for that to happen….. somehow…… So we want it to function in such a way.

    2 things a lot of people probably know, but maybe did not realise
    The key to how to do this is probably in a couple of things that Factually are, but that I have never seen clearly documented or explained, .. that being ..
    _1: Once I have syntaxly correctly written a Function code (named in this case CStrSepDbl), then VBA recognises CStrSepDbl as a Function in any other code. Because of that we can do a code line of _...
    __ Retun = CStrSepDbl(HereTheStringNumberInAnyOfTheIndicatedFormats)
    _... in any code ( even in the function CStrSepDbl, in which case another copy of the code is made available to run. This is called recursion )
    In passing that code line, the Function code is completed before the code line is completed. In other words the main code in which the code line _ Retun = CStrSepDbl(HereTheStringNumberInAnyOfTheIndicatedFormats) _ is in will pause in the middle of this code line whilst the Function code Function CStrSepDbl is carried out.

    _2: However, importantly in addition, within the Function CStrSepDbl, the use of a code line like _..
    __ CStrSepDbl = 9.3
    _.. will result in assigning the value 9.3 into the VBA variable CStrSepDbl
    ( Such a code line will error in any other code ). This would have the effect that in completion of this Main code code line _...
    _ Retun = CStrSepDbl(HereTheStringNumberInAnyOfTheIndicatedFormats) ,
    _.... the value of 9.3 would be copied from the VBA variable CStrSepDbl into Retun. In other words Retun would become 9.3 at the completion of that main code code line.
    This is because, the pseudo code of that line, as mentioned is
    _ Retun = the VBA variable CStrSepDbl


    Function code strategy
    So the strategy is to write a code which “takes in” at the first ( signature ) line the string variable (HereTheStringNumberInAnyOfTheIndicatedFormats) and turns this into a number of the required magnitude, and then , for example , puts that in a variable, _ NumberInCorrectMagnitude _ , and then finally just before the End of the Function CStrSepDbl places this in the VBA variable CStrSepDbl . The latter can be done, for example , using within the function code and towards the End of the code such a code line
    _ CStrSepDbl = NumberInCorrectMagnitude





    So a walk through the code, Function CStrSepDbl


    20 30 ( **The first couple of lines are something that I added later just to make the function a bit more flexible to return a value if used without giving it any text. It is not particularly relevant to a real life requirement , and I do not include it in the shortened working code in the second ( next ) post )
    40 60 Possible adjustments to the left hand side
    The basic idea is to consider the string text in two parts. This would not work as intended if the number starts with just a comma , or point . _ So to overcome that problem a 0 is added If the first character is either a comma , or point .
    As leading 0s can be present then just adding a 0 in any case would have been another possibility but we also need to consider cases like -.38746 or -,32876 . This problem is overcome by If the first two cahracters are -, or .- Then
    Application.WorksheetFunction.Replace( InTheText , AtFirstCharacter , ForLengthOneChharacter , SubstituteIn”-0”
    70
    We choose arbitrarily the comma , as separating symbol ( “ , is “the separator” “ ) , so just in case we have a point as separator, a
    __Replace is made of ( InTheText , APoint , IsReplacedByAComma ,
    ___________________________LookingFromAndreturningFromFirstCharacter ,
    ________________________________LookingFromTheLeftForTheFirstOccuranceIsSufficientButReplacingAllHereSimplifiesTheCodeLater ,
    _________________________________________LookingForAnExcactMatch
    _ )
    ( VBA Replace Function: http://www.excelfox.com/forum/showth...0499#post10499 )
    It is sufficient to look for one occurrence, as that would catch and replace the situation when looking from the right a point . is used as the decimal separator, but later in the code any thousand separators will be removed and it simplifies the code to only look for commas at that point
    100 – 320 MAIN CODE ===
    90 A main check is done: If we have a presence of a comma then the MAIN CODE begins.
    ________ ( 320 – 340 Else a simple conversion of the original Text to a Double number is done towards the end of the code )
    120 The position of the decimal separator is determined as that for the last comma ,

    Determination of Whole part to left of separator:
    So the position of the first comma “seen Looking in the String from the right” was obtained, which allows a
    140 simple truncation of the Text to reveal the “whole Number” part, ( that to the left of the decimal separator )
    150 Any other separators (which will be any thousand separators) will be removed.
    Determination of fractional part to right of separator (170-210)
    180 The fractional string part is obtained.
    190-210 Logic for the fractional part determination as number
    _ Consider with an example, 1.00100
    The string fractional part, strFrction, is determined to be “00100”
    The character length of this string, LenstrFrction, is 5
    Conversion of strFrction to a Double number gives 100 which is placed in variable Frction
    If one inspect these Numbers , one can see that the required fraction of ( in this case 0.001 ) is obtained from a formula of the form
    100 / (10^5), or in general _ TheDoubleNumber / (10^CharacterLength)
    ____________ = strFrction / (10^ LenstrFrction)
    ____ strFrction = strFrction / (10^ LenstrFrction)

    Reconstruction using Maths (220-290)
    240-250 For a positive original number the Mathematical addition is straight forward.
    260-280 For a negative number the Number must first be constructed with the Mathematical addition to get the correct magnitude without the –ve sign , followed finally by conversion mathematically to a –ve number by multiplying by -1


    We are almost finished… we have what we want in a variable DblReturn
    A recap of the Pseudo Declaration Idea is useful here:
    Final construction / pseudo assignment of the Function variable for return
    The Function signature line _..
    Function CStrSepDbl(strNumber As String) As Double
    _.. was considered as pseudo a Declaring ( Diming ) code line for a variable .
    The corresponding pseudo assignment of the variable to a value is realised by passing a value to strNumber , pseudo
    Let FunctionCStrSepDbl = strNumber ‘ Where strNumber is a string that “looks like a number”, noting that Excel will accept a Number type into a String variable and convert it to a string automatically.
    The actual code line required has two possible syntaxes
    _ Call CStrSepDbl(strNumber)
    _ CStrSepDbl strNumber
    Those lines do not actually “fill” the variable “FunctionCStrSepDbl
    The signature line has defined a Double type to be returned held in the Pseudo variable CStrSepDbl
    Effectively CStrSepDbl is a variable of type Double
    I can assign a variable to that variable, that is to say place in some variable the value in CStrSepDbl just as I can any variable
    Dim Retn As Double
    _ Let Retn = CStrSepDbl
    ( ** In fact in the actual code that I have done, I used in the signature line Optional strNumber As String . Because of this I can use exactly that code line, without any syntax error.)
    Final code line(s) 310 and 340 ( and 30 ) __ CStrSepDbl = xxxxx
    So the discussion so far have got our function doing what we want. This is what happens when we Call the Function, in the variable assignment type line Let Retn = CStrSepDbl(“123.45”), that is to say pseudo code lines likje the following are done:

    Retn ________ , IsEqualTo , ___ ”variable” FunctionCStrSepDbl ______ - _ ButOnlyAfterTheFunctionCodeIsRun
    InVariableRetn , Is put in it , AfterRunnigTheCStrSepDbl(Using”123.45”) - TheContentsOf”variable” FunctionCStrSepDbl

    So if a call of the Function is made, such as with Retn = CStrSepDbl(“123.45”) , then the function is run and the contents of ”variable” FunctionCStrSepDbl is put in Retn.
    So Retn becomes ….. the value of an unassigned variable of the Double type …. _..
    _.. It becomes 0 . That is not very useful!!!
    As noted at the outset, VBA is holding CStrSepDbl as variable with Double type.
    We have the final thing we want: the number in variable DblReturn. We must now put this in the ”variable” FunctionCStrSepDbl before the function Ends
    This final required steps are done either of the code lines 310 or 340 ( or 30 )
    That final code line is of the form like
    __ CStrSepDbl = Retun


    The full code is here:

    http://www.excelfox.com/forum/showth...0502#post10502
    https://pastebin.com/1kq6h9Bn


    A shortened Function code is given in the next post, along with a calling code to help demo

    Ref:
    http://www.eileenslounge.com/viewtop...=22850#p208624
    http://www.excelfox.com/forum/showth...0192#post10192
    http://www.excelfox.com/forum/showth...0463#post10463
    https://www.excelforum.com/developme...ml#post4630570
    https://www.mrexcel.com/forum/excel-...tr#post2845398
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  3. #3
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,270
    Rep Power
    10
    Shortened Code version of Function described in last Post, and demo calling code


    Code:
    '    http://www.excelfox.com/forum/showthread.php/2232-Excel-VBA-comma-point-thousand-decimal-separator-number-problem?p=10503#post10503
    Sub TestieCStrSepDblSHimpfGlified() ' using adeptly named  TabulatorSyncranartor ' / Introducing LSet TabulatorSyncranartor Statement :   http://www.excelfox.com/forum/showthread.php/2230-Built-in-VBA-methods-and-functions-to-alter-the-contents-of-existing-character-strings
    Dim LooksLikeANumber(1 To 17) As String
     Let LooksLikeANumber(1) = "001,456"
     Let LooksLikeANumber(2) = "1.0007"
     Let LooksLikeANumber(3) = "123,456.2"
     Let LooksLikeANumber(4) = "0023.345,0"
     Let LooksLikeANumber(5) = "-0023.345,0"
     Let LooksLikeANumber(6) = "1.007"
     Let LooksLikeANumber(7) = "1.3456"
     Let LooksLikeANumber(8) = "1,2345"
     Let LooksLikeANumber(9) = "01,0700000"
     Let LooksLikeANumber(10) = "1.3456"
     Let LooksLikeANumber(11) = "1,2345"
     Let LooksLikeANumber(12) = ".2345"
     Let LooksLikeANumber(13) = ",4567"
     Let LooksLikeANumber(14) = "-,340"
     Let LooksLikeANumber(15) = "00.04"
     Let LooksLikeANumber(16) = "-0,56000000"
     Let LooksLikeANumber(17) = "-,56000001"
    Dim Stear As Variant, MyStringsOut As String
        For Each Stear In LooksLikeANumber()
        Dim Retn As Double
         Let Retn = CStrSepDblSHimpfGlified(Stear)
        Dim TabulatorSyncranartor As String: Let TabulatorSyncranartor = "                         "
         LSet TabulatorSyncranartor = Stear
         Let MyStringsOut = MyStringsOut & TabulatorSyncranartor & Retn & vbCrLf
         Debug.Print Stear; Tab(15); Retn ' When in VB Editor, Hit Ctrl+g to reveal Immediate window
        Next Stear
     MsgBox MyStringsOut
    End Sub
    '
    
    
    
    ' http://www.excelfox.com/forum/showthread.php/2232-Excel-VBA-comma-point-thousand-decimal-separator-number-problem?p=10503#post10503
    Function CStrSepDblSHimpfGlified(ByVal strNumber As String) As Double
    50     If Left$(strNumber, 1) = "," Or Left$(strNumber, 1) = "." Then strNumber = "0" & strNumber
    60     If Left$(strNumber, 2) = "-," Or Left$(strNumber, 2) = "-." Then strNumber = Application.WorksheetFunction.Replace(strNumber, 1, 1, "-0")
    70    strNumber = Replace(strNumber, ".", ",")
    90     If InStr(1, strNumber, ",") > 0 Then
    240         If Left(Replace(Left$(strNumber, (InStrRev(strNumber, ",", Len(strNumber)) - 1)), ",", Empty), 1) <> "-" Then
    250          CStrSepDblSHimpfGlified = CDbl(CLng(Replace(Left$(strNumber, (InStrRev(strNumber, ",", Len(strNumber)) - 1)), ",", Empty))) + CDbl(Mid$(strNumber, (InStrRev(strNumber, ",", Len(strNumber)) + 1), (Len(strNumber) - InStrRev(strNumber, ",", Len(strNumber))))) * 1 / (10 ^ (Len(Mid$(strNumber, (InStrRev(strNumber, ",", Len(strNumber)) + 1), (Len(strNumber) - InStrRev(strNumber, ",", Len(strNumber)))))))
    260         Else
    280          CStrSepDblSHimpfGlified = (-1) * (CDbl(Replace(Replace(Left$(strNumber, (InStrRev(strNumber, ",", Len(strNumber)) - 1)), ",", Empty), "-", "", 1, 1)) + CDbl(Mid$(strNumber, (InStrRev(strNumber, ",", Len(strNumber)) + 1), (Len(strNumber) - InStrRev(strNumber, ",", Len(strNumber))))) * 1 / (10 ^ (Len(Mid$(strNumber, (InStrRev(strNumber, ",", Len(strNumber)) + 1), (Len(strNumber) - InStrRev(strNumber, ",", Len(strNumber))))))))
    290         End If
    320    Else
    340     CStrSepDblSHimpfGlified = CDbl(strNumber)
    350    End If
    End Function
    Typical demo Output:
    ( In Immediate Window )
    Code:
    001,456        1.456 
    1.0007         1.0007 
    123,456.2      123456.2 
    0023.345,0     23345 
    -0023.345,0   -23345 
    1.007          1.007 
    1.3456         1.3456 
    1,2345         1.2345 
    01,0700000     1.07 
    1.3456         1.3456 
    1,2345         1.2345 
    .2345          0.2345 
    ,4567          0.4567 
    -,340         -0.34 
    00.04          0.04 
    -0,56000000   -0.56 
    -,56000001    -0.56000001
    ( MsgBlx Displayed)
    MsgBolox.JPG https://imgur.com/MtDObYA
    MsgBolox.JPG




    Refs
    https://excelribbon.tips.net/T013675...h_Periods.html
    https://excelribbon.tips.net/T007563...ed_by_100.html
    Last edited by DocAElstein; 06-13-2021 at 04:01 PM.

Similar Threads

  1. Replies: 8
    Last Post: 05-02-2017, 06:20 PM
  2. Excel Number Format: Indian Style Comma Separation
    By Rick Rothstein in forum Rick Rothstein's Corner
    Replies: 6
    Last Post: 09-18-2013, 11:38 AM
  3. Replies: 3
    Last Post: 03-31-2013, 06:18 AM
  4. Follow-up to "Excel Number Format: Indian Style Comma Separation"
    By Rick Rothstein in forum Rick Rothstein's Corner
    Replies: 2
    Last Post: 04-14-2012, 10:46 PM
  5. Replies: 4
    Last Post: 03-10-2012, 07:15 PM

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •