! ! $Header$ ! SUBROUTINE laplacien_rot ( klevel, rotin, rotout,ghx,ghy ) ! ! P. Le Van ! ! ************************************************************ ! ... calcul de ( rotat x nxgrad ) du rotationnel rotin . ! ************************************************************ ! ! klevel et rotin sont des arguments d'entree pour le s-prog ! rotout est un argument de sortie pour le s-prog ! USE dimensions_mod, ONLY: iim, jjm, llm, ndm USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, & ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm IMPLICIT NONE ! INCLUDE "comgeom.h" ! ! .......... variables en arguments ............. ! INTEGER :: klevel REAL :: rotin( ip1jm,klevel ), rotout( ip1jm,klevel ) ! ! .......... variables locales ................ ! REAL :: ghy(ip1jm,klevel), ghx(ip1jmp1,klevel) ! ........................................................ ! ! CALL filtreg ( rotin , jjm, klevel, 2, 1, .FALSE., 1 ) CALL nxgrad ( klevel, rotin, ghx , ghy ) CALL rotatf ( klevel, ghx , ghy , rotout ) ! RETURN END SUBROUTINE laplacien_rot