source: CONFIG/UNIFORM/v7/ICOLMDZOR_v7/SOURCES/DYNAMICO/src/vertical/disvert_apbp.f90 @ 5878

Last change on this file since 5878 was 5878, checked in by aclsce, 3 years ago

Merged LMDZORv6.2.2 with ICOLMDZOR_v7 configuration te be able to launch LMDZOR experiment from ICOLMDZOR configuration.
Use of NPv6.2 physiq version in ICOLMDZOR experiments.

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