Changeset 269 for LMDZ.3.3/trunk


Ignore:
Timestamp:
Sep 5, 2001, 3:28:02 PM (23 years ago)
Author:
lmdz
Message:

Remplacement des allocates par des dimensionnements classiques. LeVan?
LF

Location:
LMDZ.3.3/trunk/libf/dyn3d
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • LMDZ.3.3/trunk/libf/dyn3d/conf_dat2d.F

    r259 r269  
    4545      ALLOCATE( xtemp(lons) )
    4646      ALLOCATE( ytemp(lats) )
     47      ALLOCATE( champf(lons,lats) )
    4748
    4849      DO i = 1, lons
     
    108109        IF ( invlon )   THEN
    109110
    110            ALLOCATE(champf(lons,lats))
    111            alloc = .TRUE.
     111           DO j = 1, lats
     112            DO i = 1,lons
     113             champf(i,j) = champd(i,j)
     114            ENDDO
     115           ENDDO
    112116
    113117           DO i = 1 ,lons
     
    164168         IF ( invlat )    THEN
    165169
    166            IF(.NOT.alloc)  THEN
    167             ALLOCATE(champf(lons,lats))
    168             alloc = .TRUE.
    169            ENDIF
    170 
    171170           DO j = 1,lats
    172171            yf(j) = ytemp(j)
     
    205204      ENDIF
    206205c
    207        IF(alloc) DEALLOCATE(champf)
     206        DEALLOCATE(champf)
    208207
    209208       DO i = 1, lons
  • LMDZ.3.3/trunk/libf/dyn3d/create_etat0_limit.F

    r259 r269  
    1 C
    2 C $Header$
    3 C
    41       PROGRAM create_etat0_limit
    52c
     
    2320      CALL etat0_netcdf ( interbar )
    2421c
     22      WRITE(6,1)
     23      WRITE(6,*) '  *********************  '
     24      WRITE(6,*) '  ***  Limit_netcdf ***  '
     25      WRITE(6,*) '  *********************  '
     26      WRITE(6,1)
     27c
    2528      CALL  limit_netcdf ( interbar, extrap , oldice )
     29
     301     FORMAT(//)
    2631
    2732      STOP
  • LMDZ.3.3/trunk/libf/dyn3d/inter_barx.F

    r259 r269  
    1 C
    2 C $Header$
    3 C
    41       SUBROUTINE inter_barx ( idatmax,xidat,fdat,imodmax,ximod,fmod )
    52
     
    2421      INTEGER idatmax, imodmax
    2522      REAL xidat(idatmax),fdat(idatmax),ximod(imodmax),fmod(imodmax)
    26       INTEGER imod,idat,i,ichang,id0,id1,nid,idatmax1
     23
     24c    ...  Variables locales ...
     25   
     26      REAL xxid(idatmax+1), xxd(idatmax+1), fdd(idatmax+1)
     27      REAL  fxd(idatmax+1), xchan(idatmax+1), fdchan(idatmax+1)
     28      REAL  xxim(imodmax)
     29
    2730      REAL x0,xim0,dx,dxm
    2831      REAL chmin,chmax,pi
    2932
    30    
    31       REAL,ALLOCATABLE :: xxid(:)
    32       REAL,ALLOCATABLE :: xxd(:)
    33       REAL,ALLOCATABLE :: fdd(:)
    34       REAL,ALLOCATABLE :: fxd(:)
    35       REAL,ALLOCATABLE :: xchan(:)
    36       REAL,ALLOCATABLE :: fdchan(:)
    37       REAL,ALLOCATABLE :: xxim(:)
    38 
    39       ALLOCATE( xxid(idatmax+1))
    40       ALLOCATE( xxd(idatmax+1))
    41       ALLOCATE( fdd(idatmax+1))
    42       ALLOCATE( fxd(idatmax+1))
    43       ALLOCATE( xchan(idatmax+1))
    44       ALLOCATE( fdchan(idatmax+1))
    45       ALLOCATE( xxim(imodmax))
    46 
     33      INTEGER imod,idat,i,ichang,id0,id1,nid,idatmax1
    4734     
    4835      pi = 2. * ASIN(1.)
  • LMDZ.3.3/trunk/libf/dyn3d/inter_barxy.F

    r259 r269  
    1 C
    2 C $Header$
    3 C
    41       SUBROUTINE inter_barxy ( interfd,jnterfd,dlonid,dlatid ,
    52     ,        champ,imod,jmod,rlonimod,rlatimod, jsort,champint )
     
    1613#include "comgeom2.h"
    1714
    18        REAL champx(iip1),chpn(iip1),chps(iip1)
     15       REAL champx(imod),champy(jnterfd +1,imod),chpn(imod),chps(imod)
    1916       REAL chhpn,chhps
    2017       REAL fmody(jjp1)
    21        INTEGER jmp1
    22    
    23        REAL,ALLOCATABLE :: champy(:,:)
    24        ALLOCATE(champy(jnterfd+1,iip1))
    2518c
    2619
     20         print *,' NEEEEE BY ** '
    2721       DO j = 1, jnterfd + 1
    2822        CALL inter_barx( interfd, dlonid, champ( 1,j ),
    2923     ,                       imod, rlonimod , champx )
    30        
    3124         DO i = 1,imod
    3225           champy(j,i) = champx(i)
     
    3629       DO i = 1, imod
    3730        CALL inter_bary( jjm,jnterfd,dlatid,champy(1,i),
    38      ,                        jmod ,rlatimod,  fmody     )
     31     ,                     jmod ,rlatimod,  fmody     )
    3932          DO j = 1, jsort
    4033           champint(i,j) = fmody(j)
     
    6053       ENDIF
    6154
    62          DEALLOCATE(champy)
    63 
    6455       RETURN
    6556       END
  • LMDZ.3.3/trunk/libf/dyn3d/inter_bary.F

    r259 r269  
    1 C
    2 C $Header$
    3 C
    41       SUBROUTINE inter_bary( jjm, jdatmax, yjdatt, fdatt  ,
    52     ,                       jmodmax, yjmodd,  fmod      )
     
    3431
    3532c  ....  Arguments  en entree  .......
    36 c
     33
    3734       INTEGER jjm , jdatmax, jmodmax
    38        REAL    yjdatt( 1 ) , fdatt( 1 )
    39        REAL    yjmodd( 1 )     
     35       REAL    yjdatt( jdatmax ) , fdatt( jdatmax +1 )
     36       REAL    yjmodd( jmodmax )     
    4037
    4138c  ....  Arguments  en sortie  .......
     
    4441c
    4542c   ...... Variables locales  ......
     43
     44       INTEGER      jmods
     45
     46       REAL       yjdat ( jdatmax +1 ), fdat( jdatmax +1)
     47       REAL       fscrat( jdatmax +1 )
     48       REAL       yjmod ( jmodmax +1 )
    4649       LOGICAL    decrois
    4750       SAVE       decrois
    48 
     51c
    4952       REAL y0,dy,dym
    5053       INTEGER jdat, jmod,i
    51 
    52        INTEGER     jmods
    53        REAL , ALLOCATABLE :: fdat(:)
    54        REAL , ALLOCATABLE :: yjdat(:)
    55        REAL , ALLOCATABLE :: yjmod(:)
    56        REAL , ALLOCATABLE :: fscrat(:)
    57        ALLOCATE (fdat(jdatmax+1))
    58        ALLOCATE (yjdat(jdatmax+1))
    59        ALLOCATE (yjmod(jmodmax))
    60        ALLOCATE (fscrat(jdatmax+1))
    6154c
    6255
     
    136129       ENDIF
    137130
    138        DEALLOCATE(fdat)
    139        DEALLOCATE(yjdat)
    140        DEALLOCATE(yjmod)
    141        DEALLOCATE(fscrat)
    142 
    143131       RETURN
    144132       END
  • LMDZ.3.3/trunk/libf/dyn3d/ord_coord.F

    r259 r269  
    1 C
    2 C $Header$
    3 C
    41       SUBROUTINE ord_coord ( nmax, xi, xo, decrois )
    52
     
    1310
    1411       INTEGER nmax
    15        REAL xi(1)
    16        INTEGER nscr
    17        PARAMETER ( nscr = 4000 )
    18        REAL xscr(nscr)
     12       REAL xi(nmax)
    1913
    2014c    .....  Arguments  en sortie  .....
    2115c
    22        REAL xo(1)
     16       REAL xo(nmax+1)
    2317       LOGICAL decrois
    2418
    2519c    .... Variables  locales  ....
    2620
     21       REAL xscr(nmax)
    2722       INTEGER i,ii
    2823       REAL pi, degres, chmin, chmax, mult
    2924c
    30 
    31        IF( nmax.GT.nscr )   THEN
    32          PRINT *,' Dans ord_coord  , nmax = ',nmax, 'est plus grand que'
    33      ,, ' nscr !  Mettre nscr a la valeur de nmax et repasser ! ' 
    34          CALL ABORT
    35        ENDIF
    3625
    3726       pi     = 2.*ASIN(1.)
  • LMDZ.3.3/trunk/libf/dyn3d/ord_coordm.F

    r259 r269  
    1 C
    2 C $Header$
    3 C
    41       SUBROUTINE ord_coordm ( nmax, xi, xo, jjm, jmods, decrois )
    52
     
    129c    .....  Arguments  en entree  .....
    1310
    14        INTEGER nmax
    15        REAL xi(1)
    16        INTEGER nscr
    17        PARAMETER ( nscr = 4000 )
    18        REAL xscr(nscr)
     11       INTEGER nmax,jjm
     12       REAL xi(nmax)
    1913
    2014c    .....  Arguments  en sortie  .....
    2115c
    22        REAL xo(1)
     16       REAL xo(nmax+1)
    2317       LOGICAL decrois
    2418       INTEGER jmods
     
    2620c    .... Variables  locales  ....
    2721
    28        INTEGER i,jjm
     22       REAL xscr(nmax)
     23       INTEGER i
    2924       REAL pi, degres, chmin, chmax,mult
    3025c
     
    3833       IF( nmax.EQ.jjm +1 ) jmods = nmax -1
    3934     
    40        IF( nmax.GT.nscr )   THEN
    41          PRINT *,' Dans ord_coord  , nmax = ',nmax, 'est plus grand que'
    42      ,, ' nscr !  Mettre nscr a la valeur de nmax et repasser ! ' 
    43          CALL ABORT
    44        ENDIF
    45 
    4635       pi     = 2.*ASIN(1.)
    4736       degres = 180./pi
Note: See TracChangeset for help on using the changeset viewer.