WasteNot Excel VBA Library Module LM2 Documentation

Data Types

DTc > Bool > wCBool wCBool ( iVar As Variant, Optional oaExc As Boolean ) As  Boolean    '191008b Returns CBool(iVar), unless this would cause a RTE,
   in which case it Fails and oaExc is Seton
  Fails if iVar is Null, Nothing, Non-Numeric, or >1 Cell, but
  **NOTE**           CBool & wCBool Both
        SUCCEED and Return False if iVar is Empty
                   eg 1 Blank Cell
              IsValBool() Fails in these cases
  egs   Returns False
                   if oaExc is SetOn
                   iVar is Empty
              for  0, 0.0 , "0" , False, "false",
              for  any Numeric Expression that Evaluates to 0
       Returns True
              for  1, 0.1 , "1" , True,  "true" ,
              for  any Numeric Expression that Evaluates to 1

DTc > Bool > wCBoolOK wCBoolOK ( iVar As Variant, Optional oaBool As Boolean ) As  Boolean    '191008c The same as wCBool(), but in a format suitable for Conditional Testing
    ie Returns wCBool()'s oaExc, and sets oaBool to wCBools()'s Return

DTc > Bool > IsValBool IsValBool ( iVar As Variant, Optional ouBool As Boolean ) As  Boolean    '191008a The Same as as wCBool() & wCBoolOK() except that
  1) IsValBool Fails if iVar is Empty
  2) On Failure, ouBool is Unchanged

DTc > Bool > we_TriS Tri-State  Enumeration    `161100a > DTc.IsValBool() we_tsUnk
we_tsRes
we_tsSet
 
=  0 = False
= -1 = True
= -2 = True -1
  zBool = (zTriS = we_tsSet); Sets zBool iff zTriS = we_tsSet
DTc > Long > wCLng wCLng ( iVar As Variant, Optional oaExc As Boolean ) As  Long    '161000n Returns CLng(iVar), unless this would cause a RTE,
  in which case it Returns 0 and oaExc is Seton (it Fails)
    Fails if iVar is Null, Nothing or >1 Cell, but
  **NOTE**           CLng & wCLng Both
         SUCCEED and Return 0 if iVar is Empty
                  eg 1 Blank Cell
             IsValLong() Fails in these cases
  Fractional iVars are Rounded using VB's Default Round to Even
  All Numeric Expressions Succeed
  eg   "&HF", Exponential Expressions, Dates etc
  Text Expressions only Succeed if CLng(TextExp) Succeeds
    egs    ""                 -> 0
           " "                -> Fails
          0.49              -> 1
          0.50              -> 0
          1.51              -> 2
          "$1.50"          -> 2
          "01-Jan-2001" -> Fails
          CDate("01-Jan-2001")
                                -> 36892
          "1-"                -> -1
          "1-1"              -> Fails

DTc > Long > wCLngOK wCLngOK ( iVar As Variant, Optional oaLong As Long ) As  Boolean    '161000p The same as as wCLng(), but in a format suitable for Conditional Testing
DTc > Long > IsValLong IsValLong ( iVar As Variant, Optional ouLong As Long, _
Optional iLowerLim As Long = wk_dtILong, _
Optional iUpperLim As Long = wk_dtALong ) As  Boolean    '191007h
The Same as as wCLng and wCLngOK() except that
  1) it also Fails if iVar is         Empty
  2)             "             <iLowerLim Or >iUpperLim
  3) On Failure, ouLong is Unchanged, whereas wCLngOK()'s oaLong is Zeroed

DTc > Long > GreLong GreLong ( iLong1 As Long, iLong2 As Long ) As  Long    '141000a Returns the Greater of two Long Values
DTc > Long > LessLong LessLong ( iLong1 As Long, iLong2 As Long ) As  Long    '141000b Returns the Lesser of two Long Values
DTc > Long > LongDiv LongDiv ( iDivd As Long, iDivs As Long, Optional oLRes As Long, _
Optional oLRem As Long, Optional oDRem As Double ) As  Boolean    '191007b
Returns the Truncated Value iDivd\iDivs (as oLRes), and the Remainder
  as a both a Long (oLRem) and a Decimal Value (oDRem)
Fails if the Divisor (iDivs) is 0
  oLRem = iDivd Mod iDivs   and   oDRem = oLRem / iDivs

DTc > Long > StripLong StripLong ( ioStr As String, Optional ocLong As Long, _
Optional iNoClear As Boolean, Optional oaLastDigPos As Long, _
Optional iTrim As Boolean ) As  Boolean    '161000j
Sets ocLong to the Long Value terminated at the First Non-Digit in ioStr (excluding a Leading Minus Sign)
  Fails if the First Character of ioStr is a Non-Digit, or a Minus Sign followed by a Non-Digit
  If StripLong Fails and iNoClear is Set, ocLong is Unmodified, Not Cleared
  oaLastDigPos is the Last Digit's Position in ioStr
  If iTrim is Set, ocLong's Characters are Trimmed from ioStr
  eg ioStr="23rd" would return ioStr as "rd"
    egs  Success      "0"    ->  0
                        "-0."   ->  0
                       "23rd"  ->  23
                       "2.99"  ->  2
           Failure     "", "-", "The 2nd"

DTc > Long > BSL BSL ( iLong As Long, Optional ByVal iNOPlaces As Long = 1, _
Optional iWrap As Boolean, Optional oaUnlBit As Boolean ) As  Long    '161000a
Returns iLong, Bit Shifted iNOPlaces to the Left
If iWrap is  False  the MSB(32) is Set to         Zero          after each Bit Shift
     "         True                 "               the Unloaded Bit            "
  oaUnlBit is the Bit Unloaded on the Last Shift
  If iNOPlaces is <1 the Return is iLong and oaUnlBit is False

DTc > Long > BSR BSR ( iLong As Long, Optional ByVal iNOPlaces As Long = 1, _
Optional iWrap As Boolean, Optional oaUnlBit As Boolean ) As  Long    '161000b
Returns iLong, Bit Shifted iNOPlaces to the Right
If iWrap is  False  the LSB(1) is Set to         Zero          after each Bit Shift
     "         True               "               the Unloaded Bit            "
  oaUnlBit is the Bit Unloaded on the Last Shift
  If iNOPlaces is <1 the Return is iLong and oaUnlBit is False

DTc > Long > CouBits CouBits ( iTestLong As Long, _
Optional oaAllMats As Long, Optional oaLastMatBitN As Long, _
Optional iMatch0s As Boolean, Optional iRight As Boolean, _
Optional iStartAtBit As Long = 1, Optional iNOBits As Long = 32, _
Optional iStopAfterNMats As Long = 32 ) As  Long    '161000c
Counts the NO Bits in iTestLong which Match the Input Criteria
Default is to Count All the 1's in iTestLong, working Left from the LSB (Bit 1)
All Matching Bits in oaAllMats are Seton
oaLastMatBitN is set to the Last Matching Bit's Number (MSB=32, LSB=1)
  Setting iMatch0s causes 0's, not 1's, to be Matched
Setting iRight causes CouBits to work Right from iStartAtBit [1]
iNOBits may be used to restrict the NO Bits Tested [32]
iStopAfterNMats may be used to limit the Maximum NO Matchs [32]
  Setting iStartAtBit, iNOBits or iStopAfterNMats outside the range of 1 to 32
   doesn't seem to cause RTE's, but may cause unpredictable ouputs

DTc > Long > FitsMask FitsMask ( iTest As Long, iMask As Long ) As  Boolean    '161000d Returns True if All the 1 Bits in iMask are also 1's in iTest
  egs  &H11  &  &H10   Succeeds
         &H10  &  &H11   Fails
            *    &    0      Succeeds

DTc > Long > we_RatFrm Rating Formats  Enumeration    `191005c DTc.WStarRat() we_rfStar
we_rfOof10
we_rfWStar
we_rfPer
0-5 Dec
0-10 Dec
0-50 in Steps of 5
0-100 Dec
DTc > Long > WStarRat WStarRat ( ioRat As Variant, ioRatFrm As we_RatFrm, Optional oaExc As Boolean ) As  Long    '191005b Returns the WasteNot Star Rating of ioRat in ioRatFrm
  Sets oaExc and Returns -1 if ioRat is Invalid, or Out Of ioRatFrm's Range
  The WasteNot Star Rating is a Whole No. between 0 and 50,
  Rounded to the Nearest multiple of 5
  egs      1 Star -> 10      2.5 Stars -> 25       5 Stars -> 50
          2.6% -> 5             54% -> 25            94%-> 45
          1/10 -> 5            5/10 -> 25

