Ignore:
Timestamp:
07/16/12 11:26:23 (12 years ago)
Author:
ymipsl
Message:

Simplify the management of the module.

YM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/etat0_ncar.f90

    r17 r19  
    11MODULE etat0_ncar_mod 
    2   USE genmod 
     2  USE icosa 
    33  PRIVATE 
    44 
     
    2828   
    2929  SUBROUTINE etat0(f_ps,f_phis,f_theta_rhodz,f_u,f_q) 
    30   USE field_mod 
    31   USE domain_mod 
    32   USE domain_mod 
    33   USE dimensions 
    34   USE grid_param 
    35   USE geometry 
     30  USE icosa 
    3631  IMPLICIT NONE 
    3732    TYPE(t_field),POINTER :: f_ps(:) 
     
    6257   
    6358  SUBROUTINE compute_etat0_ncar(ps, phis, theta_rhodz, u, q) 
    64   USE domain_mod 
    65   USE dimensions 
    66   USE grid_param 
    67   USE geometry 
    68   USE metric 
     59  USE icosa 
    6960  USE disvert_mod 
    70   USE spherical_geom_mod 
    71   USE vector 
    7261  USE pression_mod 
    7362  USE exner_mod 
    7463  USE geopotential_mod 
    7564  USE theta2theta_rhodz_mod 
    76   USE ioipsl 
    7765  IMPLICIT NONE   
    7866  REAL(rstd),INTENT(OUT) :: ps(iim*jjm) 
Note: See TracChangeset for help on using the changeset viewer.