Ignore:
Timestamp:
09/21/18 01:44:51 (6 years ago)
Author:
dubos
Message:

devel : small cleanup in idealized physics

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/physics/physics.f90

    r726 r739  
    77  PRIVATE 
    88 
    9   INTEGER, PARAMETER :: phys_none=0, phys_HS94=1, phys_DCMIP=2, phys_lmdz_generic=3, phys_LB2012=4, phys_external=5,& 
    10                         phys_DCMIP2016=6 
    11  
     9  INTEGER, PARAMETER :: phys_none=0, phys_column=1, & 
     10       phys_HS94=3, phys_LB2012=4, & 
     11       phys_DCMIP=11, phys_DCMIP2016=12, & 
     12       phys_lmdz_generic=21, phys_external=22 
    1213  INTEGER :: phys_type 
    1314  TYPE(t_field),POINTER,SAVE :: f_extra_physics_2D(:), f_extra_physics_3D(:) 
     
    2829    USE mpipara 
    2930    USE etat0_mod 
     31    USE etat0_venus_mod, ONLY : init_phys_venus=>init_physics 
    3032    USE physics_dcmip_mod, ONLY : init_physics_dcmip=>init_physics 
    3133    USE physics_dcmip2016_mod, ONLY : init_physics_dcmip2016=>init_physics 
    32     USE etat0_venus_mod, ONLY : init_phys_venus=>init_physics 
    3334    USE physics_lmdz_generic_mod, ONLY : init_physics_lmdz_generic=>init_physics 
    3435    USE physics_external_mod, ONLY : init_physics_external=>init_physics 
    35  
     36    LOGICAL :: done 
    3637    physics_inout%dt_phys = dt*itau_physics 
     38!$OMP PARALLEL 
     39    CALL allocate_field(f_du_phys,field_u,type_real,llm, name='du_phys') 
     40 
    3741    physics_type='none' 
    3842    CALL getin("physics",physics_type) 
     43    ! below, flag done is set to .FALSE. if the CALL to init_XXX must be done outside any OMP PARALLEL region 
     44    done=.TRUE. 
     45    phys_type=phys_column 
    3946    SELECT CASE(TRIM(physics_type)) 
    4047    CASE ('none') 
    41  
    42 !$OMP PARALLEL 
    4348       IF(is_mpi_root) PRINT*,"NO PHYSICAL PACKAGE USED" 
    4449       phys_type = phys_none 
    45 !$OMP END PARALLEL 
    46  
    4750    CASE ('held_suarez') 
    48  
    49 !$OMP PARALLEL 
    5051       phys_type = phys_HS94 
    51 !$OMP END PARALLEL 
    52  
    5352    CASE ('Lebonnois2012') 
    54  
    55 !$OMP PARALLEL 
    5653       phys_type = phys_LB2012 
    57        CALL init_phys_venus 
    58 !$OMP END PARALLEL 
    59  
     54       CALL init_phys_venus        
    6055    CASE ('phys_lmdz_generic') 
    61  
    62 !$OMP PARALLEL 
    63        CALL init_physics_lmdz_generic 
    6456       phys_type=phys_lmdz_generic 
    65 !$OMP END PARALLEL 
    66  
     57       done = .FALSE. 
    6758    CASE ('phys_external') 
    68  
    69        CALL init_physics_external 
    70 !$OMP PARALLEL 
    7159       phys_type=phys_external 
    72 !$OMP END PARALLEL 
    73  
    74     CASE ('dcmip') 
    75  
    76 !$OMP PARALLEL 
     60       done = .FALSE. 
     61    END SELECT 
     62 
     63    IF(phys_type == phys_column) THEN 
    7764       CALL allocate_field(f_dulon,field_t,type_real,llm, name='dulon') 
    7865       CALL allocate_field(f_dulat,field_t,type_real,llm, name='dulat') 
     
    8370       CALL allocate_field(f_pk,field_t,type_real,llm, name='pk') 
    8471       CALL init_pack_before ! Compute physics_inout%ngrid and offsets used by pack/unpack 
    85        CALL init_physics_dcmip 
    86        CALL init_pack_after ! Defines Ai, lon, lat in physics_inout 
    87        phys_type = phys_DCMIP 
     72       CALL init_pack_after  ! Defines Ai, lon, lat in physics_inout 
     73        
     74       SELECT CASE(TRIM(physics_type)) 
     75       CASE ('dcmip') 
     76          phys_type = phys_DCMIP 
     77          CALL init_physics_dcmip 
     78       CASE ('dcmip2016') 
     79          phys_type = phys_DCMIP2016 
     80          CALL init_physics_dcmip2016 
     81       CASE DEFAULT 
     82          IF(is_mpi_root) PRINT*, 'init_physics : Bad selector for variable physics <',& 
     83               TRIM(physics_type), '> options are <none>, <held_suarez>, <Lebonnois2012>,', & 
     84               '<dcmip>, <dcmip2016>, <phys_lmdz_generic>, <phys_external>' 
     85          STOP 
     86       END SELECT 
     87        
     88    END IF 
    8889!$OMP END PARALLEL 
    8990 
    90     CASE ('dcmip2016') 
    91  
    92 !$OMP PARALLEL 
    93        CALL allocate_field(f_dulon,field_t,type_real,llm, name='dulon') 
    94        CALL allocate_field(f_dulat,field_t,type_real,llm, name='dulat') 
    95        CALL allocate_field(f_temp,field_t,type_real,llm, name='temp') 
    96        CALL allocate_field(f_ulon,field_t,type_real,llm, name='ulon') 
    97        CALL allocate_field(f_ulat,field_t,type_real,llm, name='ulat') 
    98        CALL allocate_field(f_p,field_t,type_real,llm+1, name='p') 
    99        CALL allocate_field(f_pk,field_t,type_real,llm, name='pk') 
    100        CALL init_pack_before ! Compute physics_inout%ngrid and offsets used by pack/unpack 
    101        CALL init_physics_dcmip2016 
    102        CALL init_pack_after ! Defines Ai, lon, lat in physics_inout 
    103        phys_type = phys_DCMIP2016 
    104 !$OMP END PARALLEL 
    105  
    106     CASE DEFAULT 
    107        IF(is_mpi_root) PRINT*, 'init_physics : Bad selector for variable physics <',& 
    108             TRIM(physics_type), '> options are <none>, <held_suarez>, <Lebonnois2012>, <dcmip>', & 
    109                                 '<phys_lmdz_generic>, <phys_external>' 
    110        STOP 
    111     END SELECT 
    112  
    113 !$OMP PARALLEL 
    114     CALL allocate_field(f_du_phys,field_u,type_real,llm, name='du_phys') 
     91    IF(done==.FALSE.) THEN 
     92       SELECT CASE(phys_type) 
     93       CASE(phys_external)  
     94          CALL init_physics_external 
     95       CASE(phys_lmdz_generic) 
     96          CALL init_physics_lmdz_generic 
     97       END SELECT 
     98    END IF 
    11599 
    116100    IF(is_mpi_root) PRINT *, 'phys_type = ',phys_type 
    117 !$OMP END PARALLEL 
     101 
    118102  END SUBROUTINE init_physics 
    119103 
Note: See TracChangeset for help on using the changeset viewer.