DTc > Double > wCDbl wCDbl ( iVar As Variant, Optional oaExc As Boolean ) As  Double    '161007c Returns CDbl(iVar), unless this would cause a RTE,
  in which case it Returns 0.0 and oaExc is Seton
    Fails if iVar is Null, Nothing or >1 Cell, but
  **NOTE**           CDbl & wCDbl Both
        SUCCEED and Return 0 if iVar is Empty
                  eg 1 Blank Cell
             IsValDou() Fails in these cases
  All Numeric Expressions eg &H1, Exponential Expressions and Dates Succeed
    Text Expressions only Succeed if CLng(TextExp) Succeeds
    egs     ""                      -> 0.0
          " "                     -> Fails
          1.49                    -> 1.49
          "$1.50"                 -> 1.5
          "01-Jan-2001"           -> Fails
          CDate("01-Jan-2001")    -> 36892
          "1-"                    -> -1
          "1-1"                   -> Fails

DTc > Double > wCDblOK wCDblOK ( iVar As Variant, Optional oaDou As Double ) As  Boolean    '161007d The same as wCDbl(), but in a format suitable for Conditional Testing
DTc > Double > IsValDou IsValDou ( iVar As Variant, Optional ouDou As Double, _
Optional iLowerLim As Double = wk_dtIDou, _
Optional iUpperLim As Double = wk_dtADou ) As  Boolean    '161007g
The Same as Function as wCDblOK except that
  1) it also Fails if iVar is         Empty
  2)             "             <iLowerLim Or >iUpperLim
  3) On Failure, ouDou is Unchanged, whereas wCDblOK's oaDou is Zeroed

