!copyright (C) 2001  MSC-RPN COMM  %%%RPNPHY%%%
*** S/P PRELIM1
*

      SUBROUTINE PRELIM1 ( T, U, V, HU, PS, 1
     1                    VMOD, VDIR, TVA, RHOA,
     1                    N )
#include "impnone.cdk"
*
      INTEGER N 
      REAL U(N), V(N), HU(N), PS(N)
      REAL T(N)
      REAL VMOD(N), VDIR(N), TVA(N), RHOA(N)
*
*Author
*          S. Belair (January 1997)
*Revisions
* 001      S. Belair (Feb 1999)
*             variables CV, RGL, and GAMMA are now in the bus of
*             permanent variables
* 002      S. Belair (March 1999)
*             remove calculations for the soil characteristics
*             (wsat, wwilt, ...).  Put in the new subroutine
*             INISOILI.
* 003      S. Belair (March 1999)
*             remove the filling of the surface temperature varibles
*             at KOUNT=0
* 004      S. Belair (January 2000)
*             impose a minimum wind of 0.5 m/s
*
*Object
*          Preliminary calculations for ISBA
*
*Arguments
*
*          - Input -
* T        low-level temperature
* U,V      horizontal low-level winds
* HU       low-level specific humidity
* PS       surface pressure
*
*          - Output -
* VMOD     module of the low-level wind
* VDIR     direction of the low-level wind
* TVA      lowest level virtual temperature
* RHOA     air density at the lowest level
*
*
#include "consphy.cdk"
*
      INTEGER I
*
#include "dintern.cdk"
#include "fintern.cdk"
*
*
*
*
*
*                         Wind module and direction
*
      DO I=1,N
        VMOD(I) = SQRT( U(I)*U(I) + V(I)*V(I)  )
        VMOD(I) = MAX( VMOD(I), 2.5 )
*
        IF (U(I).GE.0.0.AND.V(I).GE.0.0)
     1           VDIR(I) = ATAN( V(I) / ( U(I)+1.E-6 )  )
        IF (U(I).GE.0.0.AND.V(I).LT.0.0)
     1           VDIR(I) = ATAN( V(I) / ( U(I)+1.E-6 )  )
     1                   + 2.*PI
        IF (U(I).LT.0.0 )
     1           VDIR(I) = ATAN( V(I) / ( U(I)+1.E-6 )  )
     1                   + PI
      END DO
*
*
*
*                        Air density at the lowest level
*
      DO I=1,N
        TVA(I)  = FOTVT( T(I), HU(I) )
        RHOA(I) = PS(I) / ( RGASD*TVA(I) )
      END DO
*
*
*
*
      RETURN
      END