Ignore:
Timestamp:
Aug 5, 2009, 4:38:34 PM (15 years ago)
Author:
lguez
Message:

-- Replaced "integer*4" declarations by "integer", "real*8" by

"real(kind=8)" and "real*4" by "real". Note that these are the only
modifications in the files "radiation_AR4.F" and "sw_aeroAR4.F90".

-- Corrected the kind of arguments to "max" and "min".

-- Replaced "nH" edit descriptors, which is a deleted feature in

Fortran 95, by character strings.

-- "regr_lat_time_climoz" now allows the pressure coordinate in the

input file to be in descending order.

-- Replaced call to not standard function "float" by call to intrinsic

function "real".

-- Included file "radepsi.h" in "physiq" was not used. Removed it.

The following set of modifications is related to the management of time.

-- In "gcm", "leapfrog" and "sortvarc0", "day_ini" was defined as 1

plus number of days between the reference date "(annee_ref,
day_ref)" and the first day of the current simulation. Changed
definition: "(annee_ref, day_ini)" is the first day of the current
simulation. There is an accompanying modification for "day_end".

-- Corrected bug in call to "ioconf_startdate" in "gcm".

-- Added call to "ioconf_calendar" in "create_etat0_limit".

Location:
LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar
Files:
12 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/coefpoly.F

    r774 r1220  
    1919c  On en revient a resoudre un systeme de 4 equat.a 4 inconnues a0,a1,a2,a3
    2020
    21       REAL*8 Xf1, Xf2,Xprim1,Xprim2, xtild1,xtild2, xi
    22       REAL*8 Xfout, Xprim
    23       REAL*8 a1,a2,a3,a0, xtil1car, xtil2car,derr,x1x2car
     21      REAL(KIND=8) Xf1, Xf2,Xprim1,Xprim2, xtild1,xtild2, xi
     22      REAL(KIND=8) Xfout, Xprim
     23      REAL(KIND=8) a1,a2,a3,a0, xtil1car, xtil2car,derr,x1x2car
    2424
    2525      xtil1car = xtild1 * xtild1
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/create_etat0_limit.F

    r1114 r1220  
    99       USE phys_state_var_mod     
    1010       USE infotrac
     11#ifdef CPP_IOIPSL
     12       use ioipsl, only: ioconf_calendar
     13#endif
    1114       IMPLICIT NONE
    1215c
     
    4144         call init_const_lmdz(
    4245     $        nbtr,anneeref,dayref,
    43      $        iphysiq,day_step,nday)
     46     $        iphysiq, day_step,nday)
    4447#endif
    4548         print *, 'nbtr =' , nbtr
     
    6063      call InitComgeomphy
    6164     
     65#ifdef CPP_IOIPSL
     66      call ioconf_calendar('360d')
     67#endif
    6268
    6369      WRITE(6,*) '  *********************  '
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/etat0_netcdf.F

    r1154 r1220  
    654654      itau_phy = 0
    655655      iday = dayref +itau/day_step
    656       time = FLOAT(itau-(iday-dayref)*day_step)/day_step
     656      time = real(itau-(iday-dayref)*day_step)/day_step
    657657c     
    658658      IF(time.GT.1)  THEN
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/fxyhyper.F

    r774 r1220  
    4141       REAL rlonu(iip1),xprimu(iip1),rlonv(iip1),xprimv(iip1),
    4242     , rlonm025(iip1),xprimm025(iip1), rlonp025(iip1),xprimp025(iip1)
    43        REAL*8  dxmin, dxmax , dymin, dymax
     43       REAL(KIND=8)  dxmin, dxmax , dymin, dymax
    4444
    4545c   ....   var. locales   .....
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/fyhyp.F

    r764 r1220  
    5050     
    5151       REAL   dzoom
    52        REAL*8 ylat(jjp1), yprim(jjp1)
    53        REAL*8 yuv
    54        REAL*8 yt(0:nmax2)
    55        REAL*8 fhyp(0:nmax2),beta,Ytprim(0:nmax2),fxm(0:nmax2)
     52       REAL(KIND=8) ylat(jjp1), yprim(jjp1)
     53       REAL(KIND=8) yuv
     54       REAL(KIND=8) yt(0:nmax2)
     55       REAL(KIND=8) fhyp(0:nmax2),beta,Ytprim(0:nmax2),fxm(0:nmax2)
    5656       SAVE Ytprim, yt,Yf
    57        REAL*8 Yf(0:nmax2),yypr(0:nmax2)
    58        REAL*8 yvrai(jjp1), yprimm(jjp1),ylatt(jjp1)
    59        REAL*8 pi,depi,pis2,epsilon,y0,pisjm
    60        REAL*8 yo1,yi,ylon2,ymoy,Yprimin,champmin,champmax
    61        REAL*8 yfi,Yf1,ffdy
    62        REAL*8 ypn,deply,y00
     57       REAL(KIND=8) Yf(0:nmax2),yypr(0:nmax2)
     58       REAL(KIND=8) yvrai(jjp1), yprimm(jjp1),ylatt(jjp1)
     59       REAL(KIND=8) pi,depi,pis2,epsilon,y0,pisjm
     60       REAL(KIND=8) yo1,yi,ylon2,ymoy,Yprimin,champmin,champmax
     61       REAL(KIND=8) yfi,Yf1,ffdy
     62       REAL(KIND=8) ypn,deply,y00
    6363       SAVE y00, deply
    6464
     
    6666       INTEGER jpn,jjpn
    6767       SAVE jpn
    68        REAL*8 a0,a1,a2,a3,yi2,heavyy0,heavyy0m
    69        REAL*8 fa(0:nmax2),fb(0:nmax2)
     68       REAL(KIND=8) a0,a1,a2,a3,yi2,heavyy0,heavyy0m
     69       REAL(KIND=8) fa(0:nmax2),fb(0:nmax2)
    7070       REAL y0min,y0max
    7171
    72        REAL*8     heavyside
     72       REAL(KIND=8)     heavyside
    7373
    7474       pi       = 2. * ASIN(1.)
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/gcm.F

    r1201 r1220  
    326326          annee_ref = anneeref
    327327          day_ref = dayref
    328           day_ini = 1
     328          day_ini = dayref
    329329          itau_dyn = 0
    330330          itau_phy = 0
     
    344344
    345345#ifdef CPP_IOIPSL
    346       call ioconf_startdate(annee_ref,0,day_ref, 0.)
     346      call ioconf_startdate(annee_ref,1,day_ref, 0.)
    347347#endif
    348348
     
    436436      WRITE(lunout,300)day_ini,day_end
    437437 300  FORMAT('1'/,15x,'run du jour',i7,2x,'au jour',i7//)
    438       call ju2ymds(jD_ref+day_ini-1,an, mois, jour, heure)
     438      call ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
    439439      write (lunout,301)jour, mois, an
    440       call ju2ymds(jD_ref+day_end-1,an, mois, jour, heure)
     440      call ju2ymds(jD_ref + day_end - day_ref, an, mois, jour, heure)
    441441      write (lunout,302)jour, mois, an
    442442 301  FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/grid_atob.F

    r774 r1220  
    700700      PARAMETER (imtmp=360,jmtmp=180)
    701701      REAL xtmp(imtmp), ytmp(jmtmp)
    702       REAL*8 cham1tmp(imtmp,jmtmp), cham2tmp(imtmp,jmtmp)
     702      REAL(KIND=8) cham1tmp(imtmp,jmtmp), cham2tmp(imtmp,jmtmp)
    703703      REAL zzzz
    704704c
     
    859859              number(ii,jj) = number(ii,jj) + 1.0
    860860              rugs(ii,jj) = rugs(ii,jj)
    861      .                       + LOG(MAX(0.001,cham2tmp(i,j)))
     861     .                       + LOG(MAX(0.001_8,cham2tmp(i,j)))
    862862          ENDIF
    863863          ENDDO
     
    892892         i_proche = ij_proche - (j_proche-1)*imtmp
    893893         PRINT*, "solution:", ij_proche, i_proche, j_proche
    894          rugs(i,j) = LOG(MAX(0.001,cham2tmp(i_proche,j_proche)))
     894         rugs(i,j) = LOG(MAX(0.001_8,cham2tmp(i_proche,j_proche)))
    895895         ENDIF
    896896      ENDDO
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/heavyside.F

    r774 r1220  
    1010       IMPLICIT NONE
    1111
    12        REAL*8 heavyside , a
     12       REAL(KIND=8) heavyside , a
    1313
    1414       IF ( a.LE.0. )  THEN
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/inter_barx.F

    r774 r1220  
    8181
    8282      DO idat = 1, idatmax
    83        xxd(idat) = AMOD( xxd(idat) - xim0, 360. )
     83       xxd(idat) = MOD( xxd(idat) - xim0, 360. )
    8484       fdd(idat) = fdat (idat)
    8585      ENDDO
     
    212212     
    213213
    214 3      FORMAT(1x,70(1h-))
     2143      FORMAT(1x,70("-"))
    2152152      FORMAT(1x,8f8.2)
    216216
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/leapfrog_p.F

    r1207 r1220  
    243243   1  CONTINUE
    244244
    245       jD_cur = jD_ref + (day_ini - 1) + int (itau * dtvr / daysec)
     245      jD_cur = jD_ref + day_ini - day_ref + int (itau * dtvr / daysec)
    246246      jH_cur = jH_ref +                                                 &
    247247     &          (itau * dtvr / daysec - int(itau * dtvr / daysec))
     
    684684         CALL exner_hyb_p(  ip1jmp1, ps, p,alpha,beta,pks, pk, pkf )
    685685c$OMP BARRIER
    686            jD_cur = jD_ref + (day_ini -1) + int (itau * dtvr / daysec)
     686           jD_cur = jD_ref + day_ini - day_ref
     687     $        + int (itau * dtvr / daysec)
    687688           jH_cur = jH_ref +                                            &
    688689     &              (itau * dtvr / daysec - int(itau * dtvr / daysec))
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/sortvarc.F

    r1201 r1220  
    157157      RETURN
    158158
    159 3500   FORMAT('0'10(1h*),4x,'pas'i7,5x,'jour'f9.0,'heure'f5.1,4x
    160      *   ,'date',f14.4,4x,10(1h*))
     1593500   FORMAT(10("*"),4x,'pas',i7,5x,'jour',f9.0,'heure',f5.1,4x
     160     *   ,'date',f14.4,4x,10("*"))
    1611614000   FORMAT(10x,'masse',4x,'rmsdpdt',7x,'energie',2x,'enstrophie'
    162162     * ,2x,'entropie',3x,'rmsv',4x,'mt.ang',/,'GLOB  '
  • LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/sortvarc0.F

    r774 r1220  
    130130      ang0   = SSUM(     llm,  angl, 1 )
    131131
    132       rday = FLOAT(INT ( day_ini + time ))
     132      rday = FLOAT(INT (time ))
    133133c
    134134      PRINT 3500, itau, rday, heure, time
    135135      PRINT *, ptot0,etot0,ztot0,stot0,ang0
    136136
    137 3500   FORMAT('0',10(1h*),4x,'pas',i7,5x,'jour',f5.0,'heure',f5.1,4x
    138      *   ,'date',f10.5,4x,10(1h*))
     1373500   FORMAT(10("*"),4x,'pas',i7,5x,'jour',f5.0,'heure',f5.1,4x
     138     *   ,'date',f10.5,4x,10("*"))
    139139      RETURN
    140140      END
Note: See TracChangeset for help on using the changeset viewer.