DTc > Double > we_DRouT Decimal Round Types  Enumeration    `191007i DTc.wRound() we_drtCeil
  we_drtAZ
we_drtTE
we_drtTZ
  we_drtFloor
 

(+,+)  Round All  Towards +Infinity
  (+,-)  Round 1/2Away from  Zero
(?,?)  Round 1/2to Even(Bankers)
(-,+)  Round 1/2 Towards  Zero
  (-,-)  Round All  Towards -Infinity
  eg (+,-)meansPositive Rounded Up
Negative Rounded Down
DTc > Double > wRound wRound ( iVar As Variant, Optional iRType As we_DRouT = we_drtAZ, _
Optional iRInt As Double = 1#, _
Optional oDRet As Variant, Optional oRem As Double, _
Optional oaIVarIsWhole As Boolean ) As  Boolean    '161007f

DTc > Double > GetNorExp GetNorExp ( ByVal ivVar As Variant, _
oNorExp As Long, Optional oFormStr As String ) As  Boolean    '161000e
Sets oNorExp to the Exponent of the Normalized Scientific
  Representation of ivVar, and oFormStr to a Standardized Formatting
  String with which to Display ivVar
    Fails if ivVar is Not a Valid Numeric Expression
    egs 2 for 951 (or 9.51E2)   and   -3 for 0.00951 ( or 9.51E-3)
  oFormStr is WasteNot's Standard Formatting String for the different
  oNorExp Ranges shown below;
    Format(ivVar,oFormStr) then returns;
        - the Full Value of any Long ivVar
      - a Value rounded to Three Significant Digits for other ivVar Types
        oNorExp Range         Format(ivVar,oFormStr)                    eg
             >  9           Scientific Format to 2 Decimal Places          1.23e10
      >= 0 and < 9         Includes 1,000 Separators              1,234,567,890
      >=-3 and < 0       Rounded to 3 Significant Digits              0.00123
            <-3           Scientific Format to 2 Decimal Places          1.23e-4

DTc > String > wCStr wCStr ( iVar As Variant, Optional oaExc As Boolean ) As  String    '191008d Returns CStr(iVar), unless this would cause a RTE,
  in which case it Returns the Null String and oaExc is Seton
    Fails if iVar is Null, Nothing, or >1 Cell, but
  **NOTE**           CStr & wCStr Both
        SUCCEED and Return the Null String if iVar is Empty
                   eg 1 Blank Cell
              IsValStr() Fails in these cases
  egs   Returns False
                   if oaExc is SetOn
                   iVar is Empty

DTc > String > wCStrOK wCStrOK ( iVar As Variant, Optional oaStr As String ) As  Boolean    '191008e The same as DTc_wCxzStr(), but in a format suitable for Conditional Testing
DTc > String > IsValStr IsValStr ( iVar As Variant, Optional ouStr As String ) As  Boolean    '191008f The Same as as wCStr and wCStrOK() except that
  1) it also Fails if iVar is         Empty
  2) On Failure, ouStr is Unchanged, whereas wCStrOK()'s oaStr is Nulled

DTc > String > Chars > wAscW wAscW ( iChar As String ) As  Long    '161000k Returns iChar's UTF16 (0-65,535) Character Code, as a Long Value
Similar to VB's AscW, except that VB's AscW
    1) Causes a RTE if the Input is a Null String
          ie         AscW("")   causes a RTE
      whereas    wAscW("")    returns 0
       Note however that AscW(ChrW(0)) returns 0
    2) Returns a Signed Integer
          eg          AscW(ChrW(65535)) returns  -1
      whereas    wAscW(ChrW(65535)) returns 65535
  Uses Left(iChar,1) if Len(iChar)>1

DTc > String > Chars > StrHasAnyChar StrHasAnyChar ( iChars As String, iInStr As String, _
Optional oaPos As Long ) As  Boolean    '161000h
Succeeds if iInStr contains Any of the Characters in iChars
oaPos is the Position of the first match in iChars, or Len(iChars)+1 on Failure
Succeeds with oaPos=0 if iChar is Null

DTc > String > Chars > we_CharT Character Types  Enumeration    `161100b DTc.GetCharTypes()
we_ctNone
 
we_ctCtrl
  we_ctNull
  we_ctCtrlDel
  we_ctPrn
    we_ctAlphaNum
  we_ctAlpha
  we_ctNavKey
we_ctNum
we_ctCap
we_ctLCase
    we_ctValFI



 

    we_ctValVB
 
