/[lmdze]/trunk/libf/phylmd/Interface_surf/interfsur_lim.f90
ViewVC logotype

Contents of /trunk/libf/phylmd/Interface_surf/interfsur_lim.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 54 - (show annotations)
Tue Dec 6 15:07:04 2011 UTC (12 years, 5 months ago) by guez
File size: 4446 byte(s)
Removed Numerical Recipes procedure "ran1". Replaced calls to "ran1"
in "inidissip" by calls to intrinsic procedures.

Split file "interface_surf.f90" into a file with a module containing
only variables, "interface_surf", and single-procedure files. Gathered
files into directory "Interface_surf".

Added argument "cdivu" to "gradiv" and "gradiv2", "cdivh" to
"divgrad2" and "divgrad", and "crot" to "nxgraro2" and
"nxgrarot". "dissip" now uses variables "cdivu", "cdivh" and "crot"
from module "inidissip_m", so it can pass them to "gradiv2",
etc. Thanks to this modification, we avoid a circular dependency
betwwen "inidissip.f90" and "gradiv2.f90", etc. The value -1. used by
"gradiv2", for instance, during computation of eigenvalues is not the
value "cdivu" computed by "inidissip".

Extracted procedure "start_inter_3d" from module "startdyn", to its
own module.

In "inidissip", unrolled loop on "ii". I find it clearer now.

Moved variables "matriceun", "matriceus", "matricevn", "matricevs",
"matrinvn" and "matrinvs" from module "parafilt" to module
"inifilr_m". Moved variables "jfiltnu", "jfiltnv", "jfiltsu",
"jfiltsv" from module "coefils" to module "inifilr_m".

1 module interfsur_lim_m
2
3 implicit none
4
5 contains
6
7 SUBROUTINE interfsur_lim(itime, dtime, jour, &
8 klon, nisurf, knon, knindex, &
9 debut, &
10 lmt_alb, lmt_rug)
11
12 ! Cette routine sert d'interface entre le modèle atmosphérique et
13 ! un fichier de conditions aux limites.
14
15 ! L. Fairhead 02/2000
16
17 use abort_gcm_m, only: abort_gcm
18
19 ! Parametres d'entree
20 ! input:
21 ! itime numero du pas de temps courant
22 ! dtime pas de temps de la physique (en s)
23 ! jour jour a lire dans l'annee
24 ! nisurf index de la surface a traiter (1 = sol continental)
25 ! knon nombre de points dans le domaine a traiter
26 ! knindex index des points de la surface a traiter
27 ! klon taille de la grille
28 ! debut logical: 1er appel a la physique (initialisation)
29 integer, intent(IN) :: itime
30 real , intent(IN) :: dtime
31 integer, intent(IN) :: jour
32 integer, intent(IN) :: nisurf
33 integer, intent(IN) :: knon
34 integer, intent(IN) :: klon
35 integer, dimension(klon), intent(in) :: knindex
36 logical, intent(IN) :: debut
37
38 ! Parametres de sortie
39 ! output:
40 ! lmt_sst SST lues dans le fichier de CL
41 ! lmt_alb Albedo lu
42 ! lmt_rug longueur de rugosité lue
43 ! pctsrf_new sous-maille fractionnelle
44 real, intent(out), dimension(klon) :: lmt_alb
45 real, intent(out), dimension(klon) :: lmt_rug
46
47 ! Variables locales
48 integer :: ii
49 integer, save :: lmt_pas ! frequence de lecture des conditions limites
50 ! (en pas de physique)
51 logical, save :: deja_lu_sur! pour indiquer que le jour a lire a deja
52 ! lu pour une surface precedente
53 integer, save :: jour_lu_sur
54 integer :: ierr
55 character (len = 20) :: modname = 'interfsur_lim'
56 character (len = 80) :: abort_message
57 logical, save :: newlmt = .false.
58 logical, save :: check = .false.
59 ! Champs lus dans le fichier de CL
60 real, allocatable , save, dimension(:) :: alb_lu, rug_lu
61
62 ! quelques variables pour netcdf
63
64 include "netcdf.inc"
65 integer , save :: nid, nvarid
66 integer, dimension(2), save :: start, epais
67
68 !------------------------------------------------------------
69
70 if (debut) then
71 lmt_pas = nint(86400./dtime * 1.0) ! pour une lecture une fois par jour
72 jour_lu_sur = jour - 1
73 allocate(alb_lu(klon))
74 allocate(rug_lu(klon))
75 endif
76
77 if ((jour - jour_lu_sur) /= 0) deja_lu_sur = .false.
78
79 if (check) write(*, *)modname, ':: jour_lu_sur, deja_lu_sur', jour_lu_sur, &
80 deja_lu_sur
81 if (check) write(*, *)modname, ':: itime, lmt_pas', itime, lmt_pas
82
83 ! Tester d'abord si c'est le moment de lire le fichier
84 if (mod(itime-1, lmt_pas) == 0 .and. .not. deja_lu_sur) then
85
86 ! Ouverture du fichier
87
88 ierr = NF_OPEN ('limit.nc', NF_NOWRITE, nid)
89 if (ierr.NE.NF_NOERR) then
90 abort_message &
91 = 'Pb d''ouverture du fichier de conditions aux limites'
92 call abort_gcm(modname, abort_message, 1)
93 endif
94
95 ! La tranche de donnees a lire:
96
97 start(1) = 1
98 start(2) = jour
99 epais(1) = klon
100 epais(2) = 1
101
102 ! Lecture Albedo
103
104 ierr = NF_INQ_VARID(nid, 'ALB', nvarid)
105 if (ierr /= NF_NOERR) then
106 abort_message = 'Le champ <ALB> est absent'
107 call abort_gcm(modname, abort_message, 1)
108 endif
109 ierr = NF_GET_VARA_REAL(nid, nvarid, start, epais, alb_lu)
110 if (ierr /= NF_NOERR) then
111 abort_message = 'Lecture echouee pour <ALB>'
112 call abort_gcm(modname, abort_message, 1)
113 endif
114
115 ! Lecture rugosité
116
117 ierr = NF_INQ_VARID(nid, 'RUG', nvarid)
118 if (ierr /= NF_NOERR) then
119 abort_message = 'Le champ <RUG> est absent'
120 call abort_gcm(modname, abort_message, 1)
121 endif
122 ierr = NF_GET_VARA_REAL(nid, nvarid, start, epais, rug_lu)
123 if (ierr /= NF_NOERR) then
124 abort_message = 'Lecture echouee pour <RUG>'
125 call abort_gcm(modname, abort_message, 1)
126 endif
127
128
129 ! Fin de lecture
130
131 ierr = NF_CLOSE(nid)
132 deja_lu_sur = .true.
133 jour_lu_sur = jour
134 endif
135
136 ! Recopie des variables dans les champs de sortie
137
138 !!$ lmt_alb = 0.0
139 !!$ lmt_rug = 0.0
140 lmt_alb = 999999.
141 lmt_rug = 999999.
142 DO ii = 1, knon
143 lmt_alb(ii) = alb_lu(knindex(ii))
144 lmt_rug(ii) = rug_lu(knindex(ii))
145 enddo
146
147 END SUBROUTINE interfsur_lim
148
149 end module interfsur_lim_m

  ViewVC Help
Powered by ViewVC 1.1.21