source: codes/icosagcm/trunk/src/vertical/disvert_apbp.f90

Last change on this file was 901, checked in by adurocher, 5 years ago

trunk : Fixed compilation with --std=f2008 with gfortran

Added dynamico_abort() to replace non standard ABORT() intrinsic
Other modifications to respect the fortran standard

  • Property svn:executable set to *
File size: 2.7 KB
Line 
1MODULE disvert_apbp_mod
2  USE icosa
3  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: ap(:)
4!$OMP THREADPRIVATE(ap)
5  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: bp(:)
6!$OMP THREADPRIVATE(bp)
7  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: presnivs(:)
8!$OMP THREADPRIVATE(presnivs)
9
10CONTAINS
11
12  SUBROUTINE init_disvert
13!  USE icosa
14  IMPLICIT NONE
15 
16    ALLOCATE(ap(llm+1))
17    ALLOCATE(bp(llm+1))
18    ALLOCATE(presnivs(llm))
19
20    CALL disvert(ap,bp,presnivs)   
21
22  END SUBROUTINE init_disvert 
23
24
25  SUBROUTINE disvert(ap,bp,presnivs)
26!  USE icosa
27  USE abort_mod
28  USE mpipara, ONLY: is_mpi_root
29  USE omp_para, ONLY: omp_in_parallel
30  USE transfert_omp_mod, ONLY: bcast_omp
31  USE free_unit_mod, ONLY : free_unit
32  IMPLICIT NONE
33  REAL(rstd),INTENT(OUT) :: ap(:)
34  REAL(rstd),INTENT(OUT) :: bp(:)
35  REAL(rstd),INTENT(OUT) :: presnivs(:)
36  INTEGER :: unit
37  CHARACTER(len=255) :: filename
38  INTEGER :: l,ok
39 
40    filename="apbp.txt" !file to read
41    ! but users may want to use some other file name
42    CALL getin('read_apbp_file',filename)
43   
44!$OMP MASTER
45    unit=free_unit()
46    OPEN(unit,file=filename,status="old",action="read",iostat=ok)
47    IF (ok/=0) THEN
48      WRITE(*,*) "disvert_ap_bp error: input file ",trim(filename)," not found!"
49      CALL dynamico_abort( "disvert_ap_bp : could not open input file" )
50    ENDIF
51    ! read in ap() and b() line by line, starting from surface up
52    ! to model top
53    DO l=1,llm+1
54      READ(unit,fmt=*,iostat=ok) ap(l),bp(l)
55      IF (ok/=0) THEN
56        WRITE(*,*) "disvert_ap_bp error: failed reading ap(l) and bp(l) for l=",l
57        CALL dynamico_abort( "disvert_ap_bp : could not read input file" )
58      ENDIF
59    ENDDO
60   
61    CLOSE(unit)
62!$OMP END MASTER
63    IF (omp_in_parallel()) THEN
64      CALL bcast_omp(ap)
65      CALL bcast_omp(bp)
66    ENDIF
67   
68    ! build presnivs(), approximative mid-layer pressures
69    DO l=1,llm
70      presnivs(l)=0.5*(ap(l)+bp(l)*preff+ap(l+1)+bp(l+1)*preff)
71    ENDDO
72   
73    ! tell the world about it
74    IF (is_mpi_root) THEN
75!$OMP MASTER
76      WRITE(*,*) "ap()=",ap
77      WRITE(*,*) "bp()=",bp
78      WRITE(*,*) "Approximative mid-layer pressure, assuming a surface pressure preff=",preff," Pa"
79      WRITE(*,*) "and approximative mid-layer height, assuming an atmospheric scale height of ",scale_height/1000," (km)"
80      DO l=1,llm
81        WRITE(*,*) 'PRESNIVS(',l,')=',presnivs(l),'  Z ~ ',log(preff/presnivs(l))*scale_height/1000,       &
82                   ' DZ ~ ',scale_height/1000*log((ap(l)+bp(l)*preff)/ max(ap(l+1)+bp(l+1)*preff,1.e-10))
83      ENDDO
84!$OMP END MASTER
85    ENDIF
86 
87  END SUBROUTINE disvert
88 
89END MODULE disvert_apbp_mod
Note: See TracBrowser for help on using the repository browser.