we_ctExtAsc
we_ctOther
we_ctU16M1
see also (WNXlA_123.XLA!wCharCodes

  7-Bit ASCII  '0-127
0-31 & 127
0
127
  32-126
  we_ctNum Or we_ctAlpha
we_ctCap Or we_ctLCase
  33-40
48-57
65-90
97-122
  Any we_ctPrn EXCEPT the following 9
  "  *  /  :  <  >  ?  \  |
  34  42  47  58  60  62  63  92  124
OR we_ctCtrlDel
  This Bit WILL NOT be Set for Non-7-Bit ASCII Chars,
  even though they are Valid for FI Names
  we_ctAlphaNum Or Underscore (95)
  >=8 Bits
128-255aka UTF8
256-65,535 aka UTF16
see Code Notes > ChrW(-1)
DTc > String > Chars > GetCharTypes GetCharTypes ( iStr As String, _
Optional oaU16CC As Long, _
Optional oaChar As String, _
Optional iPos As Long = 1 ) As  we_CharT    '161200a
Returns the Character Types (as defined by we_CharT) of oaChar, the Character in Position iPos of iStr
oaU16CC is the UTF-16 Character for oaChar (0-65,535)
  Returns we_ctNone=0 (and sets oaChar to Null and oaU16CC to 0) if
  iStr is Null
  iPos=<1
  iPos>Len(iStr)

DTc > String > Chars > IsWSpChar IsWSpChar ( iStr As String, Optional iPos As Long = 1, _
Optional oaU16CC As Long ) As  Boolean    '170112b
Succeeds if the Character at iPos in iStr is a WhiteSpace Character
7 WhiteSpace Chars are Defined;
      U16CC     Symbol  Description
    009 (&H09)    HT    Horizontal Tab
  010 (&H0A)    LF    Line Feed
  011 (&H0B)    VT    Vertical Tab
  012 (&H0C)    FF    Form Feed
  013 (&H0D)    CR    Carriage Return
    133 (&H85)    …     Horizontal ellipsis
  160 (&HA0)     Non-breaking space

DTc > String > Chars > GetNextCC GetNextCC ( iChar As String, ouChar As String, Optional ouOCC As Long, _
Optional iPrev As Boolean, Optional iWrapE As Boolean, _
Optional oaWrapO As Boolean, _
Optional ByVal ivTarCT As we_CharT ) As  Boolean    '161200b
If Successful, Finds the Next, or Previous, Character of the Same Character Type as iChar
ouChar is set to this Character, and ouOCC to it's UTF16 Character Code
  Fails if
  1.  No Such Chararcter Exists
  2.  ivTarCT is specified and iChar is Not that Character Type
          (and is Not Null**)
  3.  ivTarCT is Invalid
  iPrev determines the Search Direction (the Default is Next)
  iWrapE Enables Wrapping, and oaWrapO is Seton if Wrapping has Occurred
  Togther, iPrev and iWrapE determine which ivTarCT Characters are Search Candidates;
    iPrev           iWrapE           Candidates then
                                    have a Character Code
     False           False              > iChar       (the Default)
   True            False              < iChar
 Don't Care      True             Any ivTarCT
  ivTarCT may used to specify any we_CharT Character Type
  If ivTarCT is Not Specified it is;
  Set to the Same Type as iChar if iChar is
      Numeric,
      a Captital Letter, or
      a Lower Case Letter
    Otherwise it is set to the Printable Character Set
  ** Note that you can find the First (or Last) Character of a Character Type by
       setting iChar to Null (Set iPrev as well to find the Last)
  Refer to (WNXlA_123.XlA > wCharCodes Worksheet for a summary of Character Codes
  egs
  iChar   iPrev iWrapE ivTarCT     ouChar  ouOCC
     Null                                           space     32       1st Printable
   Null     True                                   ~       126       Last Printable
    A                                                B        66        2nd Capital
    a       True                                                        Fails; Wrap is Off
    0       True    True                         9         57       Last Numeric
    =                         we_ctValFI        @        64       ">" and "?" are Invalid
   Null                     we_ctExtAsc      ***      128      1st Extended Ascii
   Null     True             we_ctCtrl        ***     127       Last Control
                                                      *** = can't be Printed

DTc > String > Chars > GetNextSeqStr GetNextSeqStr ( ByVal ivStr As String, Optional oStr As String, _
Optional iPrev As Boolean, _
Optional iWrapE As Boolean, Optional oaWrapO As Boolean, _
Optional iTarCT As we_CharT = we_ctAlphaNum ) As  Boolean    '161200c
If Successful, sets oStr to the Next, or Previous, string in iTarCT Order from ivStr
Fails if
 1.  ivStr is Null (unless iTarCT = we_ctCtrl)
 2.  No Such String Exists
 3.  iTarCT is Invalid
  Uses GetNextCC to Increment (or Decrement) the Right-most Character of
ivStr that is of Type iTarCT, ignoring any Characters that are Not of Type
iTarCT   eg  "7A8b" -> "7A9b"   if iTarCT = we_ctNum
  If the Right-most Character is a Limit Value for ivTarCT in the Search Direction,
then the Next Right-Most Character is also incremented/decremented, in a
similar manner to Counting   eg  "7A9b" -> "8A0b"
  iWrapE Enables Wrapping of the Left-Most Character, and oaWrapO is Seton
  if iWrapE is Set AND the Left-Most Character Wraps
   egs "9A9b" -> "0A0b"  if iWrapE is Seton (Succeeds and Setson oaWrapO)
                    but
       "9A9b" -> "9A9b"  if iWrapE is Reset (Fails )
                    and
       "7A9b" -> "8A0b"  Succeeds and Resets oaWrapO regardless of iWrapE

DTc > String > Substring wLeft wLeft ( iStr As String, iLen As Long, Optional iRem As Boolean ) As  String    '161200d Returns a Substring of iLen Characters from the Left-hand Side of iStr
Returns   Null  if iLen is      <0         Note: VB's Left() causes a RTE for Len<0
    "       iStr      "        >Len(iStr)
  Setting iRem returns the Remainder of iStr after removing the Default Return String
  egs    iStr   iLen    iRem    Return
       Null      x         x       Null
      abcde    2                 ab
      abcde    2      True    cde
      abcde    6               abcde
      abcde   -1      True   abcde

DTc > String > Substring wRight wRight ( iStr As String, iLen As Long, Optional iRem As Boolean ) As  String    '161200e Returns a Substring of iLen Characters from the Right-hand Side of iStr
Returns   Null  if iLen is      <0         Note: VB's Right() causes a RTE for Len<0
   "        iStr       "      >Len(iStr)
  Setting iRem returns the Remainder of iStr after removing the Default Return String
  egs    iStr   iLen    iRem    Return
        Null     x         x       Null
      abcde    2                 de
      abcde    2      True     abc
      abcde    6               abcde
      abcde   -1      True   abcde

DTc > String > Substring wMid wMid ( iStr As String, iStartPos As Long, iEndPos As Long ) As  String    '190824b Returns a Substring from iStr
Similar to VB's Mid() except that
  1) iEndPos determines the NO Chars returned, rather than Length
  2) If iStartPos or iEndPos is <=0, wMid Returns a Null String,
     whereas Mid() causes a RTE

DTc > String > Substringwe_SSC A String, or Delimited String's, Substring Components  Enumeration    `161100d DTc.wMidEx() we_sscNone
  we_sscL
we_sscLP
we_sscLD
  we_sscSS
  we_sscR
we_sscRD
we_sscRS
  we_sscAll
we_sscAXSS
we_sscLPaRS
we_sscSSaDs
 

    Left (Substring)
* Left-hand Prefix
* Left-hand Delimiter
    (Middle) Substring
    Right Substring
* Right-hand Delimiter
* Right-hand Suffix
 
  All Except Substring
