/[MITgcm]/MITgcm/pkg/fizhi/update_earth_exports.F
ViewVC logotype

Diff of /MITgcm/pkg/fizhi/update_earth_exports.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph | View Patch Patch

revision 1.10 by molod, Wed Jun 16 19:19:49 2004 UTC revision 1.17 by molod, Mon Jul 26 20:15:05 2004 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    
4    #include "FIZHI_OPTIONS.h"
5         subroutine update_earth_exports (myTime, myIter, myThid)         subroutine update_earth_exports (myTime, myIter, myThid)
6  c----------------------------------------------------------------------  c----------------------------------------------------------------------
7  c  Subroutine update_earth_exports - 'Wrapper' routine to update  c  Subroutine update_earth_exports - 'Wrapper' routine to update
# Line 14  c        getemiss  (Set the surface emis Line 15  c        getemiss  (Set the surface emis
15  c                              and the snow depth)  c                              and the snow depth)
16  c-----------------------------------------------------------------------  c-----------------------------------------------------------------------
17         implicit none         implicit none
 #include "CPP_OPTIONS.h"  
18  #include "SIZE.h"  #include "SIZE.h"
19    #include "GRID.h"
20  #include "fizhi_land_SIZE.h"  #include "fizhi_land_SIZE.h"
21  #include "fizhi_SIZE.h"  #include "fizhi_SIZE.h"
22  #include "fizhi_coms.h"  #include "fizhi_coms.h"
23    #include "chronos.h"
24  #include "gridalt_mapping.h"  #include "gridalt_mapping.h"
25  #include "fizhi_land_coms.h"  #include "fizhi_land_coms.h"
26  #include "fizhi_earth_coms.h"  #include "fizhi_earth_coms.h"
# Line 27  c--------------------------------------- Line 29  c---------------------------------------
29    
30        integer myTime, myIter, myThid        integer myTime, myIter, myThid
31    
32          logical alarm
33          external alarm
34        _RL lats(sNx,sNy), lons(sNx,sNy), cosz(sNx,sNy)        _RL lats(sNx,sNy), lons(sNx,sNy), cosz(sNx,sNy)
35        _RL fraci(sNx,sNy), fracl(sNx,sNy)        _RL fraci(sNx,sNy), fracl(sNx,sNy)
36        _RL ficetile(nchp)        _RL ficetile(nchp)
37        _RL ra        _RL radius
38        integer i, j, L, bi, bj        _RL tmpij(sNx,sNy)
39          _RL tmpchp(nchp)
40          integer i, j, n, bi, bj
41        integer im1, im2, jm1, jm2, idim1, idim2, jdim1, jdim2        integer im1, im2, jm1, jm2, idim1, idim2, jdim1, jdim2
42        integer sec, day, month        integer sec, day, month
43        integer nmonf,ndayf        integer nmonf,ndayf,nsecf
44          nsecf(n) = n/10000*3600 + mod(n,10000)/100* 60 + mod(n,100)
45        nmonf(n) = mod(n,10000)/100        nmonf(n) = mod(n,10000)/100
46        ndayf(n) = mod(n,100)        ndayf(n) = mod(n,100)
47    
# Line 54  c--------------------------------------- Line 61  c---------------------------------------
61        do bi = myBxLo(myThid), myBxHi(myThid)        do bi = myBxLo(myThid), myBxHi(myThid)
62         do j = jm1,jm2         do j = jm1,jm2
63         do i = im1,im2         do i = im1,im2
64          lons(i,j,bi,bj) = xC(i,j,bi,bj)          lons(i,j) = xC(i,j,bi,bj)
65          lats(i,j,bi,bj) = yC(i,j,bi,bj)          lats(i,j) = yC(i,j,bi,bj)
66         enddo         enddo
67         enddo         enddo
68    
69         call get_landfrac(im2,jm2,nSx,nSy,bi,bj,maxtyp,surftype,tilefrac,         call get_landfrac(im2,jm2,nSx,nSy,bi,bj,maxtyp,surftype,tilefrac,
70       .                                                            fracl)       .                                                            fracl)
71    
72         do j = jm1,jm2         do j = jm1,jm2
73         do i = im1,im2         do i = im1,im2
74          if(sea_ice(i,j,bi,bj).gt.0.) then          if(sice(i,j,bi,bj).gt.0.) then
75             fraci(i,j) = 1.             fraci(i,j) = 1.
76          else          else
77             fraci(i,j) = 0.             fraci(i,j) = 0.
# Line 76  C*              Get Leaf-Area-Index and Line 84  C*              Get Leaf-Area-Index and
84  C***********************************************************************  C***********************************************************************
85    
86         if( alarm('turb') .or. alarm('radsw') ) then         if( alarm('turb') .or. alarm('radsw') ) then
87         call getlgr (sec,month,day,chlt,ityp,nchpland,nSx,nSy,bi,bj,         call getlgr (sec,month,day,chlt,ityp,nchpland,nchp,nSx,nSy,bi,bj,
88       .                                                       alai,agrn )       .                                                       alai,agrn )
89         endif         endif
90    
# Line 85  C                      Compute Surface A Line 93  C                      Compute Surface A
93  C **********************************************************************  C **********************************************************************
94    
95         if( alarm('radsw') ) then         if( alarm('radsw') ) then
96          call astro(nymd,nhms,lats,lons,im2*jm2,cosz,ra)          call astro(nymd,nhms,lats,lons,im2*jm2,cosz,radius)
97          call getalb(sec,month,day,cosz,snodep,fraci,fracl,im2,jm2,nchp,          call getalb(sec,month,day,cosz,snodep,fraci,fracl,im2,jm2,nchp,
98       .             nchpland,nSx,nSy,bi,bj,igrd,ityp,chfr,chlt,alai,agrn,       .    nchptot,nchpland,nSx,nSy,bi,bj,igrd,ityp,chfr,chlt,alai,agrn,
99       .             albvisdr,albvisdf,albnirdr,albnirdf )       .    albvisdr,albvisdf,albnirdr,albnirdf )
100         endif         endif
101    
102    
# Line 110  C*************************************** Line 118  C***************************************
118    
119         do j = jm1,jm2         do j = jm1,jm2
120         do i = im1,im2         do i = im1,im2
121          tgz(i,j,bi,bj) = 0.          tmpij(i,j) = 0.
122           enddo
123         enddo         enddo
124           do i = 1,nchp
125            tmpchp(i) = tcanopy(i,bi,bj)
126         enddo         enddo
127         call msc2grd(igrd(1,bi,bj),chfr(1,bi,bj),tcanopy(1,bi,bj),         call msc2grd(igrd(1,bi,bj),chfr(1,bi,bj),tmpchp,
128       .                           nchp,nchp,fracl,tgz(1,bi,bj),im2,jm2)       .                           nchp,nchptot,fracl,tmpij,im2,jm2)
129         do j = jm1,jm2         do j = jm1,jm2
130         do i = im1,im2         do i = im1,im2
131          if(fracl(i,j).lt.0.3.and.sea_ice(i,j,bi,bj).eq.0.0)          tgz(i,j,bi,bj) = tmpij(i,j)
132            if(fracl(i,j).lt.0.3.and.sice(i,j,bi,bj).eq.0.0)
133       .                                 tgz(i,j,bi,bj) = sst(i,j,bi,bj)       .                                 tgz(i,j,bi,bj) = sst(i,j,bi,bj)
134         enddo         enddo
135         enddo         enddo
# Line 149  C     ANIRDF:   near infra-red, diffuse Line 161  C     ANIRDF:   near infra-red, diffuse
161  C*******************************************************************  C*******************************************************************
162    
163        IMPLICIT NONE        IMPLICIT NONE
 #include "CPP_EEOPTIONS.h"  
