Changeset 56


Ignore:
Timestamp:
07/31/12 17:46:53 (12 years ago)
Author:
dubos
Message:

caldyn_gcm cleanup

File:
1 edited

Legend:

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

    r53 r56  
    1717    IMPLICIT NONE 
    1818    REAL(rstd),INTENT(IN) :: dt 
    19     INTEGER :: write_period 
     19    REAL :: write_period 
    2020     
    2121    write_period=0 
    2222    CALL getin('write_period',write_period) 
    2323    write_period=write_period/scale_factor 
    24     itau_out=INT(write_period/dt) 
    25    
     24    itau_out=FLOOR(.5+write_period/dt) 
     25    PRINT *, 'Output frequency (scaled) set to ',write_period, ' : itau_out = ',itau_out 
     26  
    2627    CALL allocate_caldyn 
    2728   
     
    4344 
    4445  END SUBROUTINE allocate_caldyn 
    45    
    46   SUBROUTINE swap_caldyn(ind) 
    47   IMPLICIT NONE 
    48     INTEGER,INTENT(IN) :: ind 
    49 !    out=f_out(ind)  
    50     out_u=f_out_u(ind)  
    51 !    out_z=f_out_z(ind)  
    52        
    53   END SUBROUTINE swap_caldyn 
    54   
     46    
    5547  SUBROUTINE check_mass_conservation(f_ps,f_dps) 
    5648  USE icosa 
     
    120112    CALL transfert_request(f_theta_rhodz,req_i1)  
    121113    CALL transfert_request(f_u,req_e1) 
    122 !    CALL transfert_request(f_u,req_e1)  
    123     
    124  
    125 !    CALL vorticity(f_u,f_out_z) 
    126114     
    127115    DO ind=1,ndomain 
    128116      CALL swap_dimensions(ind) 
    129117      CALL swap_geometry(ind) 
    130       CALL swap_caldyn(ind) 
    131118       
     119      out_u=f_out_u(ind)  
    132120      phis=f_phis(ind) 
    133121      ps=f_ps(ind) 
     
    137125      dtheta_rhodz=f_dtheta_rhodz(ind) 
    138126      du=f_du(ind) 
    139 !      ij=(jj_end-1-1)*iim+ii_begin 
    140 !      PRINT *,"--> ind=",ind,ij 
    141 !      PRINT *,u(ij+u_right,1) 
    142 !      PRINT *,u(ij+u_rup,1) 
    143 !      PRINT *,u(ij+u_lup,1) 
    144 !      PRINT *,u(ij+u_left,1) 
    145 !      PRINT *,u(ij+u_ldown,1) 
    146 !      PRINT *,u(ij+u_rdown,1) 
    147  
    148 !      ij=(jj_end-1-1)*iim+ii_end 
    149 !      PRINT *,"--> ind=",ind,ij 
    150 !      PRINT *,u(ij+u_right,1) 
    151 !      PRINT *,u(ij+u_rup,1) 
    152 !      PRINT *,u(ij+u_lup,1) 
    153 !      PRINT *,u(ij+u_left,1) 
    154 !      PRINT *,u(ij+u_ldown,1) 
    155 !      PRINT *,u(ij+u_rdown,1)       
    156127!$OMP PARALLEL DEFAULT(SHARED) 
    157128      CALL compute_caldyn(phis, ps, theta_rhodz, u, dps, dtheta_rhodz, du) 
    158129!$OMP END PARALLEL 
    159130    ENDDO 
    160  
    161 !    CALL transfert_request(f_out_u,req_e1) 
    162 !    CALL transfert_request(f_out_u,req_e1)  
    163  
    164 !    CALL vorticity(f_u,f_out_z) 
    165131 
    166132    IF (mod(it,itau_out)==0 ) THEN 
     
    169135            f_buf_i, f_buf_v, f_buf_u3d, f_buf_ulon, f_buf_ulat, f_buf_s, f_buf_p) 
    170136    END IF 
    171  
    172137 
    173138!    CALL check_mass_conservation(f_ps,f_dps) 
     
    192157    REAL(rstd) :: ww,uu  
    193158    REAL(rstd) :: delta 
    194     REAL(rstd) :: etav,hv     
     159    REAL(rstd) :: etav,hv, du2 
    195160 
    196161!   REAL(rstd) :: theta(iim*jjm,llm)  ! potential temperature 
     
    272237!    berni=1e10 
    273238     
    274  !!! Compute pression 
    275   
     239 !!! Compute pressure 
     240 
     241!    PRINT *, 'Computing pressure' 
    276242    DO    l    = 1, llm+1 
    277243!$OMP DO 
     
    285251       
    286252 !!! Compute Exner function 
     253!    PRINT *, 'Computing Exner' 
    287254    CALL compute_exner(ps,p,pks,pk,1)  
    288255 
    289256!!! Compute mass 
     257   ! PRINT *, 'Computing mass' 
    290258   DO l = 1, llm 
    291259!$OMP DO 
     
    300268 
    301269!! compute theta 
     270   ! PRINT *, 'Computing theta' 
    302271    DO    l    = 1, llm 
    303272!$OMP DO 
     
    336305    
    337306!!!  Compute mass flux 
    338 !! question ï¿œ thomas : meilleure pondï¿œration de la masse sur les liens ? 
    339307 
    340308  DO l = 1, llm 
     
    416384    ENDDO 
    417385  ENDDO 
    418    
    419  
    420 !  DO l = 1, llm 
    421 !!$OMP DO 
    422 !   DO j=jj_begin,jj_end 
    423 !    DO i=ii_begin,ii_end 
    424 !      ij=(j-1)*iim+i 
    425 !      out(ij,l)=theta(ij,l)-288 
    426 !    ENDDO 
    427 !  ENDDO 
    428 ! ENDDO 
    429  
    430  
     386 
     387   
    431388!!! Compute dps 
    432389!$OMP DO 
     
    440397 
    441398 
    442  
    443399!!! Compute vertical velocity 
    444400  DO l = 1,llm-1 
     
    455411 
    456412!$OMP DO 
     413  ! vertical mass flux at the surface = 0 
    457414  DO j=jj_begin,jj_end 
    458415    DO i=ii_begin,ii_end 
     
    463420 
    464421 
    465 !!! Compute potential vorticity 
     422!!! Compute shallow-water potential vorticity 
    466423  DO l = 1,llm 
    467424!$OMP DO 
     
    494451    ENDDO 
    495452 
    496 !!! Compute potential vorticity contribution to du 
     453!!! Compute potential vorticity (Coriolis) contribution to du 
    497454  DO l=1,llm 
    498455!$OMP DO 
     
    565522   
    566523  
    567 !!! second contribution to du 
     524!!! second contribution to du (gradients of Bernoulli and Exner functions) 
    568525  DO l=1,llm 
    569526!$OMP DO 
     
    590547  ENDDO 
    591548  
    592 !!! second contribution to du 
     549!!! save second contribution to du for debugging output 
    593550  DO l=1,llm 
    594551!$OMP DO 
     
    615572  ENDDO 
    616573 
    617 !!! contribution due to vertical advection 
     574!!! contributions due to vertical advection 
    618575  
    619576 ! Contribution to dtheta 
Note: See TracChangeset for help on using the changeset viewer.