* LP and RS (All Except Substring & Delimiters)
* Substring And Delimiters
  * Delimited Strings Only
DTc > String > Substring wMidEx wMidEx ( iStr As String, iOri As Long, iNOChars As Long, _
Optional iRev As Boolean, _
Optional iIncOs As we_SSC = we_sscSS, _
Optional oaExc As we_MidX ) As  String    '190824c
An Extended version of wMid
The Default Return is the same as VB's Mid(iStr,iOri,iNOChars)
  iOri is the Origin Character Position in iStr:
  In the default Forward Direction it is the same as VB Mid's start Parameter
        eg iOri=3 is the Third Character
  In the Reverse Direction (with iRev Set) it is the iOri'th Character,
    counting Left from the Last Character
        eg iOri=2 is the second-to-last Character
  iNOChars is the No. of Characters to be Returned counting
  Right from iOri if iRev is False    or
   Left           "             True
  If iRev is Set, the Return is StrRev(Mid(StrRev(iStr),iOri,iNOChars));
   the Returned string Ends at Len(iStr) - iOri + 1
  iIncOs may be used to Include Non-Default Substring combinations in the Return (see we_SSC)
    we_sscL        Includes the Substring to the Left  of the Default Return
  we_sscSS      Includes the Default Return
  we_sscR        Includes the Substring to the Right of the Default Return
  we_sscAXSS  Includes the Left & Right Substrings (All Except Substring)
  In All Cases, Concatenating the Left, Default and Right Substrings re-makes
   iStr; if an Exception occurs that returns a Null String, then iOri determines
   how iStr is split between the Left and Right Substrings (see last egs)
  oaExc is Zero unless an Exception occurs; see we_MidX
  egs  iStr iOri  iNOChars  iRev     iIncOs      oaExc       Return
                                             (we_ssc)   (we_mx)
      Null    x        x           x           x           Non-0          Null
     abcd    3        2           .            .              0              cd
     abcd    3        2        True          .              0              ab
     abcd    3        3           .            .             Ov             cd
     abcd    3        3        True          .             Ov             ab
     abcd    2        2           x            .              0              bc
     abcd    2        2           x           L              0               a
     abcd    3        2        True      SS + R          0            abcd
     abcd    3        2        True       AXSS           0              cd
     abcd    x        0           x          All          Non-0         abcd
     abcd    0        1           .           R             OL1          abcd
     abcd    2        0           .           R             NL1           bcd
     abcd    4        0        True         R             NL1           bcd
                             . = Default         x = Don't Care

