source: trunk/LMDZ.GENERIC/libf/phystd/surfini.F @ 1149

Last change on this file since 1149 was 837, checked in by aslmd, 12 years ago

LMDZ.GENERIC. Corrected problems with allocated arrays in start2archive and newstart. Applied a workaround to make those work without tracers (-cpp NOTRAC -- perhaps there is a better solution). Checked that everything works in debug mode.

File size: 2.3 KB
RevLine 
[787]1      SUBROUTINE surfini(ngrid,nq,qsurf,psolaralb)
2
3      USE surfdat_h
4      USE tracer_h
5
[135]6      IMPLICIT NONE
7c=======================================================================
8c
9c   creation des calottes pour l'etat initial
10c
11c=======================================================================
12c-----------------------------------------------------------------------
13c   Declarations:
14c   -------------
15#include "dimensions.h"
16#include "dimphys.h"
17#include "callkeys.h"
18c
19      INTEGER ngrid,ig,icap
[787]20      INTEGER nq
[135]21      REAL  piceco2(ngrid),psolaralb(ngrid)
[787]22      REAL qsurf(ngrid,nq) !tracer on surface (kg/m2)
[135]23
24      EXTERNAL ISMIN,ISMAX
25      INTEGER ISMIN,ISMAX
26c
27c=======================================================================
28
29c
30c     calcul de piceco2 (kg/m2) a l'etat initial
31c     ------------------------------------------
32
33      DO ig=1,ngrid
34         psolaralb(ig)=albedodat(ig)
35!         psolaralb(ig,2)=albedodat(ig)
36      ENDDO
37
38      PRINT*,'surfini: minimum des donnees albedo',
39     s     albedodat(ISMIN(ngrid,albedodat,1))
40      PRINT*,'surfini: maximum des donnees albedo',
41     s     albedodat(ISMAX(ngrid,albedodat,1))
42
43c      calcul de psolaralb
44c      -------------------
45!      DO ig=1,ngrid
46c        IF (water) THEN
[787]47c          if (qsurf(ig,nq).gt.0.005) then
[135]48c             psolaralb(ig,1) = 0.4
49c             psolaralb(ig,2) = 0.4
50c           endif
51c         ENDIF
52!      ENDDO ! of DO ig=1,ngrid     
53c IF there is more than 5 pr. um of h2o ice but no C02 ice, surface albedo is set to 0.4.
54
55      if (igcm_co2_ice.ne.0) then
56! Change Albedo if there is CO2 ice on the surface
57        DO ig=1,ngrid
58          IF (qsurf(ig,igcm_co2_ice) .GT. 0.) THEN
[837]59             !!!! no good in parallel
[135]60             IF(ig.GT.ngrid/2+1) THEN
61                icap=2
62             ELSE
63                icap=1
64             ENDIF
65             psolaralb(ig) = albedice(icap)
66!             psolaralb(ig,2) =  albedice(icap)
67          END IF
68        ENDDO ! of DO ig=1,ngrid     
69      else
70        write(*,*) "surfini: No CO2 ice tracer on surface  ..."
71        write(*,*) "         and therefore no albedo change."
72      endif
73
74      PRINT*,'surfini: minimum des donnees albedo',
75     s     psolaralb(ISMIN(ngrid,psolaralb,1))
76      PRINT*,'surfini: maximum des donnees albedo',
77     s     psolaralb(ISMAX(ngrid,psolaralb,1))
78
79      RETURN
80      END
Note: See TracBrowser for help on using the repository browser.