164    
165        INTEGER IRUN        INTEGER IRUN
166        _RL AVISDR  (IRUN), ANIRDR (IRUN), AVISDF (IRUN), ANIRDF (IRUN),        _RL AVISDR  (IRUN), ANIRDR (IRUN), AVISDF (IRUN), ANIRDF (IRUN)
167       `       VLAI   (IRUN),   VGRN (IRUN),   ZTH  (IRUN),    SNW (IRUN)        _RL VLAI(IRUN),VGRN (IRUN), SNW(IRUN)
168          _RL ZTH(IRUN)
169        INTEGER ITYP (IRUN)        INTEGER ITYP (IRUN)
170    
171        _RL ALVDRS,  ALIDRS        _RL ALVDRS,  ALIDRS
# Line 209  C                  9:  GLACIER Line 221  C                  9:  GLACIER
221  C                 10:  DARK DESERT  C                 10:  DARK DESERT
222  C  C
223    
224          INTEGER I, LAI
225  * [ Definition of Variables: ]        _RL FAC,GAMMA,BETA,ALPHA,DX,DY,ALA,GRN (2),SNWALB(4,NTYPS)
226  *        _RL COEFF
         INTEGER I, LAI  
   
         _RL FAC,               GAMMA,          BETA,          ALPHA,  
      `       DX,                DY,             ALA,           GRN (2),  
      `       SNWALB (4, NTYPS), SNWMID (NTYPS)  
   
 * [ Definition of Functions: ]  
 *  
         _RL COEFF  
   
 C   Constants used in albedo calculations:  
227    
228        _RL ALVDR (NLAI, 2, NTYPS)        _RL ALVDR (NLAI, 2, NTYPS)
229        _RL BTVDR (NLAI, 2, NTYPS)        _RL BTVDR (NLAI, 2, NTYPS)
# Line 620  C**** ---------------------------------- Line 621  C**** ----------------------------------
621    
622        DATA GRN /0.33, 0.67/        DATA GRN /0.33, 0.67/
623    
624        include 'snwmid.h'  #include "snwmid.h"
625        DATA SNWALB /.65, .38, .65, .38,        DATA SNWALB /.65, .38, .65, .38,
626       *             .65, .38, .65, .38,       *             .65, .38, .65, .38,
627       *             .65, .38, .65, .38,       *             .65, .38, .65, .38,
# Line 633  C**** ---------------------------------- Line 634  C**** ----------------------------------
634       &             .65, .38, .65, .38       &             .65, .38, .65, .38
635       `            /       `            /
636    
637  #if CRAY  #ifdef CRAY
638  #if f77  #ifdef f77
639  cfpp$ expand (coeff)  cfpp$ expand (coeff)
640  #endif  #endif
641  #endif  #endif
# Line 675  cfpp$ expand (coeff) Line 676  cfpp$ expand (coeff)
676        RETURN        RETURN
677        END        END
678        FUNCTION COEFF(TABLE, NTABL, LAI ,DX, DY)        FUNCTION COEFF(TABLE, NTABL, LAI ,DX, DY)
 #include "CPP_EEOPTIONS.h"  
679                    
680        INTEGER NTABL, LAI        INTEGER NTABL, LAI
681          _RL coeff
682        _RL TABLE (NTABL, 2), DX, DY        _RL TABLE (NTABL, 2), DX, DY
683    
684        COEFF = (TABLE(LAI,  1)        COEFF = (TABLE(LAI,  1)
# Line 689  cfpp$ expand (coeff) Line 689  cfpp$ expand (coeff)
689        RETURN        RETURN
690        END        END
691    
692        SUBROUTINE GETLGR(sec,IMON,IDAY,ALAT,ITYP,NCHPS,nSx,nSy,bi,bj,        SUBROUTINE GETLGR(sec,IMON,IDAY,ALAT,ITYP,NCHPS,nchpdim,
693       .                                                      ALAI,AGRN)       .    nSx,nSy,bi,bj,ALAI,AGRN)
694  C*********************************************************************  C*********************************************************************
695        implicit none        implicit none
 #include "CPP_EEOPTIONS.h"  
696    
697        integer ntyps        integer ntyps
698        _RL one,daylen        _RL one,daylen
# Line 701  C*************************************** Line 700  C***************************************
700        parameter (one = 1.)        parameter (one = 1.)
701        parameter (daylen = 86400.)        parameter (daylen = 86400.)
702    
703        integer sec, imon, iday, nchps, nSx, nSy, bi, bj        integer sec, imon, iday, nchps, nchpdim, nSx, nSy, bi, bj
704        _RL ALAI(NCHPS,nSx,nSy), AGRN(NCHPS,nSx,nSy)        _RL ALAI(nchpdim,nSx,nSy), AGRN(nchpdim,nSx,nSy)
705        _RL ALAT(NCHPS)        _RL ALAT(nchpdim)
706        integer ITYP(NCHPS,nSx,nSy)        integer ITYP(nchpdim,nSx,nSy)
707    
708        integer i,midmon,midm,midp,id,k1,k2,kk1,kk2        integer i,midmon,midm,midp,id,k1,k2,kk1,kk2
709        _RL fac        _RL fac
# Line 807  C*************************************** Line 806  C***************************************
806        END        END
807    
808        subroutine getalb(sec,month,day,cosz,snodep,fraci,fracg,im,jm,        subroutine getalb(sec,month,day,cosz,snodep,fraci,fracg,im,jm,
809       .                  nchp,nchpland,nSx,nSy,bi,bj,igrd,ityp,chfr,chlt,       .        nchp,nchptot,nchpland,nSx,nSy,bi,bj,igrd,ityp,chfr,chlt,
810       .                  alai,agrn,albvr,albvf,albnr,albnf)       .        alai,agrn,albvr,albvf,albnr,albnf)
811  C***********************************************************************  C***********************************************************************
812  C  PURPOSE  C  PURPOSE
813  C     To act as an interface to routine sibalb, which calculates  C     To act as an interface to routine sibalb, which calculates
# Line 847  C albnf    - real array [im,jm] of near- Line 846  C albnf    - real array [im,jm] of near-
846  C  C
847  C***********************************************************************  C***********************************************************************
848        implicit none        implicit none
 #include "CPP_EEOPTIONS.h"  
849    
850        integer sec,month,day,im,jm,nchp,nchpland,nSx,nSy,bi,bj        integer sec,month,day,im,jm,nchp,nchptot,nchpland,nSx,nSy,bi,bj
851        _RL cosz(im,jm),fraci(im,jm),fracg(im,jm)        _RL cosz(im,jm),fraci(im,jm),fracg(im,jm)
852        _RL snodep(nchp,nSx,nSy),chfr(nchp,nSx,nSy),chlt(nchp,nSx,nSy)        _RL snodep(nchp,nSx,nSy),chfr(nchp,nSx,nSy),chlt(nchp,nSx,nSy)
853        integer igrd(nchp,nSx,nSy),ityp(nchp,nSx,nSy)        integer igrd(nchp,nSx,nSy),ityp(nchp,nSx,nSy)
# Line 868  C*************************************** Line 866  C***************************************
866    
867        _RL alboc(im,jm)        _RL alboc(im,jm)
868        _RL AVISDR(nchp),ANIRDR(nchp),AVISDF(nchp)        _RL AVISDR(nchp),ANIRDR(nchp),AVISDF(nchp)
869        _RL ANIRDF(nchp),zenith(nchp)        _RL ANIRDF(nchp)
870          _RL zenith(nchp)
871          _RL tmpij(im,jm)
872        integer i,j        integer i,j
873    
874        DO I=1,IM        DO I=1,IM
875        DO J=1,JM        DO J=1,JM
876         ALBOC(I,J) = A0 + (A1 + (A2 +  A3*cosz(I,J))*cosz(I,J))*cosz(I,J)         ALBOC(I,J) = A0 + (A1 + (A2 +  A3*cosz(I,J))*cosz(I,J))*cosz(I,J)
877         ALBVR(I,J) = ALBSI * FRACI(I,J) + ALBOC(I,J) * (ONE-FRACI(I,J))         ALBVR(I,J,bi,bj) = ALBSI*FRACI(I,J) + ALBOC(I,J)*(ONE-FRACI(I,J))
878         ALBNR(I,J) = ALBVR(I,J)         ALBNR(I,J,bi,bj) = ALBVR(I,J,bi,bj)
879         ALBVF(I,J) = ALBSI * FRACI(I,J) + OCNALB * (ONE-FRACI(I,J))         ALBVF(I,J,bi,bj) = ALBSI * FRACI(I,J) + OCNALB * (ONE-FRACI(I,J))
880         ALBNF(I,J) = ALBVF(I,J)         ALBNF(I,J,bi,bj) = ALBVF(I,J,bi,bj)
881        ENDDO        ENDDO
882        ENDDO        ENDDO
   
883    
884  C and now some conversions from grid space to tile space before sibalb  C and now some conversions from grid space to tile space before sibalb
885    
# Line 890  C and now call sibalb Line 889  C and now call sibalb
889    
890        call sibalb(avisdr,anirdr,avisdf,anirdf,alai(1,bi,bj),        call sibalb(avisdr,anirdr,avisdf,anirdf,alai(1,bi,bj),
891       .  agrn(1,bi,bj),zenith,snodep(1,bi,bj),ityp(1,bi,bj),nchpland)       .  agrn(1,bi,bj),zenith,snodep(1,bi,bj),ityp(1,bi,bj),nchpland)
892    
893  C finally some transformations back to grid space for albedos  C finally some transformations back to grid space for albedos
894    
895          print *,' In getalb, chfr: '
896          print *,(chfr(i,1,1),i=1,nchptot)
897    
898          DO I=1,IM
899          DO J=1,JM
900           tmpij(i,j) = albvr(i,j,bi,bj)
901          ENDDO
902          ENDDO
903        call msc2grd(igrd(1,bi,bj),chfr(1,bi,bj),avisdr,nchp,nchpland,        call msc2grd(igrd(1,bi,bj),chfr(1,bi,bj),avisdr,nchp,nchpland,
904       .                                      fracg,albvr(1,bi,bj),im,jm)       .                                     fracg,tmpij,im,jm)
905    
906          DO I=1,IM
907          DO J=1,JM
908           albvr(i,j,bi,bj) = tmpij(i,j)
909          ENDDO
910          ENDDO
911          DO I=1,IM
912          DO J=1,JM
913           tmpij(i,j) = albvf(i,j,bi,bj)
914          ENDDO
915          ENDDO
916        call msc2grd(igrd(1,bi,bj),chfr(1,bi,bj),avisdf,nchp,nchpland,        call msc2grd(igrd(1,bi,bj),chfr(1,bi,bj),avisdf,nchp,nchpland,
917       .                                      fracg,albvf(1,bi,bj),im,jm)       .                                     fracg,tmpij,im,jm)
918          DO I=1,IM
919          DO J=1,JM
920           albvf(i,j,bi,bj) = tmpij(i,j)
921          ENDDO
922          ENDDO
923          DO I=1,IM
924          DO J=1,JM
925           tmpij(i,j) = albnr(i,j,bi,bj)
926          ENDDO
927          ENDDO
928        call msc2grd(igrd(1,bi,bj),chfr(1,bi,bj),anirdr,nchp,nchpland,        call msc2grd(igrd(1,bi,bj),chfr(1,bi,bj),anirdr,nchp,nchpland,
929       .                                      fracg,albnr(1,bi,bj),im,jm)       .                                     fracg,tmpij,im,jm)
930          DO I=1,IM
931          DO J=1,JM
932           albnr(i,j,bi,bj) = tmpij(i,j)
933          ENDDO
934          ENDDO
935          DO I=1,IM
936          DO J=1,JM
937           tmpij(i,j) = albnf(i,j,bi,bj)
938          ENDDO
939          ENDDO
940        call msc2grd(igrd(1,bi,bj),chfr(1,bi,bj),anirdf,nchp,nchpland,        call msc2grd(igrd(1,bi,bj),chfr(1,bi,bj),anirdf,nchp,nchpland,
941       .                                      fracg,albnf(1,bi,bj),im,jm)       .                                     fracg,tmpij,im,jm)
942          DO I=1,IM
943          DO J=1,JM
944           albnf(i,j,bi,bj) = tmpij(i,j)
945          ENDDO
946          ENDDO
947    
948        return        return
949        end        end
# Line 936  C emiss    - real array [im,jm,10,nSx,nS Line 979  C emiss    - real array [im,jm,10,nSx,nS
979  C  C
980  C***********************************************************************  C***********************************************************************
981        implicit none        implicit none
 #include "CPP_EEOPTIONS.h"  
982        integer im,jm,nchp,nSx,nSy,bi,bj        integer im,jm,nchp,nSx,nSy,bi,bj
983        _RL fracg(im,jm)        _RL fracg(im,jm)
984        _RL chfr(nchp,nSx,nSy)        _RL chfr(nchp,nSx,nSy)
985        integer igrd(nchp,nSx,nSy), ityp(nchp,nSx,nSy)        integer igrd(nchp,nSx,nSy), ityp(nchp,nSx,nSy)
986        _RL snowdep(nchp,nSx,nSy),fraci(nchp)        _RL snowdep(nchp,nSx,nSy)
987          _RL fraci(nchp)
988        _RL emiss(im,jm,10,nSx,nSy)        _RL emiss(im,jm,10,nSx,nSy)
989    
990        _RL emisstile(nchp,10)        _RL emisstile(nchp,10)
991          _RL tmpij(im,jm)
992        integer i,j,k,n        integer i,j,k,n
993    
994        do i = 1,10        do i = 1,10
# Line 963  c -------------------------------------- Line 1007  c --------------------------------------
1007        do k = 1,10        do k = 1,10
1008        do j = 1,jm        do j = 1,jm
1009        do i = 1,im        do i = 1,im
1010        emiss(i,j,k) = 0.0         tmpij(i,j) = 0.0
1011        enddo        enddo
1012        enddo        enddo
1013        call msc2grd(igrd(1,bi,bj),chfr(1,bi,bj),emisstile(1,k),nchp,nchp,        call msc2grd(igrd(1,bi,bj),chfr(1,bi,bj),emisstile(1,k),nchp,nchp,
1014       .      fracg,emiss(1,1,k,bi,bj),im,jm)       .      fracg,tmpij,im,jm)
1015          do j = 1,jm
1016          do i = 1,im
1017           emiss(i,j,k,bi,bj) = tmpij(i,j)
1018          enddo
1019          enddo
1020        enddo        enddo
1021    
1022        return        return
# Line 975  c -------------------------------------- Line 1024  c --------------------------------------
1024    
1025        subroutine emissivity (snowdepth,fraci,numpts,ityp,newemis)        subroutine emissivity (snowdepth,fraci,numpts,ityp,newemis)
1026        implicit none        implicit none
 #include "CPP_EEOPTIONS.h"  
1027        integer numpts        integer numpts
1028        integer   ityp(numpts)        integer   ityp(numpts)
1029        _RL snowdepth(numpts),fraci(numpts)        _RL snowdepth(numpts)
1030        _RL   newemis(numpts,10)        _RL fraci(numpts)
1031          _RL newemis(numpts,10)
1032    
1033        _RL emis(12,11)        _RL emis(12,11)
       _RL snwmid(10)  
1034        _RL fac        _RL fac
1035        integer i,j        integer i,j
1036    
# Line 1073  C water Line 1121  C water
1121       &   0.9788, 0.9833, 0.9819, 0.9820, 0.9835, 0.9865,       &   0.9788, 0.9833, 0.9819, 0.9820, 0.9835, 0.9865,
1122       &   0.9886, 0.9719, 0.9719, 0.9719, 0.9719, 0.9719/       &   0.9886, 0.9719, 0.9719, 0.9719, 0.9719, 0.9719/
1123    
1124        include 'snwmid.h'  #include "snwmid.h"
1125    
1126  c Convert to the 10 bands needed by Chou Radiation  c Convert to the 10 bands needed by Chou Radiation
1127  c ------------------------------------------------  c ------------------------------------------------
# Line 1161  C     To compute the total fraction of l Line 1209  C     To compute the total fraction of l
1209  C  C
1210  C***********************************************************************  C***********************************************************************
1211        implicit none        implicit none
 #include "CPP_EEOPTIONS.h"  
1212    
1213        integer i,j,nSx,nSy,bi,bj,maxtyp        integer im,jm,nSx,nSy,bi,bj,maxtyp
1214        integer surftype(im,jm,nSx,nSy)        integer surftype(im,jm,maxtyp,nSx,nSy)
1215        _RL surftype(im,jm,nSx,nSy)        _RL tilefrac(im,jm,maxtyp,nSx,nSy)
1216        _RL frac(im,jm)        _RL frac(im,jm)
1217    
1218        integer  i,j,k        integer  i,j,k
# Line 1179  C*************************************** Line 1226  C***************************************
1226        do k=1,maxtyp        do k=1,maxtyp
1227        do j=1,jm        do j=1,jm
1228        do i=1,im        do i=1,im
1229        if(surftype(i,j,k,bi,bj).lt.100.and.        if( (surftype(i,j,k,bi,bj).lt.100.).and.
1230                                         tilefrac(i,j,k,bi,bj).gt.0.0)then       .                               (tilefrac(i,j,k,bi,bj).gt.0.0))then
1231         frac(i,j) = frac(i,j) + tilefrac(i,j,k,bi,bj)         frac(i,j) = frac(i,j) + tilefrac(i,j,k,bi,bj)
1232        endif        endif
1233        enddo        enddo

Legend:
Removed from v.1.10  
changed lines
  Added in v.1.17

  ViewVC Help
Powered by ViewVC 1.1.22