Ignore:
Timestamp:
09/10/13 12:04:33 (11 years ago)
Author:
dubos
Message:

Activated call to physics - Held & Suarez test case seems to work now

File:
1 edited

Legend:

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

    r149 r170  
    11MODULE physics_mod 
    22 
    3   CHARACTER(LEN=255) :: physics_type="none" 
     3  CHARACTER(LEN=255) :: physics_type="automatic" 
    44 
    55 
     
    77 
    88  SUBROUTINE init_physics 
    9   USE icosa 
    10   USE physics_dcmip_mod,init_physics_dcmip=>init_physics 
    11   USE physics_dry_mod 
    12   IMPLICIT NONE 
    13      
     9    USE icosa 
     10    USE physics_dcmip_mod,init_physics_dcmip=>init_physics 
     11    USE physics_dry_mod 
     12    IMPLICIT NONE 
     13 
    1414    CALL getin("physics",physics_type) 
    15      
     15 
    1616    SELECT CASE(TRIM(physics_type)) 
    17       CASE ('none') 
    18      
    19       CASE ('dcmip') 
    20         CALL init_physics_dcmip 
     17    CASE ('automatic') 
    2118 
    22       CASE ('lmd') 
    23         CALL init_physics_dry 
    24        
    25       CASE DEFAULT 
    26          PRINT*, 'Bad selector for variable physics init <',physics_type, & 
    27               '> options are <none>, <dcmip>,' 
     19    CASE ('dcmip') 
     20       CALL init_physics_dcmip 
    2821 
     22    CASE ('dry') 
     23       CALL init_physics_dry 
     24 
     25    CASE DEFAULT 
     26       PRINT*, 'init_physics : Bad selector for variable physics <',TRIM(physics_type), & 
     27            '> options are <automatic>, <dcmip>, <dry>' 
     28       STOP 
    2929    END SELECT 
    30      
     30 
    3131  END SUBROUTINE init_physics 
    3232 
    3333  SUBROUTINE physics(it,jD_cur,jH_cur,f_phis, f_ps, f_theta_rhodz, f_ue, f_q) 
    34   USE icosa 
    35   USE physics_dry_mod 
    36   USE physics_dcmip_mod, physics_dcmip=>physics 
    37   USE etat0_mod 
    38   USE etat0_heldsz_mod 
    39   IMPLICIT NONE 
     34    USE icosa 
     35    USE physics_dry_mod 
     36    USE physics_dcmip_mod, physics_dcmip=>physics 
     37    USE etat0_mod 
     38    USE etat0_heldsz_mod 
     39    IMPLICIT NONE 
    4040    INTEGER, INTENT(IN)   :: it 
    4141    REAL(rstd),INTENT(IN)::jD_cur,jH_cur 
     
    4646    TYPE(t_field),POINTER :: f_q(:) 
    4747    LOGICAL:: firstcall,lastcall 
    48      
     48 
    4949    SELECT CASE(TRIM(physics_type)) 
    50       CASE ('none') 
     50    CASE ('automatic') 
    5151 
    52         SELECT CASE(TRIM(etat0_type)) 
    53         CASE('heldsz')  
    54 !       CALL transfert_request(f_ps,req_i1) 
    55 !       CALL transfert_request(f_theta_rhodz,req_i1) 
    56 !       CALL transfert_request(f_ue,req_e1_vect) 
    57 !       CALL held_saurez(f_ps,f_theta_rhodz,f_ue)  
    58         CASE DEFAULT 
    59         PRINT*,"NO PHYSICAL PACAKAGE USED"  
    60         END SELECT 
    61      
    62       CASE ('dcmip') 
    63         CALL physics_dcmip(it, f_phis, f_ps, f_theta_rhodz, f_ue, f_q) 
     52       SELECT CASE(TRIM(etat0_type)) 
     53       CASE('held_suarez') 
     54          !     CALL transfert_request(f_ps,req_i1) 
     55          !     CALL transfert_request(f_theta_rhodz,req_i1) 
     56          !     CALL transfert_request(f_ue,req_e1_vect) 
     57          CALL held_suarez(f_ps,f_theta_rhodz,f_ue)  
     58       CASE DEFAULT 
     59          PRINT*,"NO PHYSICAL PACAKAGE USED" ! FIXME MPI 
     60       END SELECT 
    6461 
    65       CASE ('dry') 
    66         CALL physics_dry(it,jD_cur,jH_cur,f_phis, f_ps, f_theta_rhodz, f_ue, f_q) 
    67        
    68       CASE DEFAULT 
    69          PRINT*, 'Bad selector for variable physics <',physics_type, & 
    70               '> options are <none>, <dcmip>,' 
    71   STOP 
     62    CASE ('dcmip') 
     63       CALL physics_dcmip(it, f_phis, f_ps, f_theta_rhodz, f_ue, f_q) 
     64 
     65    CASE ('dry') 
     66       CALL physics_dry(it,jD_cur,jH_cur,f_phis, f_ps, f_theta_rhodz, f_ue, f_q) 
     67 
     68    CASE DEFAULT 
     69       PRINT*, 'Bad selector for variable physics <',TRIM(physics_type), & 
     70            '> options are <automatic>, <dcmip>, <dry>' 
     71       STOP 
    7272    END SELECT 
    73      
     73 
    7474  END SUBROUTINE physics 
    7575 
Note: See TracChangeset for help on using the changeset viewer.