Page 3 of 3 FirstFirst 123
Results 21 to 30 of 30

Thread: VBA Input Pop up Boxes: Application.InputBox Method versus VBA.InputBox Function

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

    Simplified Walkthrough coding explanations

    Simplified Walkthrough coding explanations

    The detailed explanations in the last two pages ( https://www.excelfox.com/forum/showt...utBox-Function
    https://www.excelfox.com/forum/showt...Function/page2 ]
    ) are rather rich and intense, such that they need a lot of time and consideration and its easy to get bogged down and miss seeing the wood for the trees

    This page 3 ( ) will be a shorter simplified explanation based mostly on a step debug mode *step through the code lines, followed by a brief sinple run to remind us of what the whole thing is for/about.

    ( * F8 keyboard key from the VBEditor, (after selecting anywhere in the coding you want to step through, which in our case is the main Sub. That will let you step line by line through the coding. In this node a number of other useful tools are available, just one of which is that hovering over a variable, or some simple expressions, may cause a small pop up to appear telling you of the contents. - https://i.postimg.cc/tCf4krzW/Step-d...n-main-Sub.jpg )


    There will be 4 x 2 Pair explanations/demos. A Pair is made up of
    _ stepping through the codings in the uploaded file:
    _ doing a run


    The first pair is based on the same codings so far discussed, and all the codings are in one code module, AlansInputBoxComnuts

    The second pair is almost identical to the first, (most of it is a direct copy!), but the code looks at the issue of a, (perhaps untypical/ unusual thing under the circumstances), ByVal passing of the range object

    For the other 4 posts, they differ only in that the main sub is in separate module to the declarations and other two routines, as would likely be the case in the practice, with the main sub doing something actually requiring the API InputBox
    Attached Files Attached Files
    Last edited by DocAElstein; Today at 07:12 PM.

  2. #22
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,439
    Rep Power
    10
    This is now post 22 after a copy of full page 2 got me a new full page 3
    It was Taken from the Second copy from New post #16, 31 Oct 2024, all done on 31 Oct 2024
    #post24891




    Explanations to coding in module AlansInputBoxComnutByRef

    Step through the coding to explain it
    Open the Visual Basic Editor ( When in the spreadsheet Hold Alt key and press key F11 )

    We can identify 4 main coding sections.
    https://i.postimg.cc/Y9Tw5zhn/4-main...g-sections.jpg




    The second section is the coding we actually run. That coding would in a real life example likely be somewhere else, and almost certainly part of a larger coding, ( as we do in the last 4 post explanations) The other 3 sections would most likely, for the sake of tidiness, be kept in their own coding module. They are basically the main clever background API related stuff

    Click anywhere in Private Sub MainSubWithAllOtherStuffInIt(),
    Press continually the F8 key to step through line by line.
    https://i.postimg.cc/SKZ5jnXb/Step-d...n-main-Sub.jpg
    We pass Dim RSel As Range , without hanging there, (as declare type code lines such as that are pseudo already done in VBA coding). It is necessary to have been done, because we pass that range variable ( which contains a pointer to the range object) ByRef. (That "by referable" , ByRef , to the variable type passing is determined by the signature line in the next routine, Private Sub HangAHookToCatchAPIssinUserDLL_MsgBoxThenBringThat MsgBoxUp(ByRef RcelsToYou) )


    Passing Call HangAHookToCatchAPIssinUserDLL_MsgBoxThenBringThat MsgBoxUp(RSel) , takes us, as we typically expect in VBA, into Private Sub HangAHookToCatchAPIssinUserDLL_MsgBoxThenBringThat MsgBoxUp(ByRef RcelsToYou) '
    https://i.postimg.cc/L6zWjQ4C/passin...cels-To-Yo.jpg
    passing into Private Sub HangAHookToCatchAPIssinUserDLL_MsgBoxThenBringThatMsgBoxUp(ByRef Rcels.jpg





    Passing Set RcelsToYou = Selection effectively makes the variable in the main Sub, RSel point to the selected range in the active spreadsheet ( Active Cell :- http://www.eileenslounge.com/viewtop...2b3811#p313746
    http://www.eileenslounge.com/viewtop...313746#p313746
    )

    ( Passing Let BookMarkClassTeachMeWind = 5 allows us later to use a variable when we want to use a 5 , the reasons form that are explained in the extended explanations).

    Passing Let hHookTrapCrapNumber = SetWindowsHooksExample(BookMarkClassTeachMeWind, AddressOf WinSubWinCls_JerkBackOffHooKerd, 0, GetDaFredId) arranges that the final routine, Private Function WinSubWinCls_JerkBackOffHooKerd(ByVal lMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long ' is likely to be set off when certain things, "events", happen. Importantly for us, one of those things, "events", is when we use the available non modal pop up, "MessageBoxA". (That "MessageBoxA" pop up., is something similar to the standard available VBA MessageBox , and this extra one is effectively made available to us in the first declaration line. The main difference, that is important for us, is that the "MessageBoxA" is non modal, meaning in simple terms that we can make a selection in the spreadsheet whilst it is showing. That is not possible with the standard VBA MessageBox )
    Crudely, simplified in Laymen terms, I have set a hook that may catch some things

    ( The next set of code lines,
    Dim Valyou As Variant: Let Valyou = RcelsToYou.Value: If IsArray(Valyou) Then Valyou = Valyou(1, 1)
    , are not a main part of the important coding, and are only needed for the specific implementation. In this specific implementation, at some point later, I show the selection value of the range selected. This set of code lines ensures I do not error if attempting to show a single value when the user has selected more than one cell. If that was done, then I show just the top left cell value. )

    We now pass Let Rpnce = APIssinUserDLL_MsgBox( hWnd:=&H0, Prompt:="Yes, or No to ReCheck, Cancel for help ", Title:="Selection Check: Address is " & RcelsToYou.Address & " Value is """ & Valyou & """", Buts:=vbYesNoCancel ) ' . Ordinarily in a more simple use of the non modal MessageBoxA, this would bring up our Message Box pop up. But that does not immediately happen because we set a hook which amongst other things catches things that may go on when the dll coding set of by MessageBoxA, runs. (More technically speaking, I have done a bit of sub classing or made a form of custom dll of my own).
    My hook has been pulled/aroused, which sets off Function WinSubWinCls_JerkBackOffHooKerd( ByVal lMsg As Long, ByVal wParam As Long, ByVal lParam As Long ) As Long '
    https://i.postimg.cc/TP6d9sCY/passin...-As-Long-B.jpg
    passing into Function WinSubWinCls_JerkBackOffHooKerd(ByVal lMsg As Long, ByVal wParam As Lon.jpg

    The main purpose of Function WinSubWinCls_JerkBackOffHooKerd( [ color=Blue]ByVal[/color] lMsg As Long, ByVal wParam As Long, ByVal lParam As Long ) As Long ' can in simple terms be regarded as modifying some dimensions of a window that is opening. In other words we caught our MessageBoxA opening, and mess with some of its default dimensions. That is what these figures are about (wParam, 0, 10, 50, 400, 150, 40)
    There are a couple of snags, _(a) and _(b), one expected, _(b), and one that only I have noticed, _(a).
    _(a) When I do the code line SetWindowPosition(wParam, 0, 10, 50, 400, 150, 40) , an unexpected/ unwanted occurrence is that the function is set off again, that is to say a copy of it starts before the initial copy finishes. This is allowed in VBA coding and is basically the phenomena known as recursion. (Often this can go on almost for ever, before the famous stack overflow error occurs when your computer can no longer cope with storing things related to the many copies that are started but never finished. Strangely in this case, it seems to be stopped at a certain number of copies, so it is not such a terminal problem. Never the less it is undesirable. So I have a global variable, GlobinalCntChopsLog which has the effect of keeping track of the copy number currently running. (This is achieved by increasing it by 1 when a copy starts, and decreasing it by 1 when the copy finishes.
    So the second line in the, If GlobinalCntChopsLog = 2 Then …………. effectively allows us to do the necessary terminations, when the function has done once already what we want, which is the dimension related stuff, (wParam, 0, 10, 50, 400, 150, 40)
    _(b) Not all things that are caught by the hook and so set off this function are the thing which allow the (wParam, 0, 10, 50, 400, 150, 40) to do what we want. The If lMsg = 5 Then makes the correct event. (It is a bit too subtle point for this simplified explanation, but 5 coming into the function via BookMarkClassTeachMeWind from the previous routine does not always follow that a 5 would be used here. )

    We may have got a bit lost in the trees here. So lets us go back a bit to ………My hook has been pulled/aroused, which sets off Function WinSubWinCls_JerkBackOffHooKerd( ByVal lMsg As Long, ByVal wParam As Long, ByVal lParam As Long ) As Long '
    https://i.postimg.cc/TP6d9sCY/passin...-As-Long-B.jpg ……

    If you step through, you will see that the function is done a few times. This is perhaps because we are either catching many things or, as the more detailed explanations suggest, we may actually have a few hooks catching things. They do not all meet the requirement of the If lMsg = 5 Then ….. so not much is done. (In these repeated runs of the function, we ended the functions normally, so GlobinalCntChopsLog is 1, so we do not encounter the recursion phenomena discussed )
    Eventually after about 6 goes, the If lMsg = 5 Then ….. criteria is satisfied. The main …. (wParam, 0, 10, 50, 400, 150, 40)…. is then done, but you will notice that doing that seems to set off the function again, but if you continue to step through and hover over the variable GlobinalCntChopsLog, you will see that it is 2, so we have detected this, https://i.postimg.cc/DwRnkxV9/Hover-...og-is-at-2.jpg Hover over to see GlobinalCntChopsLog is at 2.JPG
    By virtue of that 2, the termination of the current running function is done with a necessary removal or the hook or hooks, or similar done by the UnHookWindowsHookCodEx hHookTrapCrapNumber
    We return then into the previous function, Sub HangAHookToCatchAPIssinUserDLL_MsgBoxThenBringThat MsgBoxUp(ByRef RcelsToYou) ' , which initially has the effect of the line which triggered Function WinSubWinCls_JerkBackOffHooKerd( ByVal lMsg As Long, ByVal wParam As Long, ByVal lParam As Long ) As Long completing ,which attempted to, and so does now , bring up the pop up. So it should then, indeed, pop up https://i.postimg.cc/s2hcw4Rf/Popped-up.jpg Popped up.jpg
    After making a selection, you will come to the next line in the main Sub of Set RcelsToYou = Selection …………….. https://i.postimg.cc/DZTbKt8D/Completed-pop-up.jpg Completed pop up.JPG


    The rest is fairly self explanatory:- Basically once you are happy that you have made the correct range selection, this routine, Sub HangAHookToCatchAPIssinUserDLL_MsgBoxThenBringThat MsgBoxUp(ByRef RcelsToYou) , ends and you are back into the main coding, and have the range object of your choice in the variable RSel
    Last edited by DocAElstein; Today at 07:11 PM.

  3. #23
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,439
    Rep Power
    10
    This is now post 23, after a copy of full page 2 gave me a full page 3
    It was First copy from New post #16, all done on 31 Oct 2024
    #post24889



    A run of Private Sub MainSubWithAllOtherStuffInIt()


    We need to make a minor change, temporarily, so as to be able to run the main macro from the spreadsheet: Change the Private to Public
    https://i.postimg.cc/rwRwrPxm/Change...emporarily.jpg

    Now, we can close the VBEditor and concentrate on the spreadsheet.

    Select some arbitrary cell with any value in it: https://i.postimg.cc/hG94CQCR/Select...alue-in-it.jpg


    Take the - View - Macros - ribbon route,
    https://i.postimg.cc/3wMJCFFZ/View-t...via-ribbon.jpg
    , ( or the short cut key combination of holding the Alt key then selecting key F8 ) , to get the macro dialogue pop up

    Select Sub MainSubWithAllOtherStuffInIt() and then the Run Button: https://i.postimg.cc/PrRqNjL9/Run-Su...tuff-In-It.jpg


    The message box pop up should now prompt you for for a response: https://i.postimg.cc/bNJJzJv1/Prompted-for-answer.jpg

    Let us say , just as a demonstration example , that you did not want that cell that is selected. So, ignore the prompt initially, and make another selection: https://i.postimg.cc/gc4jFRGY/Make-a...-selection.jpg (This should be possible, since, unlike the standard VBA message box pop up, our pop up is non modal, which means you can still select things whilst the pop up is showing)

    The message box pop up will not have changed as a result od you making a new selection, , and will it still be suggesting / asking you if you wanted the previous selection. So answer No n https://i.postimg.cc/MHsp7k9c/Answer-No.jpg

    The message box pop up should then re appear almost immediately indicating that you have the new selection:
    https://i.postimg.cc/0j5NK50R/Messag...-selection.jpg

    So answer Yes https://i.postimg.cc/Jn5nhHJ5/Answer-Yes.jpg



    The demonstration is finished at this point. This is just a demonstration, so nothing useful was done. However, in a practical coding, one that then continued, you would have now your second selection as a range object represented by the variable RSel , - To achieve that is the main purpose of this Thread


    Please remember to change back the main coding to Private, before following any further posts in this Thread, (or alternatively disregard the file you have, and re download it)
    Attached Files Attached Files
    Last edited by DocAElstein; Today at 07:10 PM.

  4. #24
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,439
    Rep Power
    10
    This is a new post 24. It appeared after a copy of full page 2 gave me a full page 3. It is #post24897
    It came from Original post #13, it got shifted down to post #15 when posts 11 12 and 13 where copied on 31 Oct 2024
    #post10485



    This is almost identical to post #24
    In fact we only really need 1 change, in the signature line of the routine first set off/Called by the main coding, but two other changes will be made to aid in the explanation
    Code:
     Set RSel = Selection    ' To aid in the explanation of the  ByVal example 
     Call HangAHookToCatchAPIssinUserDLL_MsgBoxThenBringThatMsgBoxUp(RSel)  '                     In a normal application of the main Theme of all this, this would be the main code line you use to cause a the "Pop Up User pseudo InputBox with range selection alternative with API User 32 dll Programs"
                       ' VBA.MsgBox Prompt:="Address check RSel - It is now " & RSel.Address & "" & vbCr & vbLf & "Da .Value of the range object is " & RSel.Value ' Just done to demo that A simple change of the ByRef to ByVal in the signature line of a Called routine allows you to change the value of a range object to that of the selection, but the original range object will not change, that is to say its address remains as before the selection.
    '
    '  Other stuff
     RSel.Select              ' To aid in the explanation of the  ByVal example
    End Sub ' Typically this is your main program  End Sub
    'Private Sub HangAHookToCatchAPIssinUserDLL_MsgBoxThenBringThatMsgBoxUp(ByRef RcelsToYou) ' This will by referral To You, (RSel), the actual Pointer of you the original RSel.  This is not too important a point here, but intersting if you consider the next line alternative to this one.....
    Private Sub HangAHookToCatchAPIssinUserDLL_MsgBoxThenBringThatMsgBoxUp(ByVal RcelsToYou)  '   The RSel Pointer aint Gone anywhere if you do this. Just a copy of the Pointer is here. This will allow you to change the value as the Pointer or a copy of it will tell you where to go and do that... But in neither this line or the last line case have you sent the range object. If you use this line then you will find that the address of the range object will not change, as that refers to the range object of the copy variable in this subroutine. But that will not change the range object of RSel 
    The full coding is in the code module, AlansInputBoxComnutsByVal , in the uploaded file, InputBoxMessageBoxPopUpBugsAPI.xls

    Explanation of important difference to the ByRef example.
    Since the main change is so minimal, it is probably more useful to explain the important effects of the difference rather than repeat most of what was in the previous explanation :
    We have filled/assigned the variable RSel to the current selection ** in the main sub to the existing selection, with the first extra line - Set RSel = Selection - added to aid in the explanation, and we do this just before the coding goes off into the API related things.
    The first thing that then is done in the initial API coding is that a code line - Set RcelsToYou = Selection - does effectively very similar to our first extra code line. However, the main point that will be emphasised many times in such explanations, is that the second time we are doing something important a bit different: RcelsToYou is no longer referring to the variable RSel. It will at this point, point to the same range object assigned to RSel, because it is a copy of the pointer. But as we proceed through selections via our pop up in the course of running normally all the coding, we will no longer be actually changing the range object to which RSel refers/points to.

    Just before the end of the main coding , the other extra code line - RSel.Select - will now select our very first selection, regardless of any selections we made during the course of our pop up in the course of running normally all the coding.
    The end result rather goes against the main purpose of this thread, which is to have the range object referred to/ pointed to by the variable RSel changed as a result of a selection. But it emphasises the need to have ByRef in the coding to achieve our main original requirement

    ( ** Note that if we had not had the first extra code line, then the final extra code line would actually have errored, since RSel would not have been assigned a range object. For the same situation in the previous ByRef coding example, there would be no error as the variable RSel was effectively being referred to and assigned one or more times course of our pop up in the course of running normally all the coding. )
    Attached Files Attached Files
    Last edited by DocAElstein; Today at 07:10 PM.

  5. #25
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,439
    Rep Power
    10
    This is a new post 25, appearing after a copy of full page 2 got me a new full page 3 It is #post24898
    It came from New post #16, 31 Oct 2024, it came from the original post #13 when original posts 11 12 and 13 where copied on 31 Oct 2024
    #post24888




    Working example for the ByVal case

    We will do a practical example that helps show the important difference between the ByVal and ByRef codings. (Although it should be noted that there are many simpler ways to achiever the same without the complicated API stuff)

    We will use exactly the same demo coding as in the last post The full coding is in the code module, AlansInputBoxComnutsByVal , in the uploaded file, InputBoxMessageBoxPopUpBugsAPI.xls

    I need to make the same minor temporary change to the main coding, just as I did in the last post. As previously, this is just so that I can access the macro from the spreadsheet: Please change the Private to Public in the main.
    https://i.postimg.cc/J08KY7rK/Change...emporarily.jpg

    We can close not the VBEditor, and concentrate on the spreadsheet.



    Lets say we have a long list, which in the practice could be very long. Lets say I want to work down the list , changing just some cell values.


    Take the - View - Macros - ribbon route,
    https://i.postimg.cc/3wMJCFFZ/View-t...via-ribbon.jpg
    , ( or the short cut key combination of holding the Alt key then selecting key F8 ) , to get the macro dialogue pop up

    Select Sub MainSubWithAllOtherStuffInIt() and then the Run Button: https://i.postimg.cc/LsrxfBGc/Run-Su...tuff-In-It.jpg


    Select a cell towards the top of the list,
    https://i.postimg.cc/ydcvT3Hk/Select...f-the-list.jpg
    , make a change, such as dragging a value down.
    https://i.postimg.cc/rpdhKYZG/Make-s...value-down.jpg


    Make some similar change a bit further down, such as dragging a value up.
    https://i.postimg.cc/QdY4Nrmx/Select...ue-details.jpg

    If now you select No on the message box pop up, then your top left selection value will be shown, as well as the range selection address.
    https://i.postimg.cc/QdY4Nrmx/Select...ue-details.jpg

    If you now select Yes on the message box pop up, you will be taken back to your original selection, (and the message box goes away)
    https://i.postimg.cc/WbnYKZJZ/Select...-selection.jpg


    The final selection of the original cell was caused by the last extra code line, RSel.Select , in the main sub, because in that Main sub, the range referred to in RSel is the original set cell selection. The variable was not referred to by the routine, Sub HangAHookToCatchAPIssinUserDLL_MsgBoxThenBringThat MsgBoxUp(ByVal RcelsToYou), as the variable, RcelsToYou , was instructed in that signature line, ( Sub HangAHookToCatchAPIssinUserDLL_MsgBoxThenBringThat MsgBoxUp(ByVal RcelsToYou) ) to just take a copy*, ( *in the case of a range object, (as with all objects), it is the copy of the pointer to a range object




    (Please remember to change back the main coding to Private, before following any further posts in this Thread, (or alternatively disregard the file you have, and re download it)
    Attached Files Attached Files
    Last edited by DocAElstein; Today at 07:09 PM.

  6. #26
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,439
    Rep Power
    10
    This is a new post 26, appearing after a copy of a full page 2 gave me a full page 3. It is #post24899
    It came from Second copy from New post #16, 31 Oct 2024, all done on 31 Oct 2024
    #post24890

    Last edited by DocAElstein; 11-02-2024 at 09:18 PM.

  7. #27
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,439
    Rep Power
    10
    This is a new post 27, appearing after a copy of full page 2 gave me a full page 3. It is #post24900
    It came from It was Taken from the Second copy from New post #16, 31 Oct 2024, all done on 31 Oct 2024
    #post24891

    Last edited by DocAElstein; 11-02-2024 at 09:32 PM.

  8. #28
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,439
    Rep Power
    10
    This is a new post 28, appearing after a copy of a full page 2 gave me a full page 3 It is now #post24901
    It came from It came from First copy from New post #16, all done on 31 Oct 2024
    #post24889

    Last edited by DocAElstein; 11-02-2024 at 09:32 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!!

  9. #29
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,439
    Rep Power
    10
    This was Post #20, but when I copied all of page 2, it became post #29 https://www.excelfox.com/forum/showt...age3#post24892
    https://www.excelfox.com/forum/showthread.php/2227-VBA-Input-Pop-up-Boxes-Application-InputBox-Method-versus-VBA-InputBox-Function/page3#post24892
    https://www.excelfox.com/forum/showt...ll=1#post24892
    https://www.excelfox.com/forum/showthread.php/2227-VBA-Input-Pop-up-Boxes-Application-InputBox-Method-versus-VBA-InputBox-Function?p=24892&viewfull=1#post24892
    The second link still worked, the first needed me to change the page 2 to page 3, which makes sense. (Otherwise it went to the top of page 2)


    Last edited by DocAElstein; 11-02-2024 at 07:38 PM.

  10. #30
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,439
    Rep Power
    10
    This is post 30, it came from post … well …post 29 that was post 20. So effectively it came from the post above
    29 https://www.excelfox.com/forum/showt...age3#post24902
    https://www.excelfox.com/forum/showthread.php/2227-VBA-Input-Pop-up-Boxes-Application-InputBox-Method-versus-VBA-InputBox-Function/page2#post24902
    https://www.excelfox.com/forum/showt...ll=1#post24902
    https://www.excelfox.com/forum/showthread.php/2227-VBA-Input-Pop-up-Boxes-Application-InputBox-Method-versus-VBA-InputBox-Function?p=24902&viewfull=1#post24902
    links are OK


    Last edited by DocAElstein; 11-02-2024 at 08:10 PM.

Similar Threads

  1. How To React To The Cancel Button in a VB (not Application) InputBox
    By Rick Rothstein in forum Rick Rothstein's Corner
    Replies: 2
    Last Post: 02-04-2018, 01:48 AM
  2. Replies: 2
    Last Post: 02-12-2016, 04:32 PM
  3. InputBox OK and Cancel Button Problem
    By mackypogi in forum Excel Help
    Replies: 5
    Last Post: 05-30-2014, 12:20 AM
  4. VBA To Display Pop Up Alert When Duplicate Entry Is Made
    By peter renton in forum Excel Help
    Replies: 20
    Last Post: 07-26-2013, 07:56 PM
  5. Number validation in Text Boxes VBA
    By Admin in forum Excel and VBA Tips and Tricks
    Replies: 2
    Last Post: 05-17-2012, 02:48 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
  •