Ignore:
Timestamp:
Jan 20, 2010, 3:27:21 PM (15 years ago)
Author:
Laurent Fairhead
Message:

Nettoyage general pour se rapprocher des normes et éviter des erreurs a la
compilation:

  • tous les FLOAT() sont remplacés par des REAL()
  • tous les STOP dans phylmd sont remplacés par des appels à abort_gcm
  • le common control défini dans le fichier control.h est remplacé par le module control_mod pour éviter des messages sur l'alignement des variables dans les déclarations
  • des $Header$ remplacés par des $Id$ pour svn

Quelques remplacements à faire ont pu m'échapper


General cleanup of the code to try and adhere to norms and to prevent some
compilation errors:

  • all FLOAT() instructions have been replaced by REAL() instructions
  • all STOP instructions in phylmd have been replaced by calls to abort_gcm
  • the common block control defined in the control.h file has been replaced by the control_mod to prevent compilation warnings on the alignement of declared variables
  • $Header$ replaced by $Id$ for svn

Some changes which should have been made might have escaped me

Location:
LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd
Files:
59 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/aaam_bud.F

    r1279 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      subroutine aaam_bud (iam,nlon,nlev,rjour,rsec,
     
    117117      REAL BLSU(801,401),BLSV(801,401)
    118118      REAL ZLON(801),ZLAT(401)
     119
     120      CHARACTER (LEN=20) :: modname='aaam_bud'
     121      CHARACTER (LEN=80) :: abort_message
     122
     123
    119124C
    120125C  PUT AAM QUANTITIES AT ZERO:
    121126C
    122127      if(iim+1.gt.801.or.jjm+1.gt.401)then
    123       print *,' Pb de dimension dans aaam_bud'
    124       stop
     128        abort_message = 'Pb de dimension dans aaam_bud'
     129        CALL abort_gcm (modname,abort_message,1)
    125130      endif
    126131
     
    128133      hadley=1.e18
    129134      hadday=1.e18*24.*3600.
    130       dlat=xpi/float(jjm)
    131       dlon=2.*xpi/float(iim)
     135      dlat=xpi/REAL(jjm)
     136      dlon=2.*xpi/REAL(iim)
    132137     
    133138      do iax=1,3
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/aeropt.F

    r1279 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      SUBROUTINE aeropt(pplay, paprs, t_seri, msulfate, RHcl,
     
    3939      REAL alpha_aer_sulfate(nbre_RH,5)   !--unit m2/g SO4
    4040      REAL alphasulfate     
     41
     42      CHARACTER (LEN=20) :: modname='aeropt'
     43      CHARACTER (LEN=80) :: abort_message
     44
    4145c
    4246c Proprietes optiques
     
    8589        rh=MIN(RHcl(i,k)*100.,RH_MAX)
    8690        RH_num = INT( rh/10. + 1.)
    87         IF (rh.LT.0.) STOP 'aeropt: RH < 0 not possible'
     91        IF (rh.LT.0.) THEN
     92          abort_message = 'aeropt: RH < 0 not possible'
     93          CALL abort_gcm (modname,abort_message,1)
     94        ENDIF
    8895        IF (rh.gt.85.) RH_num=10
    8996        IF (rh.gt.90.) RH_num=11
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/aeropt_5wv.F90

    r1279 r1299  
    621621  DO k=1, klev
    622622    DO i=1, klon
    623 !      IF (t_seri(i,k).EQ.0) stop 'stop aeropt_5wv T '
    624 !      IF (pplay(i,k).EQ.0) stop  'stop aeropt_5wv p '
    625623      zrho=pplay(i,k)/t_seri(i,k)/RD                  ! kg/m3
    626624!CDIR UNROLL=naero_spc
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/albedo.F

    r900 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44c
     
    6767c prend en compte l'autre moitie de la journee):
    6868      DO k = 1, npts
    69          rmu = aa + bb * COS(FLOAT(k)/FLOAT(npts)*zpi)
     69         rmu = aa + bb * COS(REAL(k)/REAL(npts)*zpi)
    7070         rmu = MAX(0.0, rmu)
    7171         fauxo = (1.47-ACOS(rmu))/.15
     
    110110c prend en compte l'autre moitie de la journee):
    111111      DO k = 1, npts
    112          rmu = aa + bb * COS(FLOAT(k)/FLOAT(npts)*zpi)
     112         rmu = aa + bb * COS(REAL(k)/REAL(npts)*zpi)
    113113         rmu = MAX(0.0, rmu)
    114114cIM cf. PB      alb = 0.058/(rmu + 0.30)
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/calcul_simulISCCP.h

    r1279 r1299  
    11c
    2 c $Header$
     2c $Id$
    33c
    44c on appelle le simulateur ISCCP toutes les 3h
     
    1818       sunlit(i)=1
    1919       IF(rmu0(i).EQ.0.) sunlit(i)=0
    20        nbsunlit(1,i,n)=FLOAT(sunlit(i))
     20       nbsunlit(1,i,n)=REAL(sunlit(i))
    2121      ENDDO
    2222c
     
    8888           print*,'seed=0 i paprs aa seed_re',
    8989     .     i,paprs(i,2),aa,seed_re(i,n)
    90            STOP
     90           abort_message = ''
     91           CALL abort_gcm (modname,abort_message,1)
    9192          ELSE IF(seed(i,n).LT.0) THEN
    9293           print*,'seed < 0, i seed itap paprs',i,
    9394     .     seed(i,n),itap,paprs(i,2)
    94            STOP
     95           abort_message = ''
     96           CALL abort_gcm (modname,abort_message,1)
    9597          ENDIF
    9698c
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/calltherm.F90

    r1295 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      subroutine calltherm(dtime  &
     
    8383!      save zentr_therm,zfm_therm
    8484
     85      character (len=20) :: modname='calltherm'
     86      character (len=80) :: abort_message
     87
    8588      integer i,k
    8689      logical, save :: first=.true.
     
    137140         if(nbptspb.GT.0) print*,'Number of points with q_seri(i,k)<=0 ',nbptspb   
    138141
    139          zdt=dtime/float(nsplit_thermals)
     142         zdt=dtime/REAL(nsplit_thermals)
    140143         do isplit=1,nsplit_thermals
    141144
     
    173176     &      ,tau_thermals,3)
    174177          else if (iflag_thermals.eq.11) then
    175             stop 'cas non prevu dans calltherm'
     178              abort_message = 'cas non prevu dans calltherm'
     179              CALL abort_gcm (modname,abort_message,1)
     180
    176181!           CALL thermcell_pluie(klon,klev,zdt  &
    177182!   &      ,pplay,paprs,pphi,zlev  &
     
    210215           if (prt_level.gt.10) write(lunout,*)'Apres thermcell_main OK'
    211216         else
    212             STOP'Cas des thermiques non prevu'
     217           abort_message = 'Cas des thermiques non prevu'
     218           CALL abort_gcm (modname,abort_message,1)
    213219         endif
    214220
     
    218224      DO i=1,klon
    219225       logexpr1(i)=flag_bidouille_stratocu.or.weak_inversion(i).gt.0.5
    220        IF(logexpr1(i)) fact(i)=1./float(nsplit_thermals)
     226       IF(logexpr1(i)) fact(i)=1./REAL(nsplit_thermals)
    221227      ENDDO
    222228
     
    255261        if(prt_level.GE.10) print*,'calltherm i Alp_bl Alp Ale_bl Ale',i,Alp_bl(i),Alp(i),Ale_bl(i),Ale(i)
    256262            fm_therm(i,klev+1)=0.
    257             Ale_bl(i)=Ale_bl(i)+Ale(i)/float(nsplit_thermals)
     263            Ale_bl(i)=Ale_bl(i)+Ale(i)/REAL(nsplit_thermals)
    258264!            write(22,*)'ALE CALLTHERM',Ale_bl(i),Ale(i)
    259             Alp_bl(i)=Alp_bl(i)+Alp(i)/float(nsplit_thermals)
     265            Alp_bl(i)=Alp_bl(i)+Alp(i)/REAL(nsplit_thermals)
    260266!            write(23,*)'ALP CALLTHERM',Alp_bl(i),Alp(i)
    261267       ENDDO
     
    276282!    &         'fm=',zfm_therm(i,k),'entr=',entr_therm(i,k)
    277283                 endif
    278 !       stop
    279284            ENDDO
    280285            ENDDO
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/conema3.F

    r1146 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      SUBROUTINE conema3 (dtime,paprs,pplay,t,q,u,v,tra,ntra,
     
    360360      cape(i) = em_CAPE
    361361      wd(i) = em_wd
    362       rflag(i) = float(iflag)
     362      rflag(i) = REAL(iflag)
    363363c SB      kbas(i) = em_bas
    364364c SB      ktop(i) = em_top
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/conf_phys.F90

    r1286 r1299  
    2727   USE surface_data
    2828   USE carbon_cycle_mod, ONLY : carbon_cycle_tr, carbon_cycle_cpl
     29   use control_mod
    2930
    3031 include "conema3.h"
     
    3637include "clesphys.h"
    3738include "compbl.h"
    38 include "control.h"
    3939include "comsoil.h"
    4040!
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/convect2.F

    r766 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      subroutine convect2(ncum,idcum,len,nd,ndp1,nl,minorig,
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/cpl_mod.F90

    r1279 r1299  
    2424  USE oasis
    2525  USE write_field_phy
     26  USE control_mod
     27
    2628 
    2729! Global attributes
     
    101103    INCLUDE "dimensions.h"
    102104    INCLUDE "indicesol.h"
    103     INCLUDE "control.h"
    104105    INCLUDE "temps.h"
    105106    INCLUDE "iniprint.h"
     
    583584    DO ig = 1, knon
    584585       cpl_sols(ig,cpl_index) = cpl_sols(ig,cpl_index) + &
    585             swdown(ig)      / FLOAT(nexca)
     586            swdown(ig)      / REAL(nexca)
    586587       cpl_nsol(ig,cpl_index) = cpl_nsol(ig,cpl_index) + &
    587             (lwdown(ig) + fluxlat(ig) +fluxsens(ig)) / FLOAT(nexca)
     588            (lwdown(ig) + fluxlat(ig) +fluxsens(ig)) / REAL(nexca)
    588589       cpl_rain(ig,cpl_index) = cpl_rain(ig,cpl_index) + &
    589             precip_rain(ig) / FLOAT(nexca)
     590            precip_rain(ig) / REAL(nexca)
    590591       cpl_snow(ig,cpl_index) = cpl_snow(ig,cpl_index) + &
    591             precip_snow(ig) / FLOAT(nexca)
     592            precip_snow(ig) / REAL(nexca)
    592593       cpl_evap(ig,cpl_index) = cpl_evap(ig,cpl_index) + &
    593             evap(ig)        / FLOAT(nexca)
     594            evap(ig)        / REAL(nexca)
    594595       cpl_tsol(ig,cpl_index) = cpl_tsol(ig,cpl_index) + &
    595             tsurf(ig)       / FLOAT(nexca)
     596            tsurf(ig)       / REAL(nexca)
    596597       cpl_fder(ig,cpl_index) = cpl_fder(ig,cpl_index) + &
    597             fder(ig)        / FLOAT(nexca)
     598            fder(ig)        / REAL(nexca)
    598599       cpl_albe(ig,cpl_index) = cpl_albe(ig,cpl_index) + &
    599             albsol(ig)      / FLOAT(nexca)
     600            albsol(ig)      / REAL(nexca)
    600601       cpl_taux(ig,cpl_index) = cpl_taux(ig,cpl_index) + &
    601             taux(ig)        / FLOAT(nexca)
     602            taux(ig)        / REAL(nexca)
    602603       cpl_tauy(ig,cpl_index) = cpl_tauy(ig,cpl_index) + &
    603             tauy(ig)        / FLOAT(nexca)     
     604            tauy(ig)        / REAL(nexca)     
    604605       cpl_windsp(ig,cpl_index) = cpl_windsp(ig,cpl_index) + &
    605             windsp(ig)      / FLOAT(nexca)
     606            windsp(ig)      / REAL(nexca)
    606607       cpl_taumod(ig,cpl_index) =   cpl_taumod(ig,cpl_index) + &
    607           SQRT ( taux(ig)*taux(ig)+tauy(ig)*tauy(ig) ) / FLOAT (nexca)
     608          SQRT ( taux(ig)*taux(ig)+tauy(ig)*tauy(ig) ) / REAL (nexca)
    608609
    609610       IF (carbon_cycle_cpl) THEN
    610611          cpl_atm_co2(ig,cpl_index) = cpl_atm_co2(ig,cpl_index) + &
    611                co2_send(knindex(ig))/ FLOAT(nexca)
     612               co2_send(knindex(ig))/ REAL(nexca)
    612613       END IF
    613614     ENDDO
     
    777778    DO ig = 1, knon
    778779       cpl_sols(ig,cpl_index) = cpl_sols(ig,cpl_index) + &
    779             swdown(ig)      / FLOAT(nexca)
     780            swdown(ig)      / REAL(nexca)
    780781       cpl_nsol(ig,cpl_index) = cpl_nsol(ig,cpl_index) + &
    781             (lwdown(ig) + fluxlat(ig) +fluxsens(ig)) / FLOAT(nexca)
     782            (lwdown(ig) + fluxlat(ig) +fluxsens(ig)) / REAL(nexca)
    782783       cpl_rain(ig,cpl_index) = cpl_rain(ig,cpl_index) + &
    783             precip_rain(ig) / FLOAT(nexca)
     784            precip_rain(ig) / REAL(nexca)
    784785       cpl_snow(ig,cpl_index) = cpl_snow(ig,cpl_index) + &
    785             precip_snow(ig) / FLOAT(nexca)
     786            precip_snow(ig) / REAL(nexca)
    786787       cpl_evap(ig,cpl_index) = cpl_evap(ig,cpl_index) + &
    787             evap(ig)        / FLOAT(nexca)
     788            evap(ig)        / REAL(nexca)
    788789       cpl_tsol(ig,cpl_index) = cpl_tsol(ig,cpl_index) + &
    789             tsurf(ig)       / FLOAT(nexca)
     790            tsurf(ig)       / REAL(nexca)
    790791       cpl_fder(ig,cpl_index) = cpl_fder(ig,cpl_index) + &
    791             fder(ig)        / FLOAT(nexca)
     792            fder(ig)        / REAL(nexca)
    792793       cpl_albe(ig,cpl_index) = cpl_albe(ig,cpl_index) + &
    793             albsol(ig)      / FLOAT(nexca)
     794            albsol(ig)      / REAL(nexca)
    794795       cpl_taux(ig,cpl_index) = cpl_taux(ig,cpl_index) + &
    795             taux(ig)        / FLOAT(nexca)
     796            taux(ig)        / REAL(nexca)
    796797       cpl_tauy(ig,cpl_index) = cpl_tauy(ig,cpl_index) + &
    797             tauy(ig)        / FLOAT(nexca)     
     798            tauy(ig)        / REAL(nexca)     
    798799       cpl_taumod(ig,cpl_index) = cpl_taumod(ig,cpl_index) + &
    799             SQRT ( taux(ig)*taux(ig)+tauy(ig)*tauy(ig) ) / FLOAT(nexca)
     800            SQRT ( taux(ig)*taux(ig)+tauy(ig)*tauy(ig) ) / REAL(nexca)
    800801    ENDDO
    801802
     
    944945!*************************************************************************************   
    945946!$OMP MASTER
    946     cpl_rriv2D(:,:) = cpl_rriv2D(:,:) + rriv2D(:,:) / FLOAT(nexca)
    947     cpl_rcoa2D(:,:) = cpl_rcoa2D(:,:) + rcoa2D(:,:) / FLOAT(nexca)
     947    cpl_rriv2D(:,:) = cpl_rriv2D(:,:) + rriv2D(:,:) / REAL(nexca)
     948    cpl_rcoa2D(:,:) = cpl_rcoa2D(:,:) + rcoa2D(:,:) / REAL(nexca)
    948949!$OMP END MASTER
    949950
     
    998999!*************************************************************************************   
    9991000!$OMP MASTER
    1000     cpl_rlic2D(:,:) = cpl_rlic2D(:,:) + rlic2D(:,:) / FLOAT(nexca)
     1001    cpl_rlic2D(:,:) = cpl_rlic2D(:,:) + rlic2D(:,:) / REAL(nexca)
    10011002!$OMP END MASTER
    10021003
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/cv30_routines.F

    r879 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44c
     
    749749
    750750#include "cv30param.h"
     751      include 'iniprint.h'
    751752
    752753c inputs:
     
    778779c local variables:
    779780      integer i,k,nn,j
     781
     782      CHARACTER (LEN=20) :: modname='cv30_compress'
     783      CHARACTER (LEN=80) :: abort_message
    780784
    781785
     
    820824
    821825      if (nn.ne.ncum) then
    822          print*,'strange! nn not equal to ncum: ',nn,ncum
    823          stop
     826         write(lunout,*)'strange! nn not equal to ncum: ',nn,ncum
     827         abort_message = ''
     828         CALL abort_gcm (modname,abort_message,1)
    824829      endif
    825830
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/cv3_inicp.F

    r966 r1299  
    1313c
    1414      INTEGER iflag_clos
     15      CHARACTER (LEN=20) :: modname='cv3_inicp'
     16      CHARACTER (LEN=80) :: abort_message
    1517c
    1618c --   Mixing probability distribution functions
     
    105107        if (abs(aire-1.0) .gt. 0.02) then
    106108            print *,'WARNING:: AREA OF MIXING PDF IS::', aire
    107             stop
     109            abort_message = ''
     110            CALL abort_gcm (modname,abort_message,1)
    108111        else
    109112            print *,'Area, mean & std deviation are ::', aire,mu,sigma
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/cv3_inip.F

    r1146 r1299  
    1212c
    1313c      INTEGER iflag_mix
     14      include 'iniprint.h'
     15
     16      CHARACTER (LEN=20) :: modname='cv3_inip'
     17      CHARACTER (LEN=80) :: abort_message
     18
    1419c
    1520c --   Mixing probability distribution functions
     
    104109c
    105110        if (abs(aire-1.0) .gt. 0.02) then
    106             print *,'WARNING:: AREA OF MIXING PDF IS::', aire
    107             stop
     111            write(lunout,*)'WARNING:: AREA OF MIXING PDF IS::', aire
     112            abort_message = ''
     113            CALL abort_gcm (modname,abort_message,1)
    108114        else
    109115            print *,'Area, mean & std deviation are ::', aire,mu,sigma
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/cv3_routines.F

    r1277 r1299  
    11!
    2 ! $Header: /home/cvsroot/LMDZ4/libf/phylmd/cv3_routines.F,v 1.16 2008-11-06 16:29:35 lmdzadmin Exp $
     2! $Id$
    33!
    44c
     
    3535      integer nd
    3636      real delt ! timestep (seconds)
     37
     38      CHARACTER (LEN=20) :: modname='cv3_param'
     39      CHARACTER (LEN=80) :: abort_message
    3740
    3841c noff: integer limit for convection (nd-noff)
     
    767770
    768771#include "cv3param.h"
     772      include 'iniprint.h'
    769773
    770774c inputs:
     
    797801      integer i,k,nn,j
    798802
     803      CHARACTER (LEN=20) :: modname='cv3_compress'
     804      CHARACTER (LEN=80) :: abort_message
    799805
    800806      do 110 k=1,nl+1
     
    839845
    840846      if (nn.ne.ncum) then
    841          print*,'strange! nn not equal to ncum: ',nn,ncum
    842          stop
     847         write(lunout,*)'strange! nn not equal to ncum: ',nn,ncum
     848         abort_message = ''
     849         CALL abort_gcm (modname,abort_message,1)
    843850      endif
    844851
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/cv3a_compress.F

    r1146 r1299  
    7676      integer i,k,nn,j
    7777
     78      CHARACTER (LEN=20) :: modname='cv3a_compress'
     79      CHARACTER (LEN=80) :: abort_message
     80
    7881
    7982      do 110 k=1,nl+1
     
    127130
    128131      if (nn.ne.ncum) then
    129          print*,'WARNING nn not equal to ncum: ',nn,ncum
    130          stop
     132        print*,'WARNING nn not equal to ncum: ',nn,ncum
     133        abort_message = ''
     134        CALL abort_gcm (modname,abort_message,1)
    131135      endif
    132136
     
    157161      if (nn.ne.ncum) then
    158162         print*,'WARNING nn not equal to ncum: ',nn,ncum
    159          stop
     163         abort_message = ''
     164         CALL abort_gcm (modname,abort_message,1)
    160165      endif
    161166
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/cv3p1_closure.F

    r973 r1299  
     1!
     2! $Id$
     3!
    14      SUBROUTINE cv3p1_closure(nloc,ncum,nd,icb,inb
    25     :                      ,pbase,plcl,p,ph,tv,tvp,buoy
     
    7477      real wb,sigmax
    7578      data wb /2./, sigmax /0.1/
     79
     80      CHARACTER (LEN=20) :: modname='cv3p1_closure'
     81      CHARACTER (LEN=80) :: abort_message
    7682c
    7783c      print *,' -> cv3p1_closure, Ale ',ale(1)
     
    509515       cbmf1(il) = alp2(il)/(0.5*wb*wb-Cin(il))
    510516       if(cbmf1(il).EQ.0.AND.alp2(il).NE.0.) THEN
    511         print*,'cv3p1_closure cbmf1=0 and alp NE 0 il alp2 alp cin ',il,
     517        write(lunout,*)
     518     &  'cv3p1_closure cbmf1=0 and alp NE 0 il alp2 alp cin ',il,
    512519     . alp2(il),alp(il),cin(il)
    513         STOP
     520        abort_message = ''
     521        CALL abort_gcm (modname,abort_message,1)
    514522       endif
    515523       cbmfmax(il) = sigmax*wb2(il)*100.*p(il,icb(il))
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/cv_routines.F

    r524 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      SUBROUTINE cv_param(nd)
     
    3838#include "cvparam.h"
    3939      integer nd
     40      CHARACTER (LEN=20) :: modname='cv_routines'
     41      CHARACTER (LEN=80) :: abort_message
    4042
    4143c noff: integer limit for convection (nd-noff)
     
    429431c local variables:
    430432      integer i,k,nn
     433      CHARACTER (LEN=20) :: modname='cv_compress'
     434      CHARACTER (LEN=80) :: abort_message
     435
     436      include 'iniprint.h'
    431437
    432438
     
    456462
    457463      if (nn.ne.ncum) then
    458          print*,'strange! nn not equal to ncum: ',nn,ncum
    459          stop
     464         write(lunout,*)'strange! nn not equal to ncum: ',nn,ncum
     465         abort_message = ''
     466         CALL abort_gcm (modname,abort_message,1)
    460467      endif
    461468
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/cva_driver.F

    r1279 r1299  
    106106#include "dimensions.h"
    107107ccccc#include "dimphy.h"
     108      include 'iniprint.h'
     109
    108110c
    109111c Input
     
    419421      logical, save :: first=.true.
    420422c$OMP THREADPRIVATE(first)
     423      CHARACTER (LEN=20) :: modname='cva_driver'
     424      CHARACTER (LEN=80) :: abort_message
    421425
    422426c
     
    563567c test niveaux couche alimentation KE
    564568       if(sig1feed1.eq.sig2feed1) then
    565                print*,'impossible de choisir sig1feed=sig2feed'
    566                print*,'changer la valeur de sig2feed dans physiq.def'
    567        stop
     569         write(lunout,*)'impossible de choisir sig1feed=sig2feed'
     570         write(lunout,*)'changer la valeur de sig2feed dans physiq.def'
     571         abort_message = ''
     572         CALL abort_gcm (modname,abort_message,1)
    568573       endif
    569574c
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/fisrtilp.F

    r1279 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44c
     
    135135         PRINT*, 'fisrtilp, evap_prec:', evap_prec
    136136         PRINT*, 'fisrtilp, cpartiel:', cpartiel
    137          IF (ABS(dtime/FLOAT(ninter)-360.0).GT.0.001) THEN
     137         IF (ABS(dtime/REAL(ninter)-360.0).GT.0.001) THEN
    138138          PRINT*, 'fisrtilp: Ce n est pas prevu, voir Z.X.Li', dtime
    139139          PRINT*, 'Je prefere un sous-intervalle de 6 minutes'
     
    436436         zfice(i) = zfice(i)**nexpo
    437437         zneb(i) = MAX(rneb(i,k), seuil_neb)
    438          radliq(i,k) = zoliq(i)/FLOAT(ninter+1)
     438         radliq(i,k) = zoliq(i)/REAL(ninter+1)
    439439      ENDIF
    440440      ENDDO
     
    453453                zcl   =cld_lc_con
    454454                zct   =1./cld_tau_con
    455                 zfroi    = dtime/FLOAT(ninter)/zdz(i)*zoliq(i)
     455                zfroi    = dtime/REAL(ninter)/zdz(i)*zoliq(i)
    456456     .              *fallvc(zrhol(i)) * zfice(i)
    457457             else
    458458                zcl   =cld_lc_lsc
    459459                zct   =1./cld_tau_lsc
    460                 zfroi    = dtime/FLOAT(ninter)/zdz(i)*zoliq(i)
     460                zfroi    = dtime/REAL(ninter)/zdz(i)*zoliq(i)
    461461     .              *fallvs(zrhol(i)) * zfice(i)
    462462             endif
    463              zchau    = zct   *dtime/FLOAT(ninter) * zoliq(i)
     463             zchau    = zct   *dtime/REAL(ninter) * zoliq(i)
    464464     .         *(1.0-EXP(-(zoliq(i)/zneb(i)/zcl   )**2)) *(1.-zfice(i))
    465465             ztot    = zchau    + zfroi
     
    468468         ztot    = MIN(ztot,zoliq(i))
    469469         zoliq(i) = MAX(zoliq(i)-ztot   , 0.0)
    470          radliq(i,k) = radliq(i,k) + zoliq(i)/FLOAT(ninter+1)
     470         radliq(i,k) = radliq(i,k) + zoliq(i)/REAL(ninter+1)
    471471      ENDIF
    472472      ENDDO
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/fisrtilp_tr.F

    r766 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44c
     
    140140         PRINT*, 'fisrtilp, evap_prec:', evap_prec
    141141         PRINT*, 'fisrtilp, cpartiel:', cpartiel
    142          IF (ABS(dtime/FLOAT(ninter)-360.0).GT.0.001) THEN
     142         IF (ABS(dtime/REAL(ninter)-360.0).GT.0.001) THEN
    143143          PRINT*, 'fisrtilp: Ce n est pas prevu, voir Z.X.Li', dtime
    144144          PRINT*, 'Je prefere un sous-intervalle de 6 minutes'
     
    335335         zfice(i) = zfice(i)**nexpo
    336336         zneb(i) = MAX(rneb(i,k), seuil_neb)
    337          radliq(i,k) = zoliq(i)/FLOAT(ninter+1)
     337         radliq(i,k) = zoliq(i)/REAL(ninter+1)
    338338      ENDIF
    339339      ENDDO
     
    342342      DO i = 1, klon
    343343      IF (rneb(i,k).GT.0.0) THEN
    344          zchau(i) = ct*dtime/FLOAT(ninter) * zoliq(i)
     344         zchau(i) = ct*dtime/REAL(ninter) * zoliq(i)
    345345     .          * (1.0-EXP(-(zoliq(i)/zneb(i)/cl)**2)) *(1.-zfice(i))
    346346         zrhol(i) = zrho(i) * zoliq(i) / zneb(i)
    347          zfroi(i) = dtime/FLOAT(ninter)/zdz(i)*zoliq(i)
     347         zfroi(i) = dtime/REAL(ninter)/zdz(i)*zoliq(i)
    348348     .              *fallv(zrhol(i)) * zfice(i)
    349349         ztot(i) = zchau(i) + zfroi(i)
     
    351351         ztot(i) = MIN(MAX(ztot(i),0.0),zoliq(i))
    352352         zoliq(i) = MAX(zoliq(i)-ztot(i), 0.0)
    353          radliq(i,k) = radliq(i,k) + zoliq(i)/FLOAT(ninter+1)
     353         radliq(i,k) = radliq(i,k) + zoliq(i)/REAL(ninter+1)
    354354      ENDIF
    355355      ENDDO
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/hines_gwd.F

    r1279 r1299  
    847847C  Use horizontal isotropy to calculate azimuthal variances at bottom level.
    848848C
    849       AZFAC = 1. / FLOAT(NAZ)
     849      AZFAC = 1. / REAL(NAZ)
    850850      DO 20 N = 1,NAZ
    851851        DO 10 I = IL1,IL2
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/ini_bilKP_ave.h

    r766 r1299  
    11c
    2 c $Header$
     2c $Id$
    33c
    44      IF (ok_journe) THEN
     
    1717cym         ENDDO
    1818         DO ll=1,klev
    19             znivsig(ll)=float(ll)
     19            znivsig(ll)=REAL(ll)
    2020         ENDDO
    2121cym         CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlat,zx_lat)
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/ini_bilKP_ins.h

    r766 r1299  
    11c
    2 c $Header$
     2c $Id$
    33c
    44      IF (ok_journe) THEN
     
    1717cym         ENDDO
    1818         DO ll=1,klev
    19             znivsig(ll)=float(ll)
     19            znivsig(ll)=REAL(ll)
    2020         ENDDO
    2121cym         CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlat,zx_lat)
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/ini_histISCCP.h

    r1045 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      IF (ok_isccp) THEN
     
    4949c
    5050        DO l=1, ncol(n)
    51           vertlev(l,n)=float(l)
     51          vertlev(l,n)=REAL(l)
    5252        ENDDO !ncol
    5353c
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/ini_histday_seri.h

    r776 r1299  
    11c
    2 c $Header$
     2c $Id$
    33c
    44cym Ne fonctionnera pas en mode parallele
     
    1919         ENDDO
    2020         DO ll=1,klev
    21             znivsig(ll)=float(ll)
     21            znivsig(ll)=REAL(ll)
    2222         ENDDO
    2323         CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlat,zx_lat)
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/ini_histmthNMC.h

    r776 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      IF (ok_mensuel) THEN
     
    2020cym         ENDDO
    2121         DO ll=1,klev
    22             znivsig(ll)=float(ll)
     22            znivsig(ll)=REAL(ll)
    2323         ENDDO
    2424cym         CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlat,zx_lat)
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/inifis.F

    r987 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      SUBROUTINE inifis(ngrid,nlayer,
     
    4545cym#include "dimphy.h"
    4646
     47      INCLUDE 'iniprint.h'
    4748      REAL prad,pg,pr,pcpp,punjours
    4849 
     
    5253 
    5354      REAL ptimestep
     55      CHARACTER (LEN=20) :: modname='inifis'
     56      CHARACTER (LEN=80) :: abort_message
     57
    5458 
    5559      IF (nlayer.NE.klev) THEN
     
    5862         PRINT*,'nlayer     = ',nlayer
    5963         PRINT*,'klev   = ',klev
    60          STOP
     64         abort_message = ''
     65         CALL abort_gcm (modname,abort_message,1)
    6166      ENDIF
    6267
     
    6671         PRINT*,'ngrid     = ',ngrid
    6772         PRINT*,'klon   = ',klon
    68          STOP
     73         abort_message = ''
     74         CALL abort_gcm (modname,abort_message,1)
    6975      ENDIF
    7076
    7177      RETURN
    72 9999  STOP'Cette version demande les fichier rnatur.dat et surf.def'
     789999  continue
     79      abort_message = 'Cette version demande les fichier rnatur.dat
     80     & et surf.def'
     81      CALL abort_gcm (modname,abort_message,1)
     82
    7383      END
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/iniphysiq.F

    r879 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44c
     
    6161 
    6262      REAL ptimestep
     63      CHARACTER (LEN=20) :: modname='iniphysiq'
     64      CHARACTER (LEN=80) :: abort_message
    6365 
    6466      IF (nlayer.NE.klev) THEN
     
    6769         PRINT*,'nlayer     = ',nlayer
    6870         PRINT*,'klev   = ',klev
    69          STOP
     71         abort_message = ''
     72         CALL abort_gcm (modname,abort_message,1)
    7073      ENDIF
    7174
     
    7578         PRINT*,'ngrid     = ',ngrid
    7679         PRINT*,'klon   = ',klon_glo
    77          STOP
     80         abort_message = ''
     81         CALL abort_gcm (modname,abort_message,1)
    7882      ENDIF
    7983c$OMP PARALLEL PRIVATE(ibegin,iend)
     
    96100
    97101      RETURN
    98 9999  STOP'Cette version demande les fichier rnatur.dat et surf.def'
     1029999  CONTINUE
     103      abort_message ='Cette version demande les fichier rnatur.dat
     104     & et surf.def'
     105      CALL abort_gcm (modname,abort_message,1)
     106
    99107      END
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/initphysto.F

    r1279 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44C
     
    1212       USE IOIPSL
    1313       USE iophy
     14       USE control_mod
     15
    1416      implicit none
    1517
     
    5254#include "serre.h"
    5355#include "indicesol.h"
    54 #include "control.h"
    5556cym#include "dimphy.h"
    5657
     
    108109C
    109110        DO l=1,llm
    110             nivsigs(l)=float(l)
     111            nivsigs(l)=REAL(l)
    111112         ENDDO
    112113
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/initrrnpb.F90

    r1279 r1299  
    11!
    2 ! $Id $
     2! $Id$
    33!
    44SUBROUTINE  initrrnpb(ftsol,pctsrf,masktr,fshtr,hsoltr,tautr,vdeptr,scavtr)
     
    3939  REAL                                  :: s
    4040
     41  CHARACTER (LEN=20) :: modname='initrrnpb'
     42  CHARACTER (LEN=80) :: abort_message
     43
     44
    4145  WRITE(*,*)'PASSAGE initrrnpb ...'
    4246!
    4347! Radon it = 1
    4448!----------------
    45   IF ( nbtr .LE. 0 ) STOP '**PHYTRAC:initrrnpb:** nbtr < 0; verifier RN dans traceur.def'
     49  IF ( nbtr .LE. 0 ) then
     50    abort_message = '**PHYTRAC:initrrnpb:** nbtr < 0; verifier RN dans traceur.def'
     51    CALL abort_gcm (modname,abort_message,1)
     52  ENDIF
    4653  it = 1
    4754  s = 1.E4             ! Source: atome par m2
     
    6875! 210Pb it = 2
    6976!----------------
    70   IF ( nbtr .LE. 1 ) STOP '**PHYTRAC**:initrrnpb:** nbtr <= 1; verifier PB dans traceur.def'
     77  IF ( nbtr .LE. 1 ) THEN
     78    abort_message='**PHYTRAC**:initrrnpb:** nbtr <= 1; verifier PB dans traceur.def'
     79    CALL abort_gcm (modname,abort_message,1)
     80  ENDIF
    7181  it = 2
    7282  s = 0.                ! Pas de source
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/mod_phys_lmdz_omp_data.F90

    r1001 r1299  
    11!
    2 !$Header$
     2!$Id$
    33!
    44MODULE mod_phys_lmdz_omp_data
     
    2727    INTEGER :: i
    2828
     29    CHARACTER (LEN=20) :: modname='Init_phys_lmdz_omp_data'
     30    CHARACTER (LEN=80) :: abort_message
     31
     32
    2933#ifdef CPP_OMP   
    3034    INTEGER :: OMP_GET_NUM_THREADS
     
    5155     is_omp_root=.TRUE.
    5256   ELSE
    53      PRINT *,'ANORMAL : OMP_MASTER /= 0'
    54      STOP
     57     abort_message = 'ANORMAL : OMP_MASTER /= 0'
     58     CALL abort_gcm (modname,abort_message,1)
    5559   ENDIF
    5660!$OMP END MASTER
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/o3cm.F

    r524 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      SUBROUTINE o3cm (amb, bmb, sortie, ntab)
     
    1919c======================================================================
    2020      external mbtozm
     21      CHARACTER (LEN=20) :: modname=''
     22      CHARACTER (LEN=80) :: abort_message
    2123c======================================================================
    2224c la fonction en ligne w(x) donne le profil de l'ozone en fonction
     
    2729      w(x) = wp/h * EXP((x-xp)/h)/ (con+EXP((x-xp)/h))**2
    2830c======================================================================
    29       IF (ntab .GT. 499) STOP 'BIG ntab'
    30       xincr = (bmb-amb) / FLOAT(ntab)
     31      IF (ntab .GT. 499) THEN
     32        abort_message = 'BIG ntab'
     33        CALL abort_gcm (modname,abort_message,1)
     34      ENDIF
     35      xincr = (bmb-amb) / REAL(ntab)
    3136      xtab(1) = amb
    3237      DO n = 2, ntab
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/orografi.F

    r1279 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      SUBROUTINE drag_noro (nlon,nlev,dtime,paprs,pplay,
     
    14971497     *       ZDVDT(KLON)
    14981498      REAL ZHCRIT(KLON,KLEV)
     1499      CHARACTER (LEN=20) :: modname='orografi'
     1500      CHARACTER (LEN=80) :: abort_message
    14991501C-----------------------------------------------------------------------
    15001502C
     
    15041506      LIFTHIGH=.FALSE.
    15051507
    1506       IF(NLON.NE.KLON.OR.NLEV.NE.KLEV)STOP
     1508      IF(NLON.NE.KLON.OR.NLEV.NE.KLEV)THEN
     1509        abort_message = 'pb dimension'
     1510        CALL abort_gcm (modname,abort_message,1)
     1511      ENDIF
    15071512      ZCONS1=1./RD
    15081513cym      KLEVM1=KLEV-1
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/orografi_strato.F

    r1001 r1299  
    8989      REAL pt(klon,klev), pu(klon,klev), pv(klon,klev)
    9090      REAL papmf(klon,klev),papmh(klon,klev+1)
     91      CHARACTER (LEN=20) :: modname='orografi_strato'
     92      CHARACTER (LEN=80) :: abort_message
    9193c
    9294c INITIALIZE OUTPUT VARIABLES
     
    16801682      logical lifthigh
    16811683      real zcons1,ztmst
     1684      CHARACTER (LEN=20) :: modname='orolift_strato'
     1685      CHARACTER (LEN=80) :: abort_message
     1686
    16821687
    16831688C-----------------------------------------------------------------------
     
    16881693      lifthigh=.false.
    16891694
    1690       if(nlon.ne.klon.or.nlev.ne.klev)stop
     1695      if(nlon.ne.klon.or.nlev.ne.klev) then
     1696        abort_message = 'pb dimension'
     1697        CALL abort_gcm (modname,abort_message,1)
     1698      ENDIF
    16911699      zcons1=1./rd
    16921700      ztmst=ptsphy
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/pbl_surface_mod.F90

    r1282 r1299  
    2222  USE climb_wind_mod,      ONLY : climb_wind_down, climb_wind_up
    2323  USE coef_diff_turb_mod,  ONLY : coef_diff_turb
     24  USE control_mod
     25
    2426
    2527  IMPLICIT NONE
     
    257259    INCLUDE "YOETHF.h"
    258260    INCLUDE "temps.h"
    259     INCLUDE "control.h"
    260261! Input variables
    261262!****************************************************************************************
     
    657658          tabindx(:)=0.
    658659          DO i=1,knon
    659              tabindx(i)=FLOAT(i)
     660             tabindx(i)=REAL(i)
    660661          END DO
    661662          debugtab(:,:) = 0.
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/phyredem.F

    r1298 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44c
     
    1414      USE traclmdz_mod, ONLY : traclmdz_to_restart
    1515      USE infotrac
     16      USE control_mod
     17
    1618
    1719      IMPLICIT none
     
    2426#include "dimsoil.h"
    2527#include "clesphys.h"
    26 #include "control.h"
    2728#include "temps.h"
    2829#include "thermcell.h"
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/phys_state_var_mod.F90

    r1279 r1299  
    289289SUBROUTINE phys_state_var_init(read_climoz)
    290290use dimphy
     291USE control_mod
    291292use aero_mod
    292293IMPLICIT NONE
     
    301302
    302303#include "indicesol.h"
    303 #include "control.h"
    304304      ALLOCATE(rlat(klon), rlon(klon))
    305305      ALLOCATE(pctsrf(klon,nbsrf))
     
    411411SUBROUTINE phys_state_var_end
    412412use dimphy
     413use control_mod
    413414IMPLICIT NONE
    414415#include "indicesol.h"
    415 #include "control.h"
    416416
    417417      deallocate(rlat, rlon, pctsrf, ftsol, falb1, falb2)
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/physiq.F

    r1298 r1299  
    3939      use conf_phys_m, only: conf_phys
    4040      use radlwsw_m, only: radlwsw
     41      USE control_mod
     42
    4143
    4244      IMPLICIT none
     
    9799#include "dimsoil.h"
    98100#include "clesphys.h"
    99 #include "control.h"
    100101#include "temps.h"
    101102#include "iniprint.h"
     
    13481349         ENDIF
    13491350c
    1350          IF (dtime*FLOAT(radpas).GT.21600..AND.cycle_diurne) THEN
     1351         IF (dtime*REAL(radpas).GT.21600..AND.cycle_diurne) THEN
    13511352           WRITE(lunout,*)'Nbre d appels au rayonnement insuffisant'
    13521353           WRITE(lunout,*)"Au minimum 4 appels par jour si cycle diurne"
     
    15181519         CALL VTb(VTinca)
    15191520!         iii = MOD(NINT(xjour),360)
    1520 !         calday = FLOAT(iii) + jH_cur
    1521          calday = FLOAT(days_elapsed) + jH_cur
     1521!         calday = REAL(iii) + jH_cur
     1522         calday = REAL(days_elapsed) + jH_cur
    15221523         WRITE(lunout,*) 'initial time chemini', days_elapsed, calday
    15231524
     
    18011802!   solarlong0
    18021803        if (solarlong0<-999.) then
    1803            CALL orbite(FLOAT(days_elapsed+1),zlongi,dist)
     1804           CALL orbite(REAL(days_elapsed+1),zlongi,dist)
    18041805        else
    18051806           zlongi=solarlong0  ! longitude solaire vraie
     
    18121813!  Avec ou sans cycle diurne
    18131814      IF (cycle_diurne) THEN
    1814         zdtime=dtime*FLOAT(radpas) ! pas de temps du rayonnement (s)
     1815        zdtime=dtime*REAL(radpas) ! pas de temps du rayonnement (s)
    18151816        CALL zenang(zlongi,jH_cur,zdtime,rlat,rlon,rmu0,fract)
    18161817      ELSE
     
    19611962
    19621963      IF (iflag_con.EQ.1) THEN
    1963           stop'reactiver le call conlmd dans physiq.F'
     1964        abort_message ='reactiver le call conlmd dans physiq.F'
     1965        CALL abort_gcm (modname,abort_message,1)
    19641966c     CALL conlmd (dtime, paprs, pplay, t_seri, q_seri, conv_q,
    19651967c    .             d_t_con, d_q_con,
     
    22052207          za = 0.0
    22062208          DO i = 1, klon
    2207             za = za + airephy(i)/FLOAT(klon)
     2209            za = za + airephy(i)/REAL(klon)
    22082210            zx_t = zx_t + (rain_con(i)+
    2209      .                   snow_con(i))*airephy(i)/FLOAT(klon)
     2211     .                   snow_con(i))*airephy(i)/REAL(klon)
    22102212          ENDDO
    22112213          zx_t = zx_t/za*dtime
     
    25992601         za = 0.0
    26002602         DO i = 1, klon
    2601             za = za + airephy(i)/FLOAT(klon)
     2603            za = za + airephy(i)/REAL(klon)
    26022604            zx_t = zx_t + (rain_lsc(i)
    2603      .                  + snow_lsc(i))*airephy(i)/FLOAT(klon)
     2605     .                  + snow_lsc(i))*airephy(i)/REAL(klon)
    26042606        ENDDO
    26052607         zx_t = zx_t/za*dtime
     
    28232825         CALL VTe(VTphysiq)
    28242826         CALL VTb(VTinca)
    2825          calday = FLOAT(days_elapsed + 1) + jH_cur
     2827         calday = REAL(days_elapsed + 1) + jH_cur
    28262828
    28272829         call chemtime(itap+itau_phy-1, date0, dtime)
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/phystokenc.F

    r1146 r1299  
    1313      USE infotrac, ONLY : nqtot
    1414      USE iophy
     15      USE control_mod
     16
    1517      IMPLICIT none
    1618
     
    2426#include "tracstoke.h"
    2527#include "indicesol.h"
    26 #include "control.h"
    2728c======================================================================
    2829
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/phytrac.F90

    r1279 r1299  
    3333  USE traclmdz_mod
    3434  USE tracinca_mod
     35  USE control_mod
     36
    3537
    3638
     
    4345  INCLUDE "temps.h"
    4446  INCLUDE "paramet.h"
    45   INCLUDE "control.h"
    4647  INCLUDE "thermcell.h"
    4748!==========================================================================
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/read_pstoke.F

    r1146 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44c
     
    1818C******************************************************************************
    1919
    20         use netcdf
    21        USE dimphy
     20      use netcdf
     21      USE dimphy
     22      USE control_mod
     23
    2224       IMPLICIT NONE
    2325
     
    3335#include "serre.h"
    3436#include "indicesol.h"
    35 #include "control.h"
    3637cccc#include "dimphy.h"
    3738       
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/read_pstoke0.F

    r1146 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44c
     
    1919        use netcdf
    2020       USE dimphy
     21       USE control_mod
     22
    2123       IMPLICIT NONE
    2224
     
    3234#include "serre.h"
    3335#include "indicesol.h"
    34 #include "control.h"
    3536cccc#include "dimphy.h"
    3637         
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/readaerosol.F90

    r1279 r1299  
    128128                 DO i = 1, klon
    129129                    pt_out(i,k,it) = &
    130                          pt_out(i,k,it) - FLOAT(iyr_in-iyr1)/FLOAT(iyr2-iyr1) * &
     130                         pt_out(i,k,it) - REAL(iyr_in-iyr1)/REAL(iyr2-iyr1) * &
    131131                         (pt_out(i,k,it) - pt_2(i,k,it))
    132132                 END DO
     
    135135              DO i = 1, klon
    136136                 psurf(i,it) = &
    137                       psurf(i,it) - FLOAT(iyr_in-iyr1)/FLOAT(iyr2-iyr1) * &
     137                      psurf(i,it) - REAL(iyr_in-iyr1)/REAL(iyr2-iyr1) * &
    138138                      (psurf(i,it) - psurf2(i,it))
    139139
    140140                 load(i,it) = &
    141                       load(i,it) - FLOAT(iyr_in-iyr1)/FLOAT(iyr2-iyr1) * &
     141                      load(i,it) - REAL(iyr_in-iyr1)/REAL(iyr2-iyr1) * &
    142142                      (load(i,it) - load2(i,it))
    143143              END DO
     
    493493                spole = spole + varyear(i,jjm+1,k,imth)
    494494             END DO
    495              npole = npole/FLOAT(iim)
    496              spole = spole/FLOAT(iim)
     495             npole = npole/REAL(iim)
     496             spole = spole/REAL(iim)
    497497             varyear(:,1,    k,imth) = npole
    498498             varyear(:,jjm+1,k,imth) = spole
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/readaerosol_interp.F90

    r1279 r1299  
    126126  IF(mpi_rank == 0 .AND. debug)then
    127127     ! 0.02 is about 0.5/24, namly less than half an hour
    128      OLDNEWDAY = (r_day-FLOAT(iday) < 0.02)
     128     OLDNEWDAY = (r_day-REAL(iday) < 0.02)
    129129     ! Once per day, update aerosol fields
    130130     lmt_pas = NINT(86400./pdtphys)
    131      PRINT*,'r_day-FLOAT(iday) =',r_day-FLOAT(iday)
     131     PRINT*,'r_day-REAL(iday) =',r_day-REAL(iday)
    132132     PRINT*,'itap =',itap
    133133     PRINT*,'pdtphys =',pdtphys
     
    233233!
    234234     DO i = 2, 13
    235        month_len(i) = float(ioget_mon_len(year_cur, i-1))
     235       month_len(i) = REAL(ioget_mon_len(year_cur, i-1))
    236236       CALL ymds2ju(year_cur, i-1, 1, 0.0, month_start(i))
    237237     ENDDO
    238      month_len(1) = float(ioget_mon_len(year_cur-1, 12))
     238     month_len(1) = REAL(ioget_mon_len(year_cur-1, 12))
    239239     CALL ymds2ju(year_cur-1, 12, 1, 0.0, month_start(1))
    240      month_len(14) = float(ioget_mon_len(year_cur+1, 1))
     240     month_len(14) = REAL(ioget_mon_len(year_cur+1, 1))
    241241     CALL ymds2ju(year_cur+1, 1, 1, 0.0, month_start(14))
    242242     month_mid(:) = month_start (:) + month_len(:)/2.
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/surf_ocean_mod.F90

    r1146 r1299  
    141141!****************************************************************************************
    142142    IF ( MINVAL(rmu0) == MAXVAL(rmu0) .AND. MINVAL(rmu0) == -999.999 ) THEN
    143        CALL alboc(FLOAT(jour),rlat,alb_eau)
     143       CALL alboc(REAL(jour),rlat,alb_eau)
    144144    ELSE  ! diurnal cycle
    145145       CALL alboc_cd(rmu0,alb_eau)
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/sw_aeroAR4.F90

    r1279 r1299  
    186186!$OMP THREADPRIVATE(AEROSOLFEEDBACK_ACTIVE) 
    187187
     188      CHARACTER (LEN=20) :: modname='sw_aeroAR4'
     189      CHARACTER (LEN=80) :: abort_message
     190
    188191  IF ((.not. ok_ade) .and. (AEROSOLFEEDBACK_ACTIVE .ge. 2)) THEN
    189      print*,'Error: direct effect is not activated but assumed to be active - see sw_aeroAR4.F90'
    190      stop
     192     abort_message ='Error: direct effect is not activated but assumed to be active - see sw_aeroAR4.F90'
     193     CALL abort_gcm (modname,abort_message,1)
    191194  ENDIF
    192195  AEROSOLFEEDBACK_ACTIVE=MIN(MAX(AEROSOLFEEDBACK_ACTIVE,0),3)
    193196  IF  (AEROSOLFEEDBACK_ACTIVE .gt. 3) THEN
    194      print*,'Error: AEROSOLFEEDBACK_ACTIVE options go only until 3'
    195      stop
     197     abort_message ='Error: AEROSOLFEEDBACK_ACTIVE options go only until 3'
     198     CALL abort_gcm (modname,abort_message,1)
    196199  ENDIF
    197200
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/thermcell.F

    r987 r1299  
     1!
     2! $Id$
     3!
    14      SUBROUTINE calcul_sec(ngrid,nlay,ptimestep
    25     s                  ,pplay,pplev,pphi,zlev
     
    132135      character*10 str10
    133136
     137      character (len=20) :: modname='calcul_sec'
     138      character (len=80) :: abort_message
     139
     140
    134141!      LOGICAL vtest(klon),down
    135142
     
    530537c      write(8,*)zmax(ig),lmax(ig),lentr(ig),lmin(ig)
    531538      enddo
    532 con stoppe après les calculs de zmax et wmax
     539con stope après les calculs de zmax et wmax
    533540      RETURN
    534541
     
    776783         do ig=1,ngrid
    777784            if(fracd(ig,l).lt.0.1) then
    778                stop'fracd trop petit'
     785              abort_message = 'fracd trop petit'
     786              CALL abort_gcm (modname,abort_message,1)
     787
    779788            else
    780789c    vitesse descendante "diagnostique"
     
    860869cRC
    861870      if (w2di.eq.1) then
    862          fm0=fm0+ptimestep*(fm-fm0)/float(tho)
    863          entr0=entr0+ptimestep*(entr-entr0)/float(tho)
     871         fm0=fm0+ptimestep*(fm-fm0)/REAL(tho)
     872         entr0=entr0+ptimestep*(entr-entr0)/REAL(tho)
    864873      else
    865874         fm0=fm
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/thermcellV0_main.F90

    r1294 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      SUBROUTINE thermcellV0_main(itap,ngrid,nlay,ptimestep  &
     
    165165      character*2 str2
    166166      character*10 str10
     167
     168      character (len=20) :: modname='thermcellV0_main'
     169      character (len=80) :: abort_message
    167170
    168171      EXTERNAL SCOPY
     
    484487! Test valable seulement en 1D mais pas genant
    485488      if (.not. (f0(1).ge.0.) ) then
    486            stop 'Dans thermcell_main'
     489        abort_message = 'Dans thermcell_main f0(1).lt.0 '
     490        CALL abort_gcm (modname,abort_message,1)
    487491      endif
    488492
     
    827831                  write(6,'(i3,7f10.3)') k,pplay(i,k),ztv(i,k),1000*po(i,k),ztva(i,k),1000*zqla(i,k),f_star(i,k),zw2(i,k)
    828832               enddo
    829 !              stop
    830833           endif
    831834         enddo
     
    863866
    864867      REAL f(ngrid)
     868
     869      character (len=20) :: modname='thermcellV0_main'
     870      character (len=80) :: abort_message
    865871
    866872      do ig=1,ngrid
     
    885891                print*,'zmax_sec',zmax_sec(ig)
    886892                print*,'wmax_sec',wmax_sec(ig)
    887                 stop
     893                abort_message = 'zdenom<1.e-14'
     894                CALL abort_gcm (modname,abort_message,1)
    888895             endif
    889896             if ((zmax_sec(ig).gt.1.e-10).and.(iflag_thermals_ed.eq.0)) then
     
    13381345!        if(detr_star(ig,l).GT.1.) THEN
    13391346!         print*,'th_plumeAFT ig l detr_star f0 1/f0',ig,l,detr_star(ig,l),f0(ig), &
    1340 !   &     float(1)/f0(ig)
     1347!   &     REAL(1)/f0(ig)
    13411348!        endif
    13421349!IM 060508 end
     
    16561663
    16571664            if (zw2(ig,l+1)>0. .and. zw2(ig,l+1).lt.1.e-10) then
    1658 !               stop'On tombe sur le cas particulier de thermcell_dry'
    16591665                print*,'On tombe sur le cas particulier de thermcell_plume'
    16601666                zw2(ig,l+1)=0.
     
    18321838
    18331839            if (zw2(ig,l+1)>0. .and. zw2(ig,l+1).lt.1.e-10) then
    1834 !               stop'On tombe sur le cas particulier de thermcell_dry'
    18351840!               print*,'On tombe sur le cas particulier de thermcell_dry'
    18361841                zw2(ig,l+1)=0.
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/thermcell_dq.F90

    r983 r1299  
    3131      real ztimestep
    3232      integer niter,iter
     33      CHARACTER (LEN=20) :: modname='thermcell_dq'
     34      CHARACTER (LEN=80) :: abort_message
    3335
    3436
     
    4244            if (entr(ig,k).gt.zzm) then
    4345               print*,'entr dt > m ',entr(ig,k)*ptimestep,masse(ig,k)
    44                stop
     46               abort_message = ''
     47               CALL abort_gcm (modname,abort_message,1)
    4548            endif
    4649         enddo
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/thermcell_dry.F90

    r1294 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44       SUBROUTINE thermcell_dry(ngrid,nlay,zlev,pphi,ztv,alim_star,  &
     
    3939       REAL linter(ngrid),zlevinter(ngrid)
    4040       INTEGER lmix(ngrid),lmax(ngrid),lmin(ngrid)
     41      CHARACTER (LEN=20) :: modname='thermcell_dry'
     42      CHARACTER (LEN=80) :: abort_message
    4143
    4244!initialisations
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/thermcell_flux.F90

    r1146 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44
     
    5151!$OMP THREADPRIVATE(fomass_max,alphamax)
    5252
     53      character (len=20) :: modname='thermcell_flux'
     54      character (len=80) :: abort_message
     55
    5356      fomass_max=0.5
    5457      alphamax=0.7
     
    9295                    print*,'alim_star(ig,l)',alim_star(ig,l)
    9396                    print*,'detr_star(ig,l)',detr_star(ig,l)
    94 !                   stop
    9597               endif
    9698            else
     
    100102                    print*,'alim_star(ig,l)',alim_star(ig,l)
    101103                    print*,'detr_star(ig,l)',detr_star(ig,l)
    102                     stop
     104                    abort_message = ''
     105                    CALL abort_gcm (modname,abort_message,1)
    103106               endif
    104107            endif
     
    264267            if (entr(ig,l)<0.) then
    265268               print*,'N1 ig,l,entr',ig,l,entr(ig,l)
    266                stop 'entr negatif'
     269               abort_message = 'entr negatif'
     270               CALL abort_gcm (modname,abort_message,1)
    267271            endif
    268272            if (detr(ig,l).gt.fm(ig,l)) then
     
    292296               print*,'entr(ig,l)',entr(ig,l)
    293297               print*,'fm(ig,l)',fm(ig,l)
    294                stop 'probleme dans thermcell flux'
     298               abort_message = 'probleme dans thermcell flux'
     299               CALL abort_gcm (modname,abort_message,1)
    295300            endif
    296301         enddo
     
    319324               print*,'detr(ig,l)',detr(ig,l)
    320325               print*,'fm(ig,l)',fm(ig,l)
    321                stop 'probleme dans thermcell flux'
     326               abort_message = 'probleme dans thermcell flux'
     327               CALL abort_gcm (modname,abort_message,1)
    322328            endif
    323329        enddo
     
    420426                         print*,'fm(ig,l+1)',fm(ig,l+1)
    421427                         print*,'fm(ig,l)',fm(ig,l)
    422                          stop 'probleme dans thermcell_flux'
     428                         abort_message = 'probleme dans thermcell_flux'
     429                         CALL abort_gcm (modname,abort_message,1)
    423430                      endif
    424431                      entr(ig,l+1)=entr(ig,l+1)-ddd
     
    478485      character*3 descr
    479486
     487      character (len=20) :: modname='thermcell_flux'
     488      character (len=80) :: abort_message
     489
    480490      lm=lmax(igout)+5
    481491      if(lm.gt.klev) lm=klev
     
    500510          print*,'detr(igout,l)',detr(igout,l)
    501511          print*,'fm(igout,l)',fm(igout,l)
    502           stop
     512          abort_message = ''
     513          CALL abort_gcm (modname,abort_message,1)
    503514          endif
    504515      enddo
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/thermcell_flux2.F90

    r1146 r1299  
     1!
     2! $Id$
     3!
    14      SUBROUTINE thermcell_flux2(ngrid,klev,ptimestep,masse, &
    25     &       lalim,lmax,alim_star,  &
     
    4750      save fomass_max,alphamax
    4851
     52      character (len=20) :: modname='thermcell_flux2'
     53      character (len=80) :: abort_message
     54
    4955      fomass_max=0.5
    5056      alphamax=0.7
     
    8894                    print*,'alim_star(ig,l)',alim_star(ig,l)
    8995                    print*,'detr_star(ig,l)',detr_star(ig,l)
    90 !                   stop
    9196               endif
    9297            else
     
    96101                    print*,'alim_star(ig,l)',alim_star(ig,l)
    97102                    print*,'detr_star(ig,l)',detr_star(ig,l)
    98                     stop
     103                    abort_message = ''
     104                    CALL abort_gcm (modname,abort_message,1)
    99105               endif
    100106            endif
     
    256262            if (entr(ig,l)<0.) then
    257263               print*,'N1 ig,l,entr',ig,l,entr(ig,l)
    258                stop 'entr negatif'
     264               abort_message = 'entr negatif'
     265               CALL abort_gcm (modname,abort_message,1)
    259266            endif
    260267            if (detr(ig,l).gt.fm(ig,l)) then
     
    285292               print*,'entr(ig,l)',entr(ig,l)
    286293               print*,'fm(ig,l)',fm(ig,l)
    287                stop 'probleme dans thermcell flux'
     294               abort_message = 'probleme dans thermcell flux'
     295               CALL abort_gcm (modname,abort_message,1)
    288296            endif
    289297         enddo
     
    312320               print*,'detr(ig,l)',detr(ig,l)
    313321               print*,'fm(ig,l)',fm(ig,l)
    314                stop 'probleme dans thermcell flux'
     322               abort_message = 'probleme dans thermcell flux'
     323               CALL abort_gcm (modname,abort_message,1)
    315324            endif
    316325        enddo
     
    413422                         print*,'fm(ig,l+1)',fm(ig,l+1)
    414423                         print*,'fm(ig,l)',fm(ig,l)
    415                          stop 'probleme dans thermcell_flux'
     424                         abort_message = 'probleme dans thermcell_flux'
     425                         CALL abort_gcm (modname,abort_message,1)
    416426                      endif
    417427                      entr(ig,l+1)=entr(ig,l+1)-ddd
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/thermcell_main.F90

    r1294 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      SUBROUTINE thermcell_main(itap,ngrid,nlay,ptimestep  &
     
    170170      character*2 str2
    171171      character*10 str10
     172
     173      character (len=20) :: modname='thermcell_main'
     174      character (len=80) :: abort_message
    172175
    173176      EXTERNAL SCOPY
     
    466469! Test valable seulement en 1D mais pas genant
    467470      if (.not. (f0(1).ge.0.) ) then
    468            stop'Dans thermcell_main'
     471              abort_message = '.not. (f0(1).ge.0.)'
     472              CALL abort_gcm (modname,abort_message,1)
    469473      endif
    470474
     
    781785      if (prt_level.ge.1) print*,'thermcell_main FIN  OK'
    782786
    783 !     if(icount.eq.501) stop'au pas 301 dans thermcell_main'
    784787      return
    785788      end
     
    817820                  write(6,'(i3,7f10.3)') k,pplay(i,k),ztv(i,k),1000*po(i,k),ztva(i,k),1000*zqla(i,k),f_star(i,k),zw2(i,k)
    818821               enddo
    819 !              stop
    820822           endif
    821823         enddo
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/thermcell_old.F

    r987 r1299  
    112112      character (len=10) :: str10
    113113
     114      character (len=20) :: modname='thermcell2002'
     115      character (len=80) :: abort_message
     116
    114117      LOGICAL vtest(klon),down
    115118
     
    336339            if(w2di.eq.2) then
    337340               entr(ig,k)=entr(ig,k)+
    338      s         ptimestep*(zzz-entr(ig,k))/float(tho)
     341     s         ptimestep*(zzz-entr(ig,k))/REAL(tho)
    339342            else
    340343               entr(ig,k)=zzz
     
    379382c     print*,'ig,l+1,ztv(ig,l+1)'
    380383c     print*, ig,l+1,ztv(ig,l+1)
    381 c        stop'dans thermiques'
    382384c     endif
    383385               zw2(ig,l+1)=2.*RG*(ztv(ig,l)-ztv(ig,l+1))/ztv(ig,l+1)
     
    395397c     print*,'Tv ',(ztv(ig,ll),ll=1,klev)
    396398c     print*,'Entr ',(entr(ig,ll),ll=1,klev)
    397 c        stop'dans thermiques'
    398399c     endif
    399400               ztva(ig,l)=(fmc(ig,l)*ztva(ig,l-1)+entr(ig,l)*ztv(ig,l))
     
    517518         do ig=1,ngrid
    518519            if(fracd(ig,l).lt.0.1) then
    519                stop'fracd trop petit'
    520             else
     520              abort_message = 'fracd trop petit'
     521              CALL abort_gcm (modname,abort_message,1)
     522           else
    521523c    vitesse descendante "diagnostique"
    522524               wd(ig,l)=fm(ig,l)/(fracd(ig,l)*rhobarz(ig,l))
     
    588590
    589591      if (w2di.eq.1) then
    590          fm0=fm0+ptimestep*(fm-fm0)/float(tho)
    591          entr0=entr0+ptimestep*(entr-entr0)/float(tho)
     592         fm0=fm0+ptimestep*(fm-fm0)/REAL(tho)
     593         entr0=entr0+ptimestep*(entr-entr0)/REAL(tho)
    592594      else
    593595         fm0=fm
     
    10001002      character*2 str2
    10011003      character*10 str10
     1004
     1005      character (len=20) :: modname='thermcell_cld'
     1006      character (len=80) :: abort_message
    10021007
    10031008      LOGICAL vtest(klon),down
     
    18551860       if (l.eq.klev) then
    18561861          print*,'THERMCELL PB ig=',ig,'   l=',l
    1857           stop
     1862          abort_message = 'THERMCELL PB'
     1863          CALL abort_gcm (modname,abort_message,1)
    18581864       endif
    18591865!       if ((zw2(ig,l+1).gt.1.e-10).and.(zw2(ig,l).gt.1.e-10).and.
     
    21642170         do ig=1,ngrid
    21652171            if(fracd(ig,l).lt.0.1.and.(test(ig).eq.1)) then
    2166                stop'fracd trop petit'
     2172              abort_message = 'fracd trop petit'
     2173              CALL abort_gcm (modname,abort_message,1)
    21672174            else
    21682175c    vitesse descendante "diagnostique"
     
    22622269
    22632270      if (w2di.eq.1) then
    2264          fm0=fm0+ptimestep*(fm-fm0)/float(tho)
    2265          entr0=entr0+ptimestep*(alim+entr-entr0)/float(tho)
     2271         fm0=fm0+ptimestep*(fm-fm0)/REAL(tho)
     2272         entr0=entr0+ptimestep*(alim+entr-entr0)/REAL(tho)
    22662273      else
    22672274         fm0=fm
     
    27472754      character*10 str10
    27482755
     2756      character (len=20) :: modname='thermcell_eau'
     2757      character (len=80) :: abort_message
     2758
    27492759      LOGICAL vtest(klon),down
    27502760      LOGICAL Zsat(klon)
     
    34103420         do ig=1,ngrid
    34113421            if(fracd(ig,l).lt.0.1) then
    3412                stop'fracd trop petit'
     3422              abort_message = 'fracd trop petit'
     3423              CALL abort_gcm (modname,abort_message,1)
    34133424            else
    34143425c    vitesse descendante "diagnostique"
     
    34813492
    34823493      if (w2di.eq.1) then
    3483          fm0=fm0+ptimestep*(fm-fm0)/float(tho)
    3484          entr0=entr0+ptimestep*(entr-entr0)/float(tho)
     3494         fm0=fm0+ptimestep*(fm-fm0)/REAL(tho)
     3495         entr0=entr0+ptimestep*(entr-entr0)/REAL(tho)
    34853496      else
    34863497         fm0=fm
     
    38483859      character*10 str10
    38493860
     3861      character (len=20) :: modname='thermcell'
     3862      character (len=80) :: abort_message
     3863
    38503864      LOGICAL vtest(klon),down
    38513865
     
    43944408         do ig=1,ngrid
    43954409            if(fracd(ig,l).lt.0.1) then
    4396                stop'fracd trop petit'
     4410              abort_message = 'fracd trop petit'
     4411              CALL abort_gcm (modname,abort_message,1)
    43974412            else
    43984413c    vitesse descendante "diagnostique"
     
    44774492cRC
    44784493      if (w2di.eq.1) then
    4479          fm0=fm0+ptimestep*(fm-fm0)/float(tho)
    4480          entr0=entr0+ptimestep*(entr-entr0)/float(tho)
     4494         fm0=fm0+ptimestep*(fm-fm0)/REAL(tho)
     4495         entr0=entr0+ptimestep*(entr-entr0)/REAL(tho)
    44814496      else
    44824497         fm0=fm
     
    52575272      character*10 str10
    52585273
     5274      character (len=20) :: modname='thermcell_sec'
     5275      character (len=80) :: abort_message
     5276
    52595277      LOGICAL vtest(klon),down
    52605278
     
    58225840         do ig=1,ngrid
    58235841            if(fracd(ig,l).lt.0.1) then
    5824                stop'fracd trop petit'
     5842              abort_message = 'fracd trop petit'
     5843              CALL abort_gcm (modname,abort_message,1)
    58255844            else
    58265845c    vitesse descendante "diagnostique"
     
    59055924cRC
    59065925      if (w2di.eq.1) then
    5907          fm0=fm0+ptimestep*(fm-fm0)/float(tho)
    5908          entr0=entr0+ptimestep*(entr-entr0)/float(tho)
     5926         fm0=fm0+ptimestep*(fm-fm0)/REAL(tho)
     5927         entr0=entr0+ptimestep*(entr-entr0)/REAL(tho)
    59095928      else
    59105929         fm0=fm
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/thermcell_plume.F90

    r1294 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      SUBROUTINE thermcell_plume(itap,ngrid,klev,ptimestep,ztv,zthl,po,zl,rhobarz,  &
     
    436436            if (zw2(ig,l+1)>0. .and. zw2(ig,l+1).lt.1.e-10) then
    437437!               stop'On tombe sur le cas particulier de thermcell_dry'
    438                 print*,'On tombe sur le cas particulier de thermcell_plume'
     438                write(lunout,*)                                         &
     439     &          'On tombe sur le cas particulier de thermcell_plume'
    439440                zw2(ig,l+1)=0.
    440441                linter(ig)=l+1
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/tracinca_mod.F90

    r1279 r1299  
    4545    USE vampir
    4646    USE comgeomphy
     47    USE control_mod
     48
    4749   
    4850    IMPLICIT NONE
    4951   
    5052    INCLUDE "indicesol.h"
    51     INCLUDE "control.h"
    5253    INCLUDE "dimensions.h"
    5354    INCLUDE "paramet.h"
     
    125126    CALL VTb(VTinca)
    126127   
    127     calday = FLOAT(julien) + gmtime
     128    calday = REAL(julien) + gmtime
    128129    ncsec  = NINT (86400.*gmtime)
    129130     
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/undefSTD.F

    r1279 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      SUBROUTINE undefSTD(nlevSTD,itap,tlevSTD,
     
    1313c I. Musat : 09.2004
    1414c
    15 c Calcul * du nombre de pas de temps (FLOAT(ecrit_XXX)-tnondef))
     15c Calcul * du nombre de pas de temps (REAL(ecrit_XXX)-tnondef))
    1616c          ou la variable tlevSTD est bien definie (.NE.1.E+20),
    1717c et
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/write_histISCCP.h

    r1045 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      IF (ok_isccp) THEN
     
    7777     .                 meantaucld(:,n))
    7878c
    79         zx_tmp_fi2d(1:klon)=float(seed(1:klon,n))
     79        zx_tmp_fi2d(1:klon)=REAL(seed(1:klon,n))
    8080c
    8181c       print*,'n=',n,' write_ISCCP avant seed'
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/yamada4.F

    r938 r1299  
    11!
    2 ! $Header$
     2! $Id$
    33!
    44      SUBROUTINE yamada4(ngrid,dt,g,rconst,plev,temp
     
    106106c$OMP THREADPRIVATE(rino,smyam,styam,lyam,knyam,w2yam,t2yam)
    107107      logical,save :: firstcall=.true.
     108
     109      character (len=20) :: modname='yamada4'
     110      character (len=80) :: abort_message
     111
    108112c$OMP THREADPRIVATE(firstcall)       
    109113      frif(ri)=0.6588*(ri+0.1776-sqrt(ri*ri-0.3221*ri+0.03156))
     
    128132
    129133      if (.not.(iflag_pbl.ge.6.and.iflag_pbl.le.9)) then
    130            stop'probleme de coherence dans appel a MY'
     134              abort_message = 'probleme de coherence dans appel a MY'
     135              CALL abort_gcm (modname,abort_message,1)
    131136      endif
    132137
Note: See TracChangeset for help on using the changeset viewer.