Objet WorksheetFunction (Excel)
Cet objet est utilisé comme conteneur des fonctions de feuille de calcul Microsoft Excel que vous pouvez appeler à partir de Visual Basic pour Applications.
Exemple
Utilisez la propriété WorksheetFunction de l’objet Application pour renvoyer l’objet WorksheetFunction.
Cet exemple montre comment afficher le résultat obtenu après application de la fonction de feuille de calcul Min à la plage A1:C10.
Set myRange = Worksheets("Sheet1").Range("A1:C10")
answer = Application.WorksheetFunction.Min(myRange)
MsgBox answer
Cet exemple utilise la fonction de feuille de calcul CountA pour déterminer combien de cellules de la colonne A contiennent une valeur. Pour cet exemple, les valeurs dans la colonne A doivent être sous forme de texte. Cet exemple fait une vérification orthographique sur chaque valeur dans la colonne A et si la valeur est mal orthographié, insère le texte « Incorrecte » dans la colonne B ; dans le cas contraire, il insère le texte « OK » dans la colonne B.
Sub StartSpelling()
'Set up your variables
Dim iRow As Integer
'And define your error handling routine.
On Error GoTo ERRORHANDLER
'Go through all the cells in column A, and perform a spellcheck on the value.
'If the value is spelled incorrectly, write "Wrong" in column B; otherwise, write "OK".
For iRow = 1 To WorksheetFunction.CountA(Columns(1))
If Application.CheckSpelling( _
Cells(iRow, 1).Value, , True) = False Then
Cells(iRow, 2).Value = "Wrong"
Else
Cells(iRow, 2).Value = "OK"
End If
Next iRow
Exit Sub
'Error handling routine.
ERRORHANDLER:
MsgBox "The spell check feature is not installed!"
End Sub
Méthodes
- AccrInt
- AccrIntM
- Acos
- Acosh
- Acot
- Acoth
- Aggregate
- AmorDegrc
- AmorLinc
- And
- Arabic
- Asc
- Asin
- Asinh
- Atan2
- Atanh
- AveDev
- Average
- AverageIf
- AverageIfs
- BahtText
- Base
- BesselI
- BesselJ
- BesselK
- BesselY
- Beta_Dist
- Beta_Inv
- BetaDist
- BetaInv
- Bin2Dec
- Bin2Hex
- Bin2Oct
- Binom_Dist
- Binom_Dist_Range
- Binom_Inv
- BinomDist
- Bitand
- Bitlshift
- Bitor
- Bitrshift
- Bitxor
- Ceiling
- Ceiling_Math
- Ceiling_Precise
- ChiDist
- ChiInv
- ChiSq_Dist
- ChiSq_Dist_RT
- ChiSq_Inv
- ChiSq_Inv_RT
- ChiSq_Test
- ChiTest
- Choose
- Clean
- Combin
- Combina
- Complex
- Confidence
- Confidence_Norm
- Confidence_T
- Convert
- Correl
- Cosh
- Cot
- Coth
- Count
- CountA
- CountBlank
- CountIf
- CountIfs
- CoupDayBs
- CoupDays
- CoupDaysNc
- CoupNcd
- CoupNum
- CoupPcd
- Covar
- Covariance_P
- Covariance_S
- CritBinom
- Csc
- Csch
- CumIPmt
- CumPrinc
- DAverage
- Jours
- Days360
- Db
- Dbcs
- DCount
- DCountA
- Ddb
- Dec2Bin
- Dec2Hex
- Dec2Oct
- Decimal
- Degrees
- Delta
- DevSq
- DGet
- Disc
- DMax
- DMin
- Dollar
- DollarDe
- DollarFr
- DProduct
- DStDev
- DStDevP
- DSum
- Durée
- DVar
- DVarP
- EDate
- Effect
- EncodeUrl
- EoMonth
- Erf
- Erf_Precise
- ErfC
- ErfC_Precise
- Even
- Expon_Dist
- ExponDist
- F_Dist
- F_Dist_RT
- F_Inv
- F_Inv_RT
- F_Test
- Fact
- FactDouble
- FDist
- FilterXML
- Chercher
- FindB
- FInv
- Fisher
- FisherInv
- Fixed
- Floor
- Floor_Math
- Floor_Precise
- Forecast
- Forecast_ETS
- Forecast_ETS_ConfInt
- Forecast_ETS_Seasonality
- Forecast_ETS_STAT
- Forecast_Linear
- Frequency
- FTest
- Fv
- FVSchedule
- Gamma
- Gamma_Dist
- Gamma_Inv
- GammaDist
- GammaInv
- GammaLn
- GammaLn_Precise
- Gauss
- Gcd
- GeoMean
- GeStep
- Growth
- HarMean
- Hex2Bin
- Hex2Dec
- Hex2Oct
- HLookup
- HypGeom_Dist
- HypGeomDist
- IfError
- IfNa
- ImAbs
- Imaginary
- ImArgument
- ImConjugate
- ImCos
- ImCosh
- ImCot
- ImCsc
- ImCsch
- ImDiv
- ImExp
- ImLn
- ImLog10
- ImLog2
- ImPower
- ImProduct
- ImReal
- ImSec
- ImSech
- ImSin
- ImSinh
- ImSqrt
- ImSub
- ImSum
- ImTan
- Index
- Intercept
- IntRate
- Ipmt
- Irr
- IsErr
- IsError
- IsEven
- IsFormula
- IsLogical
- IsNA
- IsNonText
- IsNumber
- ISO_Ceiling
- IsOdd
- IsoWeekNum
- Ispmt
- IsText
- Kurt
- Large
- Lcm
- LinEst
- Ln
- Log
- Log10
- LogEst
- LogInv
- LogNorm_Dist
- LogNorm_Inv
- LogNormDist
- Lookup
- Match
- Max
- MDeterm
- MDuration
- Median
- Min
- MInverse
- MIrr
- MMult
- Mode
- Mode_Mult
- Mode_Sngl
- MRound
- MultiNomial
- Munit
- NegBinom_Dist
- NegBinomDist
- NetworkDays
- NetworkDays_Intl
- Nominal
- Norm_Dist
- Norm_Inv
- Norm_S_Dist
- Norm_S_Inv
- NormDist
- NormInv
- NormSDist
- NormSInv
- NPer
- Npv
- NumberValue
- Oct2Bin
- Oct2Dec
- Oct2Hex
- Odd
- OddFPrice
- OddFYield
- OddLPrice
- OddLYield
- Or
- PDuration
- Pearson
- Percentile
- Percentile_Exc
- Percentile_Inc
- PercentRank
- PercentRank_Exc
- PercentRank_Inc
- Permut
- Permutationa
- Phi
- Phonetic
- Pi
- Pmt
- Poisson
- Poisson_Dist
- Puissance
- Ppmt
- Price
- PriceDisc
- PriceMat
- Prob
- Produit
- Proper
- Pv
- Quartile
- Quartile_Exc
- Quartile_Inc
- Quotient
- Radians
- RandBetween
- Rank
- Rank_Avg
- Rank_Eq
- Rate
- Received
- Replace
- ReplaceB
- Rept
- Roman
- Round
- RoundDown
- RoundUp
- Rri
- RSq
- RTD
- Recherche
- SearchB
- Sec
- Sech
- SeriesSum
- Sinh
- Skew
- Skew_p
- Sln
- Slope
- Small
- SqrtPi
- Standardize
- StDev
- StDev_P
- StDev_S
- StDevP
- StEyx
- Substitute
- Subtotal
- Sum
- SumIf
- SumIfs
- SumProduct
- SumSq
- SumX2MY2
- SumX2PY2
- SumXMY2
- Syd
- T_Dist
- T_Dist_2T
- T_Dist_RT
- T_Inv
- T_Inv_2T
- T_Test
- Tanh
- TBillEq
- TBillPrice
- TBillYield
- TDist
- Text
- TInv
- Transpose
- Trend
- Trim
- TrimMean
- TTest
- Unichar
- Unicode
- USDollar
- Var
- Var_P
- Var_S
- VarP
- Vdb
- VLookup
- WebService
- Weekday
- WeekNum
- Weibull
- Weibull_Dist
- WorkDay
- WorkDay_Intl
- Xirr
- Xnpv
- Xor
- YearFrac
- YieldDisc
- YieldMat
- Z_Test
- ZTest
Propriétés
Voir aussi
- Utiliser une fonction de feuille de calcul dans une macro Visual Basic dans Excel
- Référence du modèle objet Excel
Assistance et commentaires
Avez-vous des questions ou des commentaires sur Office VBA ou sur cette documentation ? Consultez la rubrique concernant l’assistance pour Office VBA et l’envoi de commentaires afin d’obtenir des instructions pour recevoir une assistance et envoyer vos commentaires.