Changeset 208


Ignore:
Timestamp:
07/10/14 11:28:31 (10 years ago)
Author:
ymipsl
Message:

Atmosphere scaleheight is not hard coded in disvert_std, and given in meters instead km
YM

Location:
codes/icosagcm/trunk/src
Files:
3 edited

Legend:

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

    r207 r208  
    3333  REAL(rstd),INTENT(OUT) :: presnivs(:) 
    3434   
    35   INTEGER,PARAMETER :: unit=42 
    3635  CHARACTER(len=255) :: filename 
    3736  INTEGER :: l,ok 
     
    6968    ! tell the world about it 
    7069    IF (is_mpi_root) THEN 
     70!$OMP MASTER 
    7171      WRITE(*,*) "ap()=",ap 
    7272      WRITE(*,*) "bp()=",bp 
    7373      WRITE(*,*) "Approximative mid-layer pressure, assuming a surface pressure preff=",preff," Pa" 
    74       WRITE(*,*) "and approximative mid-layer height, assuming an atmospheric scale height of ",scaleheight," (km)" 
     74      WRITE(*,*) "and approximative mid-layer height, assuming an atmospheric scale height of ",scaleheight/1000," (km)" 
    7575      DO l=1,llm 
    76         WRITE(*,*) 'PRESNIVS(',l,')=',presnivs(l),'  Z ~ ',log(preff/presnivs(l))*scaleheight,       & 
    77                    ' DZ ~ ',scaleheight*log((ap(l)+bp(l)*preff)/ max(ap(l+1)+bp(l+1)*preff,1.e-10)) 
     76        WRITE(*,*) 'PRESNIVS(',l,')=',presnivs(l),'  Z ~ ',log(preff/presnivs(l))*scaleheight/1000,       & 
     77                   ' DZ ~ ',scaleheight/1000*log((ap(l)+bp(l)*preff)/ max(ap(l+1)+bp(l+1)*preff,1.e-10)) 
    7878      ENDDO 
     79!$OMP END MASTER 
    7980    ENDIF 
    8081   
  • codes/icosagcm/trunk/src/disvert_std.f90

    r186 r208  
    2626  USE icosa 
    2727  USE mpipara 
     28  USE earth_const 
    2829  IMPLICIT NONE 
    2930  REAL(rstd),INTENT(OUT) :: ap(:) 
     
    5960    ap(1)=0. 
    6061    ap(llm+1) = pa * ( sig(llm+1) - bp(llm+1) ) 
    61      
    62     IF (is_mpi_root) PRINT*,'ap',ap 
    63     IF (is_mpi_root) PRINT*,'bp',bp 
    64      
    65     IF (is_mpi_root) PRINT*, 'Niveaux de pressions approximatifs aux centres des' 
    66     IF (is_mpi_root) PRINT*, 'couches calcules pour une pression de surface =', preff 
    67     IF (is_mpi_root) PRINT*, 'et altitudes equivalentes pour une hauteur d echelle de' 
    68     IF (is_mpi_root) PRINT*, '8km' 
    69      
    7062    DO l = 1, llm 
    7163      presnivs(l) = 0.5 *( ap(l)+bp(l)*preff + ap(l+1)+bp(l+1)*preff ) 
    72    
    73       IF (is_mpi_root) PRINT*, 'PRESNIVS(',l,')=',presnivs(l),'  Z ~ ',log(preff/presnivs(l))*8.,       & 
    74                                ' DZ ~ ',8.*log((ap(l)+bp(l)*preff)/ max(ap(l+1)+bp(l+1)*preff,1.e-10)) 
    7564    ENDDO 
     65     
     66    ! tell the world about it 
     67    IF (is_mpi_root) THEN 
     68!$OMP MASTER 
     69      WRITE(*,*) "ap()=",ap 
     70      WRITE(*,*) "bp()=",bp 
     71      WRITE(*,*) "Approximative mid-layer pressure, assuming a surface pressure preff=",preff," Pa" 
     72      WRITE(*,*) "and approximative mid-layer height, assuming an atmospheric scale height of ",scaleheight/1000," (km)" 
     73      DO l=1,llm 
     74        WRITE(*,*) 'PRESNIVS(',l,')=',presnivs(l),'  Z ~ ',log(preff/presnivs(l))*scaleheight/1000,       & 
     75                   ' DZ ~ ',scaleheight/1000*log((ap(l)+bp(l)*preff)/ max(ap(l+1)+bp(l+1)*preff,1.e-10)) 
     76      ENDDO 
     77!$OMP END MASTER 
     78    ENDIF 
    7679   
    7780  END SUBROUTINE disvert 
  • codes/icosagcm/trunk/src/earth_const.f90

    r207 r208  
    1111  REAL(rstd),SAVE :: preff=101325. 
    1212  REAL(rstd),SAVE :: pa=50000. 
    13   REAL(rstd),SAVE :: scaleheight=8. ! atmospheric scale height (km) 
     13  REAL(rstd),SAVE :: scaleheight=8000. ! atmospheric scale height (m) 
    1414  REAL(rstd),SAVE :: scale_factor=1. 
    1515 
Note: See TracChangeset for help on using the changeset viewer.