source: dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/climoz_mod.f90 @ 3983

Last change on this file since 3983 was 3895, checked in by ymipsl, 9 years ago

Make LMDZ5 be compliant to generate initiale state and compute in openMP mode suing unstructured grid.

YM

File size: 2.0 KB
Line 
1! This module may contains all subroutine and function used
2! for ozone climatology
3! code re-design is needed
4
5MODULE climoz_mod
6
7
8
9
10
11CONTAINS
12
13
14  SUBROUTINE create_climoz(read_climoz)
15  USE mod_grid_phy_lmdz, ONLY :  grid_type, unstructured
16  USE regr_lat_time_climoz_m
17  USE mod_phys_lmdz_para
18  USE XIOS
19  IMPLICIT NONE
20  INTEGER, INTENT(IN)  :: read_climoz
21
22    !--- OZONE CLIMATOLOGY
23    IF (grid_type==unstructured) THEN
24   
25      IF(read_climoz>=1) THEN
26        IF (is_master) CALL regr_lat_time_climoz(read_climoz,.FALSE.)
27        IF (is_omp_master) THEN
28          CALL xios_set_field_attr( "tro3_reg",  enabled=.TRUE.)
29          CALL xios_set_field_attr( "tro3_read", enabled=.TRUE.)
30          IF (read_climoz==2) THEN
31            CALL xios_set_field_attr( "tro3_daylight_reg",  enabled=.TRUE.)
32            CALL xios_set_field_attr( "tro3_daylight_read", enabled=.TRUE.)
33          ENDIF
34        ENDIF
35      ENDIF
36   
37    ENDIF
38
39  END SUBROUTINE create_climoz
40
41
42 
43  SUBROUTINE get_ozone_var(name,press_in_edg,paprs,v3)
44  USE dimphy
45  USE mod_phys_lmdz_para
46  USE xios
47  USE regr1_step_av_m, only: regr1_step_av
48  IMPLICIT NONE
49    CHARACTER(LEN=*), INTENT(in):: name(:) ! of the NetCDF variables     
50    REAL, INTENT(IN):: press_in_edg(:)    ! edges of pressure intervals for input data, in Pa, in strictly ascending order
51    REAL, INTENT(IN):: paprs(:, :) ! (klon, klev + 1)
52    REAL, INTENT(OUT):: v3(:, :, :) ! (klon, klev, size(name))
53   
54    REAL  :: v1_mpi(klon_mpi, size(press_in_edg) - 1, size(v3,3))
55    REAL  :: v1(klon, size(press_in_edg) - 1, size(v3,3))
56    INTEGER :: m,i
57   
58    DO m=1,size(name)
59      IF (is_omp_master) CALL xios_recv_field(name(m),v1_mpi(:,:,m))
60      CALL scatter_omp(v1_mpi,v1)
61      ! Regrid in pressure at each horizontal position:
62      DO i = 1, klon
63         v3(i, klev:1:-1, m) = regr1_step_av(v1(i,:,m), press_in_edg, &
64              paprs(i, klev+1:1:-1))
65         ! (invert order of indices because "paprs" is in descending order)
66      END DO
67    ENDDO
68
69  END SUBROUTINE get_ozone_var 
70 
71
72END MODULE climoz_mod
Note: See TracBrowser for help on using the repository browser.