SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
ol_read_atm.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6 SUBROUTINE ol_read_atm (&
7  hsurf_filetype, hforcing_filetype, kforc_step, &
8  pta,pqa,pwind,pdir_sw,psca_sw,plw,psnow,prain,pps,&
9  pco2,pdir,olimit_qair )
10 !**************************************************************************
11 !
12 !! PURPOSE
13 !! -------
14 ! Read in the netcdf file the atmospheric forcing for the actual time
15 ! step KFORC_STEP, and for the next one.
16 ! The two time step are needed for the time interpolation of the
17 ! forcing.
18 ! If the end of the file is reached, set the two step to the last
19 ! values.
20 ! Return undef value if the variable is not present
21 !!
22 !!** METHOD
23 !! ------
24 !!
25 !! EXTERNAL
26 !! --------
27 !!
28 !! IMPLICIT ARGUMENTS
29 !! ------------------
30 !!
31 !! REFERENCE
32 !! ---------
33 !!
34 !!
35 !! AUTHOR
36 !! ------
37 !! F. Habets *Meteo France*
38 !!
39 !! MODIFICATIONS
40 !! -------------
41 !! Original 06/2003
42 !! P. Le Moigne 10/2004: set XCOUNT to 2 because of revised temporal loop in offline.f90:
43 !! time evolution is done at the end of isba time step so first
44 !! isba computation is done on first forcing time step
45 !! P. Le Moigne 10/2005: consistency checking between orographies read from forcing
46 !! file and from initial file
47 !! B. Decharme 01/2009: Optional, limitation of Qair (<= Qsat(tair))
48 !
49 !
50 !
51 !
52 USE modd_surf_par, ONLY : xundef
53 USE modd_io_surf_ol, ONLY : xstart,xcount,xstride,lpartr
54 !
55 USE modi_ol_read_atm_netcdf
56 USE modi_ol_read_atm_ascii
57 USE modi_ol_read_atm_binary
58 !
59 USE mode_thermos
60 !
61 !
62 USE yomhook ,ONLY : lhook, dr_hook
63 USE parkind1 ,ONLY : jprb
64 !
65 USE modi_abor1_sfx
66 !
67 IMPLICIT NONE
68 !
69 ! global variables
70 !
71 !
72 REAL, DIMENSION(:,:),INTENT(INOUT) :: pta !K
73 REAL, DIMENSION(:,:),INTENT(INOUT) :: pqa
74 REAL, DIMENSION(:,:),INTENT(INOUT) :: pwind
75 REAL, DIMENSION(:,:),INTENT(INOUT) :: pdir_sw
76 REAL, DIMENSION(:,:),INTENT(INOUT) :: psca_sw
77 REAL, DIMENSION(:,:),INTENT(INOUT) :: plw
78 REAL, DIMENSION(:,:),INTENT(INOUT) :: psnow
79 REAL, DIMENSION(:,:),INTENT(INOUT) :: prain
80 REAL, DIMENSION(:,:),INTENT(INOUT) :: pps
81 REAL, DIMENSION(:,:),INTENT(INOUT) :: pco2
82 REAL, DIMENSION(:,:),INTENT(INOUT) :: pdir
83 INTEGER,INTENT(IN) :: kforc_step
84  CHARACTER(LEN=6) ,INTENT(IN) :: hsurf_filetype
85  CHARACTER(LEN=6) ,INTENT(IN) :: hforcing_filetype
86 LOGICAL ,INTENT(IN) :: olimit_qair
87 !
88 REAL, PARAMETER :: ztair = 286.0
89 REAL, PARAMETER :: zpsurf = 101325.0
90 !
91 REAL, DIMENSION(SIZE(PTA,1),SIZE(PTA,2)) :: zwork1, zwork2, zqsat
92 !
93 INTEGER :: jfrc, ifrc, jj, ini, inb
94 !
95 REAL(KIND=JPRB) :: zhook_handle
96 !
97 !
98 !set time variables
99 IF (lhook) CALL dr_hook('OL_READ_ATM',0,zhook_handle)
100 xstart =kforc_step
101 xcount =SIZE(pta,2)
102 xstride=1
103 lpartr=.true.
104 !
105 ! read data
106 !
107 IF (hforcing_filetype == 'NETCDF') THEN
108  CALL ol_read_atm_netcdf(&
109  hsurf_filetype, &
110  pta,pqa,pwind,pdir_sw,psca_sw,plw,psnow,prain,pps,&
111  pco2,pdir )
112 ELSE IF (hforcing_filetype == 'ASCII ') THEN
113  CALL ol_read_atm_ascii(kforc_step, &
114  pta,pqa,pwind,pdir_sw,psca_sw,plw,psnow,prain,pps,&
115  pco2,pdir )
116 ELSE IF (hforcing_filetype == 'BINARY') THEN
117  CALL ol_read_atm_binary(kforc_step, &
118  pta,pqa,pwind,pdir_sw,psca_sw,plw,psnow,prain,pps,&
119  pco2,pdir )
120 ENDIF
121 !
122 ! Assume Qair <= Qsat_air
123 !
124 IF(olimit_qair)THEN
125 !
126  ini = SIZE(pta,1)
127  ifrc = SIZE(pta,2)
128  inb = 0
129 !
130  DO jfrc=1,ifrc
131  DO jj=1,ini
132  IF(pta(jj,jfrc)>0.0.AND.pta(jj,jfrc)/=xundef)THEN
133  inb = inb+1
134  zwork1(jj,jfrc) = pta(jj,jfrc)
135  zwork2(jj,jfrc) = pps(jj,jfrc)
136  ELSE
137  zwork1(jj,jfrc) = ztair
138  zwork2(jj,jfrc) = zpsurf
139  pta(jj,jfrc) = xundef
140  pqa(jj,jfrc) = 0.0
141  ENDIF
142  ENDDO
143  ENDDO
144 !
145  IF(inb==0 .AND. ini/=0)THEN
146  CALL abor1_sfx('OL_READ_ATM: THE FORCING IS UNDEFINED')
147  ENDIF
148 !
149  zqsat(:,:) = qsat(zwork1(:,:),zwork2(:,:))
150 !
151  pqa(:,:) = min(pqa(:,:),zqsat(:,:))
152 !
153 ENDIF
154 !
155 IF (lhook) CALL dr_hook('OL_READ_ATM',1,zhook_handle)
156 !
157 END SUBROUTINE ol_read_atm
subroutine ol_read_atm(HSURF_FILETYPE, HFORCING_FILETYPE, KFORC_STEP, PTA, PQA, PWIND, PDIR_SW, PSCA_SW, PLW, PSNOW, PRAIN, PPS, PCO2, PDIR, OLIMIT_QAIR)
Definition: ol_read_atm.F90:6
subroutine ol_read_atm_binary(KFORC_STEP, PTA, PQA, PWIND, PDIR_SW, PSCA_SW, PLW, PSNOW, PRAIN, PPS, PCO2, PDIR)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine ol_read_atm_ascii(KFORC_STEP, PTA, PQA, PWIND, PDIR_SW, PSCA_SW, PLW, PSNOW, PRAIN, PPS, PCO2, PDIR)
subroutine ol_read_atm_netcdf(HSURF_FILETYPE, PTA, PQA, PWIND, PDIR_SW, PSCA_SW, PLW, PSNOW, PRAIN, PPS, PCO2, PDIR)