source: trunk/LMDZ.TITAN/libf/phytitan/calmufi.F90 @ 1862

Last change on this file since 1862 was 1819, checked in by jvatant, 7 years ago

Commit various bugs leading to negative tracer tendencies
Also deleted some useless cfg files
--JVO

  • Property svn:executable set to *
File size: 6.9 KB
Line 
1SUBROUTINE calmufi(plev, zlev, play, zlay, temp, pq, zdq)
2  !! Interface subroutine to YAMMS model for Titan LMDZ GCM.
3  !!
4  !! The subroutine computes the microphysics processes for a single vertical column.
5  !!
6  !! - All input vectors are assumed to be defined from GROUND to TOP of the atmosphere.
7  !! - All output vectors are defined from GROUND to TOP of the atmosphere.
8  !! - Only tendencies are returned.
9  !!
10  !! @important
11  !! The method assumes global initialization of YAMMS model (and extras) has been already
12  !! done elsewhere.
13  !!
14  !! Authors : J.Burgalat, J.Vatant d'Ollone - 2017
15  !!
16  USE MMP_GCM
17  USE tracer_h
18  USE comcstfi_mod, only : g
19  USE callkeys_mod, only : callclouds
20  IMPLICIT NONE
21
22  REAL(kind=8), DIMENSION(:,:), INTENT(IN) :: plev  !! Pressure levels (Pa).
23  REAL(kind=8), DIMENSION(:,:), INTENT(IN) :: zlev  !! Altitude levels (m).
24  REAL(kind=8), DIMENSION(:,:), INTENT(IN) :: play  !! Pressure layers (Pa).
25  REAL(kind=8), DIMENSION(:,:), INTENT(IN) :: zlay  !! Altitude at the center of each layer (m).
26  REAL(kind=8), DIMENSION(:,:), INTENT(IN) :: temp  !! Temperature at the center of each layer (K).
27
28  REAL(kind=8), DIMENSION(:,:,:), INTENT(IN)  :: pq   !! Tracers (\(kg.kg^{-1}}\)).
29  REAL(kind=8), DIMENSION(:,:,:), INTENT(OUT) :: zdq  !! Tendency for tracers (\(kg.kg^{-1}}\)).
30 
31  REAL(kind=8), DIMENSION(:), ALLOCATABLE :: m0as !! 0th order moment of the spherical mode (\(m^{-2}\)).
32  REAL(kind=8), DIMENSION(:), ALLOCATABLE :: m3as !! 3rd order moment of the spherical mode (\(m^{3}.m^{-2}\)).
33  REAL(kind=8), DIMENSION(:), ALLOCATABLE :: m0af !! 0th order moment of the fractal mode (\(m^{-2}\)).
34  REAL(kind=8), DIMENSION(:), ALLOCATABLE :: m3af !! 3rd order moment of the fractal mode (\(m^{3}.m^{-2}\)).
35
36  REAL(kind=8), DIMENSION(:), ALLOCATABLE   :: m0n  !! 0th order moment of the CCN distribution (\(m^{-2}\)).
37  REAL(kind=8), DIMENSION(:), ALLOCATABLE   :: m3n  !! 3rd order moment of the CCN distribution (\(m^{3}.m^{-2}\)).
38  REAL(kind=8), DIMENSION(:,:), ALLOCATABLE :: m3i  !! 3rd order moments of the ice components (\(m^{3}.m^{-2}\)).
39  REAL(kind=8), DIMENSION(:,:), ALLOCATABLE :: gazs !! Condensible species gazs molar fraction (\(mol.mol^{-1}\)).
40
41  REAL(kind=8), DIMENSION(:), ALLOCATABLE   :: dm0as !! Tendency of the 0th order moment of the spherical mode distribution (\(m^{-2}\)).
42  REAL(kind=8), DIMENSION(:), ALLOCATABLE   :: dm3as !! Tendency of the 3rd order moment of the spherical mode distribution (\(m^{3}.m^{-2}\)).
43  REAL(kind=8), DIMENSION(:), ALLOCATABLE   :: dm0af !! Tendency of the 0th order moment of the fractal mode distribution (\(m^{-2}\)).
44  REAL(kind=8), DIMENSION(:), ALLOCATABLE   :: dm3af !! Tendency of the 3rd order moment of the fractal mode distribution (\(m^{3}.m^{-2}\)).
45  REAL(kind=8), DIMENSION(:), ALLOCATABLE   :: dm0n  !! Tendency of the 0th order moment of the _CCN_ distribution (\(m^{-2}\)).
46  REAL(kind=8), DIMENSION(:), ALLOCATABLE   :: dm3n  !! Tendency of the 3rd order moment of the _CCN_ distribution (\(m^{3}.m^{-2}\)).
47  REAL(kind=8), DIMENSION(:,:), ALLOCATABLE :: dm3i  !! Tendencies of the 3rd order moments of each ice components (\(m^{3}.m^{-2}\)).
48  REAL(kind=8), DIMENSION(:,:), ALLOCATABLE :: dgazs !! Tendencies of each condensible gaz species !(\(mol.mol^{-1}\)).
49
50  REAL(kind=8), DIMENSION(:), ALLOCATABLE ::  int2ext
51  TYPE(error) :: err
52
53  INTEGER :: ilon, i,nices
54
55  INTEGER :: nlon,nlay
56
57  ! Read size of arrays
58  nlon  = size(play,DIM=1)
59  nlay  = size(play,DIM=2)
60  nices = size(ices_indx)
61  ! Conversion intensive to extensive
62  ALLOCATE( int2ext(nlay) ) 
63
64  ! Loop on horizontal grid points
65
66  ! Allocate arrays
67  ALLOCATE( m0as(nlay) )
68  ALLOCATE( m3as(nlay) )
69  ALLOCATE( m0af(nlay) )
70  ALLOCATE( m3af(nlay) )
71  ALLOCATE( m0n(nlay) )
72  ALLOCATE( m3n(nlay) )
73  ALLOCATE( m3i(nlay,nices) )
74  ALLOCATE( gazs(nlay,nices) )
75
76  ALLOCATE( dm0as(nlay) )
77  ALLOCATE( dm3as(nlay) )
78  ALLOCATE( dm0af(nlay) )
79  ALLOCATE( dm3af(nlay) )
80  ALLOCATE( dm0n(nlay) )
81  ALLOCATE( dm3n(nlay) )
82  ALLOCATE( dm3i(nlay,nices) )
83  ALLOCATE( dgazs(nlay,nices) )
84
85  ! Initialization of zdq here since intent=out and no action performed on every tracers
86  zdq(:,:,:) = 0.0
87
88  DO ilon = 1, nlon
89    ! Convert tracers to extensive ( except for gazs where we work with molar mass ratio )
90    ! We suppose a given order of tracers !
91    int2ext(:) = ( plev(ilon,1:nlay) - plev(ilon,2:nlay+1) ) / g
92
93    m0as(:) = pq(ilon,:,1) * int2ext(:)
94    m3as(:) = pq(ilon,:,2) * int2ext(:)
95    m0af(:) = pq(ilon,:,3) * int2ext(:)
96    m3af(:) = pq(ilon,:,4) * int2ext(:)
97   
98    if (callclouds) then ! if call clouds
99      dm0n(:) = pq(ilon,:,5) * int2ext(:)
100      dm3n(:) = pq(ilon,:,6) * int2ext(:)
101      do i=1,nices
102        dm3i(:,nices) = pq(ilon,:,6+i) * int2ext(:)
103        dgazs(:,i)    = pq(ilon,:,ices_indx(i)) * rat_mmol(ices_indx(i)) ! For gazs we work on the full tracer array !!
104        ! We use the molar mass ratio from GCM in case there is discrepancy with the mm one
105      enddo
106    endif
107
108
109    ! Initialize YAMMS atmospheric column
110    err = mm_column_init(plev(ilon,:),zlev(ilon,:),play(ilon,:),zlay(ilon,:),temp(ilon,:)) ; IF (err /= 0) call abort_program(err)
111    ! Initialize YAMMS aerosols moments column
112    err = mm_aerosols_init(m0as,m3as,m0af,m3af) ; IF (err /= 0) call abort_program(err)
113    IF (callclouds) THEN ! call clouds
114      err = mm_clouds_init(m0n,m3n,m3i,gazs) ; IF (err /= 0) call abort_program(err)
115    ENDIF
116
117    ! Check on size (???)
118
119    ! initializes tendencies:
120    !dm0as(:) = 0._mm_wp ; dm3as(:) = 0._mm_wp ; dm0af(:) = 0._mm_wp ; dm3af(:) = 0._mm_wp
121    !dm0n(:) = 0._mm_wp ; dm3n(:) = 0._mm_wp ; dm3i(:,:) = 0._mm_wp ; dgazs(:,:) = 0._mm_wp
122
123    dm0as(:) = 0.0 ; dm3as(:) = 0.0 ; dm0af(:) = 0.0 ; dm3af(:) = 0.0
124    dm0n(:) = 0.0 ; dm3n(:) = 0.0 ; dm3i(:,:) = 0.0 ; dgazs(:,:) = 0.0
125    ! call microphysics
126
127    IF (callclouds) THEN ! call clouds
128      IF(.NOT.mm_muphys(dm0as,dm3as,dm0af,dm3af,dm0n,dm3n,dm3i,dgazs)) &
129        call abort_program(error("mm_muphys aborted -> initialization not done !",-1))
130    ELSE
131      IF (.NOT.mm_muphys(dm0as,dm3as,dm0af,dm3af)) &
132        call abort_program(error("mm_muphys aborted -> initialization not done !",-1))
133    ENDIF
134
135    ! Convert tracers back to intensives ( except for gazs where we work with molar mass ratio )
136    ! We suppose a given order of tracers !
137
138    zdq(ilon,:,1) = dm0as(:) / int2ext(:)
139    zdq(ilon,:,2) = dm3as(:) / int2ext(:)
140    zdq(ilon,:,3) = dm0af(:) / int2ext(:)
141    zdq(ilon,:,4) = dm3af(:) / int2ext(:)
142   
143    if (callclouds) then ! if call clouds
144      zdq(ilon,:,5) = dm0n(:) / int2ext(:)
145      zdq(ilon,:,6) = dm3n(:) / int2ext(:)
146      do i=1,nices
147        zdq(ilon,:,6+i) = dm3i(:,nices) / int2ext(:)
148        zdq(ilon,:,ices_indx(i)) = dgazs(:,i)  / rat_mmol(ices_indx(i)) ! For gazs we work on the full tracer array !!
149        ! We use the molar mass ratio from GCM in case there is discrepancy with the mm one
150      enddo
151    endif
152
153  END DO ! loop on ilon
154
155END SUBROUTINE calmufi
Note: See TracBrowser for help on using the repository browser.