DTc > String > Substring we_MidX wMidEx() Exceptions  Enumeration    `190824d wMidEx() we_mxNone
  we_mxOL1
we_mxOGL
  we_mxNL1
 
  we_mxOv


  * iOri <1Return=ZLS
  iOri > Len(iStr)  Return=ZLS
  * iNOChars < 1  Return=ZLS
  * Mid() causes a RTE in these cases
    Overflow, when iOri + iNOChars > Len(iStr)
  In this case Len(iStr) - iOri + 1 Characters are Returned
DTc > String > Substring wMidOK wMidOK ( iStr As String, iOri As Long, iNOChars As Long, _
Optional oaSS As String, Optional oaExc As we_MidX, _
Optional iRev As Boolean, _
Optional iIncOs As we_SSC = we_sscSS ) As  Boolean    '190824e
The same as wMidEx(), but in a format suitable for Conditional Testing
DTc > String > Substring FindSS FindSS ( iSS As String, ByVal ivInStr As String, _
Optional ocLeftStr As String, Optional ocRightStr As String, _
Optional ocFouAtPos As Long, Optional iRev As Boolean, _
Optional ByVal ivOri As Long = 1, _
Optional iComp As VbCompareMethod = vbTextCompare, _
Optional iPresOsOnFail As Boolean ) As  Boolean    '180626a
If ivInStr contains iSS, Succeeds and Splits ivInStr into ocLeftStr and ocRightStr
The Split is made at ocFouAtPos, which is the Position of the First
  (or the Last) Occurance of iSS in ivInStr, (depending on iRev)
  iSS IS NOT INCLUDED in either ocLeftStr or ocRightStr       (see NOTE 2)
  If Successful, ocFouAtPos will be between 1 and Len(ivInStr),
On Failure,   ocFouAtPos is set to 0, unless iPresOsOnFail is Set
                                                                                   (see NOTE 1)
  If iRev is   False   ivInStr is searched from   Left to Right
     "       True                  "                    Right to Left
  If ivOri is                                                                       (see NOTE 1)
       =1           then   All of ivInStr is searched (the Default)
    >1 And        then   the Search Starts at that Position
<=Len(InStr)                   Relative to either;
                             the   Start   of ivInStr, if iRev is   False,
                     or      "      End              "                   True
      <1 Or        then   FindSS Fails
 >Len(InStr)
    The Default iComp = vbTextCompare   = 1   IS NOT CASE SENSITIVE,
   Setting    iComp = vbBinaryCompare = 0   makes FindSS Case Sensitive
  On Failure Outputs are Cleared by Default, or Unmodified if
  iPresOsOnFail is Seton
  Succeeds if iSS is NULL (unless ivOri causes it to Fail) and in this case
     ocFouAtPos = ivOri                                                   (see NOTE 2)
  Fails if ivInStr is NULL
  NOTE 1   ivOri        is   relative to one End of ivInStr (depending on iRev)
   but ocFouAtPos   is   always relative to the Start of ivInStr
  NOTE 2   FindSS can be used to Split ivInStr AFTER ivOri,
            by Setting iSS to NULL
  egs
                              ----- iRev=False ----          ----- iRev=True -----
  iSS                      ocFouAtPos                  ocFouAtPos
          ivInStr                   ocLeftStr                       ocLeftStr
                       ivOri                  ocRightStr                     ocRightStr
  NULL     NULL      x         0                                  0
NULL     abcde     3         3      abc      de              3      ab      cde
 a        1234a      1         5     1234                      5    1234
 a        a2345      2         0        .                         1              2345
 a      a234a67     3         5     a234     67             5     a234    67
abc    123abc7     3         4      123       7              0       .
abc    123abc7     2         4      123       7              4     123      7
                                                   . = ivInStr

DTc > String > Substring FindDSS FindDSS ( iLDS As String, iInStr As String, iRDS As String, _
Optional ocSS As String, Optional ouStr2 As String, _
Optional iSS2IncOs As we_SSC = we_sscRS, _
Optional iRev As Boolean, Optional ByVal ivOri As Long = 1, _
Optional ocFCPos As Long, Optional ocLCPos As Long, _
Optional iComp As VbCompareMethod = vbTextCompare, _
Optional oaSSIsNull As Boolean ) As  Boolean    '170106a
Finds the first Substring in iInStr Delimited by Left and Right Delimiting Strings, iLDS & iRDS
 If     iInStr contains Both iLDS & iRDS
And    a Substring (including the Null String) exists Between them
then   FindDSS Succeeds and sets ocSS to the Left-Most such
           Substring                                                             [NOTE 1]
  Setting iLDS to the Null String is Valid and has a "Wildcard" effect;
 ocSS is then set to the LHS of iInStr, up to (but not including)
 the First Character of iRDS. Similarly;                                      [eg2]
Setting iRDS to the Null String returns the RHS of iInStr, after the
  Last Character of iLDS                                                          [eg3]
EXCEPTION: If BOTH iLDS and IRDS are Null, FindDSS Succeeds and Returns iInStr   [eg4]
  A Second Output String, ouStr2, is also returned and it's value
  determined by setting iSS2IncOs to any combination of the
  Component Substrings defined in Enum we_SSC                        [eg9]
  Refer to the the FindSS Function for a description of the functions of iRev, ivOri & iComp
  ocFCPos & ocLCPos are the Positions of the First & Last Characters
  of ocSS in iInStr                                                          [NOTE 2]
  oaSSIsNull is Set whenever ocSS is Null
  egs FindDSS Fails, or [eg10] iInStr = iLDS & iRDS                             [NOTE 2]
  NOTE 1     If iInStr itself is Null, FindDSS Fails                          [eg1]
NOTE 2     If FindDSS Succeeds   And   ocSS is Null,
                then ocLCPos=ocFCPos-1                                     [eg10]
  egs  iLDS      iInStr  iRDS Return    ocSS     Non-Defaults/Variations
  1     Null       Null         Null    Fail    Null
2      Null           abc            c      Suc     ab
3      A           abc            Null      Suc     bc
4      Null             abc           Null    Suc    abc
5      B      ABCDabcd      B      Suc    CDa
6      B      ABCDabcd      B      Fail     Null    iComp=vbBinaryCompare
7      A      ABCDabcd      D      Suc     bc      iRev=True
8      A      ABCDabcd      D      Suc     BC      iRev=True &
                                                                  iComp=vbBinaryCompare
9      A      ABCDabcd      C      Suc     B       default iSS2IncOs=we_ssRS
                                                                 returns ouStr2=Dabcd
10  ABCD   ABCDabcd    abcd    Suc    Null      oaSSIsNull=True,
                                                                  ocFCPos=5 & ocLCPos=4

DTc > String > Substring TrimBufStr TrimBufStr ( iStr As String ) As  String    '170109b Returns the Substring to the Left of the First Null Character in iStr
DTc > String > Substring FirLineOfStr FirLineOfStr ( ByVal ivStr As String ) As  String    '170109a Returns ivStr up to it's First Carriage Return or Line Feed Character,
  Ignoring and Excluding Leading CR and LF Characters

DTc > String > Substring CouSSs CouSSs ( iSS As String, iInStr As String, _
Optional iComp As VbCompareMethod = vbTextCompare ) As  Long    '170112a
Returns the No. of Occurances of iSS in iInStr
Returns -1 if iSS or iInstr is Null
  The Default   iComp = vbTextCompare   = 1     IS NOT CASE SENSITIVE,
     Setting     iComp = vbBinaryCompare = 0   makes CouSSs Case Sensitive

DTc > String > Substring StrHasAnySS StrHasAnySS ( iSSs As String, iDStr As String, iInStr As String, _
Optional oSS As String, Optional ocPos As Long ) As  Boolean    '170110a
If Successful, sets oSS to the First Substring from iSSs (Delimited by iDStr)
found in iInStr, and sets ocPos to iSSs Position in iInStr
Fails if iSSs, iDStr or iInStr is Null, or if iSSs and iDStr are the Same

DTc > String > Substring SplDStr SplDStr ( ByVal ivStr As String, ByVal ivDStr As String, oaStrA() As String, _
Optional iPresDS As Boolean, Optional iIgnDSReps As Boolean, _
Optional ByVal ivCopyToOriCe As Range = Nothing ) As  Long    '170111a
Splits ivStr into an Array of Substrings, and Returns a Count of these Substrings
ivDStr Delimits the Substrings in ivStr and is is dropped from each
  Substring, unless iPresDS is Seton
  oaStrA is ReDim'd to a 0-Based Array, with
  LBound(oaStrA) =   0          and
  UBound(oaStrA) = Ret-1,   where Ret = SplDStr's Return
  egs ivStr=""                 with ivDStr= *      Returns 0
      ivStr="123"            with ivDStr= ""      Returns a 1 Entry Array: 123
      ivStr="1,22,,4444"   with ivDStr= ","     Returns a 4 Entry Array:
                                                               1  22  Null  4444
  Setting iPresDS Preserves the ivDStr; each oaStrA Entry, except the Last,
  will end with ivDStr
  Setting iIgnDSReps causes Consecutive Delimiters to be Ignored.
  The example above would then Return a 3 Entry Array: 1 22 4444
  If ivCopyToOriCe is specified, oaStrA is copied that Row, starting in
  ivCopyToOriCe

DTc > String > Modify wTrim wTrim ( iFromStr As String, Optional iTrimStr As String = " ", Optional iLorROnly As String = "" ) As  String    '170111c Returns a copy of iFromStr with all Leading and/or Trailing iTrimStr's Removed
iTrimStr defaults to a Space; " "
  Setting iLorROnly to "L" or "R" causes Only Leading or Only Trailing iTrimStrs Only to be Removed respectively
  iTrimStr will generally be a Single Character; wTrim works with longer strings,
  but only entire iTrimStr's are Removed
     eg  wTrim("aaaBBaa","aa") returns "aBB"

DTc > String > Modify TrimWSp TrimWSp ( ByVal ivStr As String, Optional iLorROnly As String = "" ) As  String    '170112c Returns ivStr with Whitespace Characters Trimmed from it
Setting iLorROnly to "L" or "R" causes Only Leading or Only Trailing Whitespace Only to be Removed respectively

DTc > String > Modify TrimArt TrimArt ( iStr As String, _
Optional iArtSuf As String, Optional ocArt As String ) As  String    '190824f
Returns iStr, Trimmed of any Leading Article "a" or "the" (in any Case)
Returns any such Article, Suffixed with iArtSuf, as ocArt
  Capitalization is Unchanged and, in the Default case, the Space between ocArt and iStr is lost
              egs     iStr        iArtSuf       ocArt       Return
                 "a Word"        ""           "a"          "Word"
                "An Idea"       "x"           "x"         "An Idea"
               "THE Time"      " "         "THE "       "Time"

DTc > String > Modify wPad wPad ( iStr As String, iPadStr As String, ByVal ivNOCopies As Long, iLorR As String ) As  String    '170112d Returns ivNOCopies of iPadStr added to the Left or Right of iStr
Setting iLorR to "L" or "R" adds Copies to the Left or Right Side respectively
  egs   wPad(Null,"a",2,"left") -> "aa"
       wPad("a","bcd",1,"R") -> "abcd"

DTc > String > Modify wReplace wReplace ( iFindStr As String, iRepWStr As String, iInStr As String, _
Optional iStartRepsPos As Long = 1, Optional iCou As Long = -1, Optional iComp As VbCompareMethod = vbTextCompare ) As  String    '170113m
Similar to VB Replace() except that;
    1) the Parameter Names and Order are Different
    2) iStartRepsPos<1 Or iCou<-1 Return iInStr, rather than causing a RTE
          eg  wReplace("c","3","abc",-1,-2) Returns "abc"         whereas
                 Replace("abc","c","3",-1,-2) causes RTE 5
    3) if iStartRepsPos>1, Character's in Positions <iStartRepsPos are simply
      not Replaced, rather than being Trimmed
          eg  wReplace("c","3","abc",2, 1) Returns "cb3"            whereas
                 Replace("abc","c","3",2, 1) Returns "b3"
  Note that if iFindStr is Null, wReplace and VB Replace both Return iInStr
  (subject to 2) and 3) above)
     eg  wReplace("","3","abc")               and
            Replace("","3","abc")       both Return "abc"

DTc > String > Modify RepStrs RepStrs ( ByVal ivFindStrs As String, ByVal ivRepWStrs As String, _
ByVal ivDStr As String, iInStr As String, _
Optional iComp As VbCompareMethod = vbTextCompare ) As  String    '170113g
Uses wReplace to Return iInStr with each substring from ivFindStrs Replaced with the Respective Substring from iRepWStr
ivDStr Delimits the Substrings in ivFindStrs and ivRepWStrs
  If ivRepStrs has Fewer Substrings than ivFindStrs, the Last ivRepStr
  Substring is used for ivFindStrs that don't have a
  corresponding ivRetStr value
  eg  iFind="a,b,c"  iRep="x,*"  ivDStr=","  iInstr=  "1A3B5C7"
                                                          Returns  "1x3*5*7"
                                                          with Default iComp

DTc > String > Modify CapSen CapSen ( iSen As String, Optional ByVal ivXPoss As String ) As  String    '170113b Returns a Copy of iSen with the First Letter, and the First Letter of Every Word, Capitalized
ivXPoss is a Comma-Separated String of Exception Positions in iSen for which this Logic is Inverted;
  ie     Position 1       Is Not   Capitalized
       First-Letters   Are Not       "
       Other Letters     Are         "
  ivXPoss must be in Ascending Order, values >Len(iSen) have no affect
    eg   iSen="ie mr mcgee", ivXPoss="1,9" Returns "ie Mr McGee"

DTc > String > Modify PrepSpasToCaps PrepSpasToCaps ( iStr As String, Optional ByVal ivXPoss As String ) As  String    '170113f Returns a String with a Space Prepended before Every Capital Letter in iStr, except iStr's First Character
ivXPoss is a Comma-Separated String of Exception Positions in iStr, for which;
    If the Exception Position=1, a Space IS Prepended to the First Character
     (regardless of it's Type)
    If the Character at the Exception Position;
       IS      a Capital, a Space   IS NOT   Prepended to it
    IS NOT               "                 IS                 "

DTc > String > Specialized NegBStr NegBStr ( iStr As String ) As  String    '170113e Returns a Logically Negated copy of a (Binary) String iStr, replacing all 1's with 0's and vice versa
Leading 0's are Preserved
Other Characters are Unchanged
    eg   NegBStr("01a0")  Returns  "00a1"

DTc > String > Specialized BNibExDig BNibExDig ( iDigChar As String, iOct As Boolean ) As  String    '170113a Returns any Valid Hex or Octal Digit (iDigChar) as a Binary String (or Nibble)
Other Values Return Null
  If iOct is   False   iDigChar may be any   Hex Digit (0-9, A-E or a-e)
      "        True                  "               Octal Digit     (0-7)
  If iOct is   False   the Return is   4   Bits long
      "        True          "            3        "
  If Len(iDigChar)>1 BNibExDig uses it's First Character
    egs BNibExDig("e")        Returns   "1110"
                    ("71",True)     "       "111"
                    ("8",True)       "        Null

DTc > String > Specialized SwapFir2Nums SwapFir2Nums ( iStr As String, Optional oaStr As String ) As  Boolean    '170113k If Successful, sets oaStr to iStr with the First and Second Numbers, as delimited by Non-Digit(s), Swapped
This function is intended for dd-mm <-> mm-dd Date Data Type Conversions
  iStr's First Character must be Numeric
The Numbers must be delimited by a Single Non-Numerical Character
Otherwise Fails & Returns iStr if this is not possible
   egs   "31-1"   returns   "1-31"
      "1/31/12" returns "31/1/12"
      "a31-1",  "31--1" and  "31st March"   all Fail

DTc > String > Specialized IsValBaseChar IsValBaseChar ( iChar As String, iBase As Long, _
Optional oNum As Long, Optional oaExcN As Long ) As  Boolean    '170113c
If Successful, sets oNum to iChar's Numerical Value in iBase
On Failure, Returns a Non-0 Exception No. (oaExcN)
  Exceptions 1 = iChar isn't a Single Char
          2 = iBase  is <2 Or >36
          3 = iChar is Invalid in Any iBase
          4 = iChar is Invalid in iBase
  egs "1",10 -> 1,   "a",16 -> 10,   "E",16 -> 15,   "z",36 -> 35

DTc > String > Specialized RGBToHexStr RGBToHexStr ( iColr As Variant, Optional iPre As String ) As  String    '191009a Pads an RGB Color value (iColr) out with 0's to a 6-Digit Hex String;
  two Hex Digits for each Primary Color, in BGR Order Left to Right
  Returns a Null String if iColr is not a Valid Color Value
  iPre may also be specified as a Prefix for the Returned String
  egs    Red         256  ->  &H0000FF    (with iPre="&H")
      Blue   16711680  ->  &HFF0000
      Yellow    65535  ->  &H00FFFF

DTc > Time & Date > wTimeStr wTimeStr ( Optional ByVal ivSecs As Double = -1#, Optional iRouMs As Boolean, _
Optional oaDays As Long ) As  String    '170114b
Returns a Seconds Value, ivSecs, as a String of Format hh:mm:ss.mmm
mmm is the Millisecond Component of ivSecs
  If ivSecs is Not Specified, or is Negative,
  wTimeStr Returns the Current Time Of Day (since Midnight)
  This is the same as wTimeStr(Timer)
  If iRouMs is Set, the Return is Rounded to the nearest Second and Formatted hh:mm:ss
  wTimeStr Always returns a 12 or 8 Character String; values of >= 24 Hours Wrap back to <24 Hours
      egs 86,399.499 -> "23:59:59.499"   with oaDays =0   if iRouMs is Reset
          86,399.499 -> "23:59:59"       with oaDays =0   if iRouMs is Set
          86,400.501 -> "00:00:01"       with oaDays =1   if iRouMs is Set

DTc > Array > ArrBou ArrBou ( iArr As Variant, Optional iDim As Variant = 1, Optional iLBou As Boolean ) As  Long    '190824g Returns the (iDim'th) Upper or Lower Dimension of iArr
Similar to VB's UBound() and LBound(), except that these cause a RTE for
  Invalid Inputs*, whereas ArrBou Returns 0 in these cases
  *Invalid Inputs are;
  iArr is Not an Array
  iArr has UBound < LBound
  iArr has <iDims
  iDim Defaults to 1
  Returns  UBound  if iLBou is   Reset  [Default]
     "       LBound          "        SetOn

DTc > Array > we_ArrT Array Types  Enumeration    `161100e > ArrIsAllocd() we_atNone
  we_atStatic
  we_atDyn
we_atUnaDyn
we_atAllDyn

 
 
Unalloc'd Dynamic
Alloc'd Dynamic
DTc > Array > ArrIsAllocd ArrIsAllocd ( iArr As Variant, Optional oaIsArr As Boolean ) As  Boolean    '170114a Succeeds if the Array iArr is an Array, and has been Allocated
oaIsArr is Set if iArr is an Array
  Note that Static Arrays are always Allocated
  refer to http://www.cpearson.com/excel/ArrIsAllocd.aspx

DTc > Variant > IsSameObj IsSameObj ( iO1 As Variant, iO2 As Variant ) As  Boolean    '191005a Succeeds if iO1 and iO2 refer to the Same Object
iO1 and iO2 must literally refer to the Same Object; NOT simply
  be of the Same Object Type and/or Identical Instances
  egs   iO1                 iO2                     Return
        Empty               Empty                   False
      Nothing             Nothing                 True
        Set Ra1=ActiveCell  Set Ra2=ActiveCell      False
      Set Ra1=ActiveCell  Set Ra2=Ra1             True
        ActiveCell.Parent   Activecell.Worksheet    True