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

Last change on this file since 374 was 135, checked in by aslmd, 14 years ago

CHANGEMENT ARBORESCENCE ETAPE 2 -- NON COMPLET

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