source: codes/icosagcm/devel/src/vertical/disvert_apbp.f90 @ 595

Last change on this file since 595 was 531, checked in by dubos, 7 years ago

devel : tyding up sources

File size: 2.5 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 mpipara, ONLY: is_mpi_root
28  USE omp_para, ONLY: omp_in_parallel
29  USE transfert_omp_mod, ONLY: bcast_omp
30  USE free_unit_mod, ONLY : free_unit
31  IMPLICIT NONE
32  REAL(rstd),INTENT(OUT) :: ap(:)
33  REAL(rstd),INTENT(OUT) :: bp(:)
34  REAL(rstd),INTENT(OUT) :: presnivs(:)
35  INTEGER :: unit
36  CHARACTER(len=255) :: filename
37  INTEGER :: l,ok
38 
39    filename="apbp.txt" !file to read
40    ! but users may want to use some other file name
41    CALL getin('read_apbp_file',filename)
42   
43!$OMP MASTER
44    unit=free_unit()
45    OPEN(unit,file=filename,status="old",action="read",iostat=ok)
46    IF (ok/=0) THEN
47      WRITE(*,*) "disvert_ap_bp error: input file ",trim(filename)," not found!"
48      CALL ABORT
49    ENDIF
50    ! read in ap() and b() line by line, starting from surface up
51    ! to model top
52    DO l=1,llm+1
53      READ(unit,fmt=*,iostat=ok) ap(l),bp(l)
54      IF (ok/=0) THEN
55        WRITE(*,*) "disvert_ap_bp error: failed reading ap(l) and bp(l) for l=",l
56        CALL ABORT
57      ENDIF
58    ENDDO
59   
60    CLOSE(unit)
61!$OMP END MASTER
62    IF (omp_in_parallel()) THEN
63      CALL bcast_omp(ap)
64      CALL bcast_omp(bp)
65    ENDIF
66   
67    ! build presnivs(), approximative mid-layer pressures
68    DO l=1,llm
69      presnivs(l)=0.5*(ap(l)+bp(l)*preff+ap(l+1)+bp(l+1)*preff)
70    ENDDO
71   
72    ! tell the world about it
73    IF (is_mpi_root) THEN
74!$OMP MASTER
75      WRITE(*,*) "ap()=",ap
76      WRITE(*,*) "bp()=",bp
77      WRITE(*,*) "Approximative mid-layer pressure, assuming a surface pressure preff=",preff," Pa"
78      WRITE(*,*) "and approximative mid-layer height, assuming an atmospheric scale height of ",scale_height/1000," (km)"
79      DO l=1,llm
80        WRITE(*,*) 'PRESNIVS(',l,')=',presnivs(l),'  Z ~ ',log(preff/presnivs(l))*scale_height/1000,       &
81                   ' DZ ~ ',scale_height/1000*log((ap(l)+bp(l)*preff)/ max(ap(l+1)+bp(l+1)*preff,1.e-10))
82      ENDDO
83!$OMP END MASTER
84    ENDIF
85 
86  END SUBROUTINE disvert
87 
88END MODULE disvert_apbp_mod
Note: See TracBrowser for help on using the repository browser.