!copyright (C) 2001  MSC-RPN COMM  %%%RPNPHY%%%
***S/R MHUAES  -  PASSAGE DE HU A ES
*
#include "phy_macros_f.h"

      SUBROUTINE MHUAES(ES,HU,TX,PX,LNPS,MODP,SWTT,SWPH, 2,3
     $                  NI,NK,N)
*
#include "impnone.cdk"
*
      INTEGER NI, NK, N, MODP
      REAL ES(NI,NK), HU(NI,NK), TX(NI,NK)
      REAL PX(NK), LNPS(NI,*)
      REAL TEMP1
      LOGICAL SWTT, SWPR, SWPH
*
*Author
*          N. Brunet  (Jan91)
*
*Revision
* 001      B. Bilodeau  (August 1991)- Adaptation to UNIX
* 002      B. Bilodeau (January 2001) - Automatic arrays
* 003      B. Bilodeau (September 2003) - IBM conversion
*                       - call to vslog from massvp4 library
*
*Object
*          to calculate the dew point depression from specific
*          humidity, temperature and pressure
*
*Arguments
*
*          - Output -
* ES       dew point depressions in degrees Celsius
*
*          - Input -
* HU       specific humidity in kg/kg
* TX       temperature or virtual temperature in Kelvins
* PX       see MODP
* LNPS     see MODP
* MODP     pressure mode (SI units only):
*          =0; pressure level in PX
*          =1; sigma level in PX and PS(surface pressure) in LNPS
*          =2; sigma level in PX and logarithm of sigma level in
*          LNPS
*          =3; all points of pressure in LNPS(NI,*) in Pascals
*          =4; sigma level in PX and logarithm of sigma level in
*          LNPS(in millibars unless using SI units)
*          =5; logarithm of pressure level in PX(in millibars unless
*          using SI units)
* SWTT     .TRUE. to pass TT for argument
*          .FALSE. to pass TV for argument
* SWPH     .TRUE. to consider water and ice phase
*          .FALSE. to consider water phase only
* NI       horizontal dimension
* NK       vertical dimension
* N        number of treated points
*
*Notes
*          If HU <= 0, the value of HU is not changed but the
*          function MAX(HU,0.0000000001) will prevent the log
*          of a negative number.
*
*
*IMPLICITES
#include "consphy.cdk"
*MODULES
      EXTERNAL INCTPHY
*
**
*--------------------------------------------------------------------
************************************************************************
*     AUTOMATIC ARRAYS
************************************************************************
*
      AUTOMATIC ( PN , REAL , (N) )
      AUTOMATIC ( TP , REAL , (N) )
      AUTOMATIC ( CTE, REAL , (N) )
*
************************************************************************
*
      REAL TD, PETIT
      INTEGER  K, I
*
#include "dintern.cdk"
#include "fintern.cdk"
*--------------------------------------------------------------------
#include "initcph.cdk"
*
*
      PETIT = 0.0000000001
*
      DO 10 K=1,NK
*
#include "modpr2.cdk"
*
         IF(SWTT)THEN
            DO 100 I=1,N
               TP(I) = TX(I,K)
100         CONTINUE
         ELSE
            DO 110 I=1,N
               TP(I) = FOTTV(TX(I,K), HU(I,K))
110         CONTINUE
         END IF
*
         DO I=1,N
            TEMP1  = PN(I)
            CTE(I)   = (FOEFQ(MAX(PETIT,HU(I,K)), TEMP1))/610.78
         END DO
*
         CALL VSLOG(CTE,CTE,N)
*
         DO I=1,N
            TD = (35.86*CTE(I) - 17.269*TRPL)/(CTE(I) - 17.269)
*
            IF(TD.LT.TRPL.AND.SWPH)
     $         TD = (7.66*CTE(I) - 21.875*TRPL)/(CTE(I) - 21.875)
*
            ES(I,K) = TP(I) - TD
*
         END DO
*
10    CONTINUE
*
*
      RETURN
      END