source: codes/icosagcm/devel/src/dynamics/compute_caldyn.f90 @ 1050

Last change on this file since 1050 was 1034, checked in by dubos, 4 years ago

devel : work around PGI compiler complaints (bugs ?)

File size: 3.6 KB
Line 
1MODULE compute_caldyn_mod
2  USE prec, ONLY : rstd
3  IMPLICIT NONE
4 
5  ! fake array dimensions, for interfaces
6  INTEGER, PARAMETER :: iim_jjm_i=1, iim_jjm_u=1, iim_jjm_v =1, llm_=1, llm1=1, nqdyn_=1
7
8  INTERFACE
9     
10    SUBROUTINE comp_pvort_only(u,rhodz,qu,qv, hv)
11      IMPORT
12      REAL(rstd), INTENT(IN)    :: u(:,:)
13      REAL(rstd), INTENT(INOUT) :: rhodz(:,:)
14      REAL(rstd), INTENT(OUT)   :: qu(:,:)
15      REAL(rstd), INTENT(OUT)   :: qv(:,:)
16      REAL(rstd), INTENT(OUT)   :: hv(:,:)
17    END SUBROUTINE comp_pvort_only
18
19    SUBROUTINE comp_theta(mass_col,theta_rhodz, rhodz,theta)
20      IMPORT
21      REAL(rstd), INTENT(IN)    :: mass_col(:)
22      REAL(rstd), INTENT(IN)    :: theta_rhodz(:,:,:)
23      REAL(rstd), INTENT(INOUT) :: rhodz(:,:)
24      REAL(rstd), INTENT(OUT)   :: theta(:,:,:)
25    END SUBROUTINE comp_theta
26
27    SUBROUTINE comp_geopot(rhodz,theta, ps,pk,geopot) 
28      IMPORT
29      REAL(rstd), INTENT(IN)    :: rhodz(:,:)    ! rho*dz = mass per unit surface in each full model level
30      REAL(rstd), INTENT(IN)    :: theta(:,:,:)  ! active scalars : theta/entropy, moisture, ...
31      REAL(rstd), INTENT(INOUT) :: ps(:)         ! surface pressure
32      REAL(rstd), INTENT(OUT)   :: pk(:,:)       ! Exner function (compressible) /Lagrange multiplier (Boussinesq)
33      REAL(rstd), INTENT(INOUT) :: geopot(:,:)   ! geopotential
34    END SUBROUTINE comp_geopot
35
36    SUBROUTINE comp_caldyn_fast(tau,theta,geopot, pk,berni,du,u)
37      IMPORT
38      REAL(rstd), INTENT(IN)    :: tau           ! "solve" u-tau*du/dt = rhs
39      REAL(rstd), INTENT(IN)    :: theta(:,:,:)
40      REAL(rstd), INTENT(IN)    :: geopot(:,:)
41      REAL(rstd), INTENT(INOUT) :: pk(:,:)
42      REAL(rstd), INTENT(INOUT) :: berni(:,:)    ! partial Bernoulli function
43      REAL(rstd), INTENT(INOUT) :: du(:,:)
44      REAL(rstd), INTENT(INOUT) :: u(:,:)        ! INOUT if tau>0
45    END SUBROUTINE comp_caldyn_fast
46
47    SUBROUTINE comp_caldyn_slow_hydro(zero, u,rhodz,hv,Kv, berni, hflux,du)
48      IMPORT
49      LOGICAL,    INTENT(IN)    :: zero
50      REAL(rstd), INTENT(IN)    :: u(:,:)      ! prognostic "velocity"
51      REAL(rstd), INTENT(IN)    :: rhodz(:,:)
52      REAL(rstd), INTENT(IN)    :: hv(:,:)     ! height/mass averaged to vertices
53      REAL(rstd), INTENT(IN)    :: Kv(:,:)     ! kinetic energy at vertices
54      REAL(rstd), INTENT(OUT)   :: berni(:,:)  ! Bernoulli function
55      REAL(rstd), INTENT(OUT)   :: hflux(:,:)  ! hflux in kg/s
56      REAL(rstd), INTENT(INOUT) :: du(:,:)
57    END SUBROUTINE comp_caldyn_slow_hydro
58   
59    SUBROUTINE comp_caldyn_coriolis(hflux,theta,qu, Ftheta, convm,dtheta_rhodz,du)
60      IMPORT
61      REAL(rstd), INTENT(IN)    :: hflux(:,:)   ! hflux in kg/s
62      REAL(rstd), INTENT(IN)    :: theta(:,:,:) ! active scalars
63      REAL(rstd), INTENT(IN)    :: qu(:,:)
64      REAL(rstd), INTENT(OUT)   :: Ftheta(:,:)  ! potential temperature flux
65      REAL(rstd), INTENT(OUT)   :: convm(:,:)   ! mass flux convergence
66      REAL(rstd), INTENT(OUT)   :: dtheta_rhodz(:,:,:)
67      REAL(rstd), INTENT(INOUT) :: du(:,:)
68    END SUBROUTINE comp_caldyn_coriolis
69
70  END INTERFACE
71
72  PROCEDURE(comp_pvort_only),        POINTER, SAVE :: compute_pvort_only        => NULL()
73  PROCEDURE(comp_theta),             POINTER, SAVE :: compute_theta             => NULL()
74  PROCEDURE(comp_geopot),            POINTER, SAVE :: compute_geopot            => NULL()
75  PROCEDURE(comp_caldyn_fast),       POINTER, SAVE :: compute_caldyn_fast       => NULL()
76  PROCEDURE(comp_caldyn_slow_hydro), POINTER, SAVE :: compute_caldyn_slow_hydro => NULL()
77  PROCEDURE(comp_caldyn_coriolis),   POINTER, SAVE :: compute_caldyn_coriolis   => NULL()
78
79END MODULE compute_caldyn_mod
Note: See TracBrowser for help on using the repository browser.