Ignore:
Timestamp:
10/30/15 15:41:06 (9 years ago)
Author:
dubos
Message:

Progress towards NH

File:
1 edited

Legend:

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

    r362 r366  
    1212   
    1313  SUBROUTINE caldyn_hevi(write_out,tau, f_phis, f_ps, f_mass, f_theta_rhodz, f_u, f_q, & 
    14        f_geopot, f_hflux, f_wflux, f_dps, f_dmass, f_dtheta_rhodz, f_du_slow, f_du_fast) 
     14       f_W, f_geopot, f_hflux, f_wflux, f_dps, f_dmass, f_dtheta_rhodz, & 
     15       f_du_slow, f_du_fast, f_dPhi_slow, f_dPhi_fast, f_dW_slow, f_dW_fast)  
    1516    USE icosa 
    1617    USE observable_mod 
     
    3435    TYPE(t_field),POINTER :: f_u(:) 
    3536    TYPE(t_field),POINTER :: f_q(:) 
     37    TYPE(t_field),POINTER :: f_W(:) 
    3638    TYPE(t_field),POINTER :: f_geopot(:) 
    3739    TYPE(t_field),POINTER :: f_hflux(:), f_wflux(:) 
     
    4143    TYPE(t_field) :: f_du_slow(:) 
    4244    TYPE(t_field) :: f_du_fast(:) 
     45    TYPE(t_field) :: f_dW_slow(:) 
     46    TYPE(t_field) :: f_dW_fast(:) 
     47    TYPE(t_field) :: f_dPhi_slow(:) 
     48    TYPE(t_field) :: f_dPhi_fast(:) 
    4349     
    4450    REAL(rstd),POINTER :: ps(:), dps(:) 
    4551    REAL(rstd),POINTER :: mass(:,:), theta_rhodz(:,:), dtheta_rhodz(:,:) 
    46     REAL(rstd),POINTER :: du(:,:), hflux(:,:), wflux(:,:) 
    47     REAL(rstd),POINTER :: u(:,:), qu(:,:), qv(:,:) 
     52    REAL(rstd),POINTER :: du(:,:), dW(:,:), dPhi(:,:), hflux(:,:), wflux(:,:) 
     53    REAL(rstd),POINTER :: u(:,:), w(:,:), qu(:,:), qv(:,:) 
    4854 
    4955! temporary shared variable 
     
    6874      CALL init_message(f_u,req_e1_vect,req_u) 
    6975      CALL init_message(f_qu,req_e1_scal,req_qu) 
     76      IF(.NOT.hydrostatic) THEN 
     77         CALL init_message(f_geopot,req_i1,req_geopot) 
     78         CALL init_message(f_w,req_i1,req_w) 
     79      END IF 
    7080    ENDIF 
    7181     
     
    8191    CALL send_message(f_theta_rhodz,req_theta_rhodz) ! COM01 
    8292    CALL wait_message(req_theta_rhodz) ! COM01 Moved from caldyn_pvort 
     93 
     94    IF(.NOT.hydrostatic) THEN 
     95       CALL send_message(f_geopot,req_geopot) ! COM03 
     96       CALL wait_message(req_geopot) ! COM03 
     97       CALL send_message(f_w,req_w) ! COM04 
     98       CALL wait_message(req_w) ! COM04 
     99    END IF 
    83100     
    84101    DO ind=1,ndomain 
     
    87104       CALL swap_geometry(ind) 
    88105       ps=f_ps(ind) 
    89        u=f_u(ind) 
    90        du=f_du_fast(ind) 
    91106       theta_rhodz=f_theta_rhodz(ind) 
    92107       mass=f_mass(ind) 
    93108       theta = f_theta(ind) 
     109       CALL compute_theta(ps,theta_rhodz, mass,theta) 
    94110       pk = f_pk(ind) 
    95111       geopot = f_geopot(ind) 
    96        CALL compute_theta(ps,theta_rhodz, mass,theta) 
    97        CALL compute_geopot(ps,mass,theta, pk,geopot) 
    98        CALL compute_caldyn_fast(tau,u,mass,theta,pk,geopot, du) ! computes du_fast and updates u 
     112       IF(hydrostatic) THEN 
     113          CALL compute_geopot(ps,mass,theta, pk,geopot) 
     114       ELSE 
     115          W = f_W(ind) 
     116          dW = f_dW_fast(ind) 
     117          dPhi = f_dPhi_fast(ind) 
     118          CALL compute_caldyn_solver(tau,mass,theta,pk,geopot,W,dPhi,dW) ! computes d(Phi,W)_fast and updates Phi,W 
     119       END IF 
     120       u=f_u(ind) 
     121       du=f_du_fast(ind) 
     122       CALL compute_caldyn_fast(tau,u,mass,theta,pk,geopot,du) ! computes du_fast and updates du 
    99123    ENDDO 
    100124     
Note: See TracChangeset for help on using the changeset viewer.