Ignore:
Timestamp:
05/18/20 21:07:49 (4 years ago)
Author:
dubos
Message:

devel : towards conformity to F2008 standard

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/dynamics/compute_caldyn.f90

    r938 r1027  
    1111    SUBROUTINE comp_pvort_only(u,rhodz,qu,qv, hv) 
    1212      IMPORT 
    13       REAL(rstd),INTENT(IN)  :: u(iim_jjm_i, llm_) 
    14       REAL(rstd),INTENT(INOUT) :: rhodz(iim_jjm_i, llm_) 
    15       REAL(rstd),INTENT(OUT) :: qu(iim_jjm_u, llm_) 
    16       REAL(rstd),INTENT(OUT) :: qv(iim_jjm_v, llm_) 
    17       REAL(rstd),INTENT(OUT) :: hv(iim_jjm_v, llm_) 
     13      REAL(rstd), INTENT(IN)    :: u(:,:) 
     14      REAL(rstd), INTENT(INOUT) :: rhodz(:,:) 
     15      REAL(rstd), INTENT(OUT)   :: qu(:,:) 
     16      REAL(rstd), INTENT(OUT)   :: qv(:,:) 
     17      REAL(rstd), INTENT(OUT)   :: hv(:,:) 
    1818    END SUBROUTINE comp_pvort_only 
    1919 
    2020    SUBROUTINE comp_theta(mass_col,theta_rhodz, rhodz,theta) 
    2121      IMPORT 
    22       REAL(rstd),INTENT(IN)    :: mass_col(iim_jjm_i) 
    23       REAL(rstd),INTENT(IN)    :: theta_rhodz(iim_jjm_i, llm_, nqdyn_) 
    24       REAL(rstd),INTENT(INOUT) :: rhodz(iim_jjm_i, llm_) 
    25       REAL(rstd),INTENT(OUT)   :: theta(iim_jjm_i, llm_, nqdyn_) 
     22      REAL(rstd), INTENT(IN)    :: mass_col(:) 
     23      REAL(rstd), INTENT(IN)    :: theta_rhodz(:,:,:) 
     24      REAL(rstd), INTENT(INOUT) :: rhodz(:,:) 
     25      REAL(rstd), INTENT(OUT)   :: theta(:,:,:) 
    2626    END SUBROUTINE comp_theta 
    2727 
    2828    SUBROUTINE comp_geopot(rhodz,theta, ps,pk,geopot)  
    2929      IMPORT 
    30       REAL(rstd),INTENT(IN)    :: rhodz(iim_jjm_i, llm_)         ! rho*dz = mass per unit surface in each full model level 
    31       REAL(rstd),INTENT(IN)    :: theta(iim_jjm_i, llm_, nqdyn_) ! active scalars : theta/entropy, moisture, ... 
    32       REAL(rstd),INTENT(INOUT) :: ps(iim_jjm_i)                  ! surface pressure 
    33       REAL(rstd),INTENT(OUT)   :: pk(iim_jjm_i, llm_)            ! Exner function (compressible) /Lagrange multiplier (Boussinesq) 
    34       REAL(rstd),INTENT(INOUT) :: geopot(iim_jjm_i, llm1)        ! geopotential 
     30      REAL(rstd), INTENT(IN)    :: rhodz(:,:)    ! rho*dz = mass per unit surface in each full model level 
     31      REAL(rstd), INTENT(IN)    :: theta(:,:,:) ! active scalars : theta/entropy, moisture, ... 
     32      REAL(rstd), INTENT(INOUT) :: ps(:)         ! surface pressure 
     33      REAL(rstd), INTENT(OUT)   :: pk(:,:)       ! Exner function (compressible) /Lagrange multiplier (Boussinesq) 
     34      REAL(rstd), INTENT(INOUT) :: geopot(:,:)   ! geopotential 
    3535    END SUBROUTINE comp_geopot 
    3636 
    3737    SUBROUTINE comp_caldyn_fast(tau,theta,geopot, pk,berni,du,u) 
    3838      IMPORT 
    39       REAL(rstd),INTENT(IN)    :: tau                ! "solve" u-tau*du/dt = rhs 
    40       REAL(rstd),INTENT(IN)    :: theta(iim_jjm_i, llm_, nqdyn_) 
    41       REAL(rstd),INTENT(IN)    :: geopot(iim_jjm_i, llm1) 
    42       REAL(rstd),INTENT(INOUT) :: pk(iim_jjm_i, llm_) 
    43       REAL(rstd),INTENT(INOUT) :: berni(iim_jjm_i, llm_)  ! partial Bernoulli function 
    44       REAL(rstd),INTENT(INOUT) :: du(iim_jjm_u, llm_) 
    45       REAL(rstd),INTENT(INOUT) :: u(iim_jjm_u, llm_)   ! INOUT if tau>0 
     39      REAL(rstd), INTENT(IN)    :: tau           ! "solve" u-tau*du/dt = rhs 
     40      REAL(rstd), INTENT(IN)    :: theta(:,:,:) 
     41      REAL(rstd), INTENT(IN)    :: geopot(:,:) 
     42      REAL(rstd), INTENT(INOUT) :: pk(:,:) 
     43      REAL(rstd), INTENT(INOUT) :: berni(:,:)    ! partial Bernoulli function 
     44      REAL(rstd), INTENT(INOUT) :: du(:,:) 
     45      REAL(rstd), INTENT(INOUT) :: u(:,:)        ! INOUT if tau>0 
    4646    END SUBROUTINE comp_caldyn_fast 
    4747 
    4848    SUBROUTINE comp_caldyn_slow_hydro(zero, u,rhodz,hv,Kv, berni, hflux,du) 
    4949      IMPORT 
    50       LOGICAL, INTENT(IN) :: zero 
    51       REAL(rstd),INTENT(IN)  :: u(iim_jjm_u, llm_)    ! prognostic "velocity" 
    52       REAL(rstd),INTENT(IN)  :: rhodz(iim_jjm_i, llm_) 
    53       REAL(rstd),INTENT(IN)  :: hv(iim_jjm_v, llm_)   ! height/mass averaged to vertices 
    54       REAL(rstd),INTENT(IN)  :: Kv(iim_jjm_v, llm_)   ! kinetic energy at vertices 
    55       REAL(rstd), INTENT(OUT) :: berni(iim_jjm_i, llm_)  ! Bernoulli function 
    56       REAL(rstd),INTENT(OUT) :: hflux(iim_jjm_u, llm_) ! hflux in kg/s  
    57       REAL(rstd),INTENT(INOUT) :: du(iim_jjm_u, llm_) 
     50      LOGICAL,    INTENT(IN)    :: zero 
     51      REAL(rstd), INTENT(IN)    :: u(:,:)      ! prognostic "velocity" 
     52      REAL(rstd), INTENT(IN)    :: rhodz(:,:) 
     53      REAL(rstd), INTENT(IN)    :: hv(:,:)     ! height/mass averaged to vertices 
     54      REAL(rstd), INTENT(IN)    :: Kv(:,:)     ! kinetic energy at vertices 
     55      REAL(rstd), INTENT(OUT)   :: berni(:,:)  ! Bernoulli function 
     56      REAL(rstd), INTENT(OUT)   :: hflux(:,:) ! hflux in kg/s  
     57      REAL(rstd), INTENT(INOUT) :: du(:,:) 
    5858    END SUBROUTINE comp_caldyn_slow_hydro 
    5959     
    6060    SUBROUTINE comp_caldyn_coriolis(hflux,theta,qu, Ftheta, convm,dtheta_rhodz,du) 
    6161      IMPORT 
    62       REAL(rstd),INTENT(IN)    :: hflux(iim_jjm_u, llm_)  ! hflux in kg/s 
    63       REAL(rstd),INTENT(IN)    :: theta(iim_jjm_i, llm_, nqdyn_) ! active scalars 
    64       REAL(rstd),INTENT(IN)    :: qu(iim_jjm_u, llm_) 
    65       REAL(rstd), INTENT(OUT)  :: Ftheta(iim_jjm_u, llm_)  ! potential temperature flux 
    66       REAL(rstd),INTENT(OUT)   :: convm(iim_jjm_i, llm_)  ! mass flux convergence 
    67       REAL(rstd),INTENT(OUT)   :: dtheta_rhodz(iim_jjm_i, llm_, nqdyn_) 
    68       REAL(rstd),INTENT(INOUT) :: du(iim_jjm_u, llm_) 
     62      REAL(rstd), INTENT(IN)    :: hflux(:,:)   ! hflux in kg/s 
     63      REAL(rstd), INTENT(IN)    :: theta(:,:,:) ! active scalars 
     64      REAL(rstd), INTENT(IN)    :: qu(:,:) 
     65      REAL(rstd), INTENT(OUT)   :: Ftheta(:,:)  ! potential temperature flux 
     66      REAL(rstd), INTENT(OUT)   :: convm(:,:)   ! mass flux convergence 
     67      REAL(rstd), INTENT(OUT)   :: dtheta_rhodz(:,:,:) 
     68      REAL(rstd), INTENT(INOUT) :: du(:,:) 
    6969    END SUBROUTINE comp_caldyn_coriolis 
    7070 
Note: See TracChangeset for help on using the changeset viewer.