Changeset 55 for trunk


Ignore:
Timestamp:
02/10/09 15:03:49 (15 years ago)
Author:
pinsard
Message:

parametrisation of SIMULS_IRCAAM/progfiltrage_....f (modulo dimension); add makefile

Location:
trunk/src
Files:
1 added
6 edited
2 copied

Legend:

Unmodified
Added
Removed
  • trunk/src/SIMULS_IRCAAM/prepare_olr_filtre_simulation.m

    r53 r55  
    5454% $Id$ 
    5555% 
     56% - fplod 2009-02-04T09:40:31Z aedon.locean-ipsl.upmc.fr (Darwin) 
     57%   * force output to be written using EEE floating point with little-endian byte  
     58%     order 
    5659% - fplod 2009-02-02T13:45:57Z aedon.locean-ipsl.upmc.fr (Darwin) 
    5760% 
     
    6972global IRCAAM_ID; 
    7073global IRCAAM_OD; 
     74 
     75% force output to be written using EEE floating point with little-endian byte  
     76% order 
     77machineformat='l'  
    7178 
    7279if nargin==2 
     
    140147 
    141148fullfilename=[IRCAAM_OD,'olr_nofiltre_',ircaam_dataset,'_', simulation, '.dat']; 
    142 fid=fopen(fullfilename,'w'); 
     149fid=fopen(fullfilename,'w',machineformat); 
    143150clear fullfilename; 
    144151fwrite(fid,olr,'float'); 
  • trunk/src/SIMULS_IRCAAM/progfiltrage_10_30.f

    r10 r55  
     1c PROGRAM Filtrage 
     2C 
     3C+ 
     4C 
     5C EVOLUTIONS 
     6C =========== 
     7C 
     8C $Id$ 
     9C  
     10C - fplod 2009-02-10T13:22:27Z aedon.locean-ipsl.upmc.fr (Darwin) 
     11C 
     12C   * replaced by progfiltrage_simulation.f 
     13C 
     14C- 
    115 
    2 c PROGRAM Filtrage 
    316 
    417c   filtrage sur olr JAN-DEC de 1968 
  • trunk/src/SIMULS_IRCAAM/progfiltrage_1_8.f

    r10 r55  
    1  
    21c PROGRAM Filtrage 
     2C 
     3C+ 
     4C 
     5C EVOLUTIONS 
     6C =========== 
     7C 
     8C $Id$ 
     9C 
     10C - fplod 2009-02-10T13:22:27Z aedon.locean-ipsl.upmc.fr (Darwin) 
     11C 
     12C   * replaced by progfiltrage_simulation.f modulo dimension 
     13C 
     14C- 
    315 
    416c   filtrage sur olr JAN-DEC de 1968 
  • trunk/src/SIMULS_IRCAAM/progfiltrage_30_100.f

    r10 r55  
    1  
    21c PROGRAM Filtrage 
     2C 
     3C+ 
     4C 
     5C EVOLUTIONS 
     6C =========== 
     7C 
     8C $Id$ 
     9C 
     10C - fplod 2009-02-10T13:22:27Z aedon.locean-ipsl.upmc.fr (Darwin) 
     11C 
     12C   * replaced by progfiltrage_simulation.f modulo dimension 
     13C 
     14C- 
    315 
    416c   filtrage sur olr JAN-DEC de 1968 
  • trunk/src/SIMULS_IRCAAM/progfiltrage_8_28.f

    r10 r55  
    1  
    21c PROGRAM Filtrage 
     2C 
     3C+ 
     4C 
     5C EVOLUTIONS 
     6C =========== 
     7C 
     8C $Id$ 
     9C 
     10C - fplod 2009-02-10T13:22:27Z aedon.locean-ipsl.upmc.fr (Darwin) 
     11C 
     12C   * replaced by progfiltrage_simulation.f modulo dimension 
     13C 
     14C- 
    315 
    416c   filtrage sur olr JAN-DEC de 1968 
  • trunk/src/SIMULS_IRCAAM/progfiltrage_simulation.f

    r22 r55  
    1  
    2 c PROGRAM Filtrage 
    3  
    4 c   filtrage sur olr JAN-DEC de 1968 
    5  
    6       parameter (nb=3538.,period1=10.,period2=30.) 
    7  
    8        dimension olr(24,15,nb),vb(nb) 
    9        dimension vvb(nb),vvvb(nb),olrf(24,15,nb) 
    10  
    11       open(1,file='olr_ctl.dat'  
    12      *,form='unformatted',access='direct',recl=nb*24*15*4) 
    13       read(1,rec=1)  
    14      *(((olr(i,j,k),i=1,24),j=1,15),k=1,nb) 
    15       close(1) 
     1      PROGRAM progfiltrage_simulation 
     2C+ 
     3C 
     4C NAME 
     5C ==== 
     6C 
     7C ``progfiltrage_simulation.x`` 
     8C 
     9C SYNOPSIS 
     10C ======== 
     11C 
     12C ``progfiltrage_simulation.x`` 
     13C 
     14C DESCRIPTION 
     15C =========== 
     16C 
     17C filtrage sur olr JAN-DEC de 1968 
     18C ++ 
     19C 
     20C From olr_nofiltre_arpege_ \ *simulation*\ .dat. 
     21C ``progfiltrage_simulation.x`` compute ++. 
     22C 
     23C ``progfiltrage_simulation.x`` write 
     24C olr_filtre_\ *period1*\ -\ *period2*\ d_arpege_ \ *simulation*\ .dat. 
     25C 
     26C 
     27C CAUTIONS 
     28C ======== 
     29C 
     30C On MAC ppc, this program must be compile with ``-fendian=little`` 
     31C for g95 
     32C according to machineformat used in prepare_olr_filtre_simulation.m_. 
     33C 
     34C EXAMPLES 
     35C ======== 
     36C 
     37C Following line read ``olr_nofiltre_arpege_AfNQIVIV.dat``, 
     38C compute ++, 
     39C write ``olr_filtre_10-30d_arpege_AfNQIVIV.dat`` 
     40C :: 
     41C 
     42C $ echo "arpege AfNQIVIV 10 30" | progfiltrage_simulation.x - 
     43C 
     44C SEE ALSO 
     45C ======== 
     46C 
     47C prepare_olr_filtre_simulation.m_ 
     48C 
     49C .. _prepare_olr_filtre_simulation.m : prepare_olr_filtre_simulation.m.html 
     50C 
     51C forfilter.f_ 
     52C 
     53C .. _forfilter.f : forfilter.f.html 
     54C 
     55C TODO 
     56C ==== 
     57C 
     58C underflow tracking (see ifort failure) 
     59C 
     60C REAL ou DOUBLE PRECISION dans les fichiers matlab 
     61C 
     62C improve description 
     63C 
     64C improve file pb (err in open/read/write) 
     65C 
     66C F90 modules 
     67C 
     68C portability check because of getenv : now (20090203) written for 
     69C working on zeus using g95 (GCC 4.0.3 (g95!) Jun 18 2006) 
     70C 
     71C use PT fortran tool box ?! when public ... 
     72C 
     73C direct access file ? seems to work but see also 
     74C http://objectmix.com/fortran/305264-read-binaries-matlab.html 
     75C 
     76C EVOLUTIONS 
     77C ========== 
     78C 
     79C $Id$ 
     80C 
     81C - fplod 2009-02-10T13:57:29Z aedon.locean-ipsl.upmc.fr (Darwin) 
     82C 
     83C   * bug fix on output file name to be compatible to convention 
     84C     (not fixed period number of digits) 
     85C 
     86C - fplod 2009-02-02T13:45:57Z aedon.locean-ipsl.upmc.fr (Darwin) 
     87C 
     88C   * created from progfiltrage_10_30.f  to replace it as well as 
     89C     progfiltrage_30_100.f 
     90C 
     91C   * Subroutines externalized in forfilter.f 
     92C 
     93C   * add parameters ircaam_dataset and simulation according to 
     94C     prepare_olr_filtre_simulation.m 
     95C 
     96C   * consolidation : implicit none, inquire iolength, force 
     97C     LITTLE ENDIAN 
     98C 
     99C- 
     100C 
     101      IMPLICIT NONE 
     102 
     103      EXTERNAL FILTRE 
     104 
     105      INTEGER, PARAMETER :: nb = 3660 
     106      INTEGER :: period1 
     107      INTEGER :: period2 
     108C 
     109      INTEGER :: i 
     110      INTEGER :: j 
     111      INTEGER :: k 
     112      INTEGER :: l 
     113      INTEGER :: lon0 
     114      INTEGER :: lat0 
     115C 
     116      REAL :: olr(24,15,nb),vb(nb) 
     117      REAL :: vvb(nb),vvvb(nb),olrf(24,15,nb) 
     118C 
     119      CHARACTER (LEN=255) :: ircaam_id 
     120      CHARACTER (LEN=255) :: ircaam_od 
     121C 
     122      CHARACTER (LEN=255) :: fullfilename 
     123      CHARACTER (LEN=255) :: fullfilename_format 
     124      INTEGER :: record_length = 0 
     125C 
     126      CHARACTER (LEN=6) :: ircaam_dataset 
     127      CHARACTER (LEN=8) :: simulation 
     128      LOGICAL           :: vsel = .TRUE. 
     129 
     130      write (*,*) 'enter ircaam_dataset simulation period1 period2' 
     131      read (*,*) ircaam_dataset,simulation,period1,period2 
     132 
     133      write (*,*) 'ircaam_dataset : ', ircaam_dataset 
     134      write (*,*) 'simulation : ', simulation 
     135      write (*,*) 'period1 : ', period1 
     136      write (*,*) 'period2 : ', period2 
     137 
     138C validation of ircaam_dataset 
     139      IF (ircaam_dataset /= 'arpege') THEN 
     140       vsel = .FALSE. 
     141       WRITE(*,*)' eee : pb validation ircaam_dataset' 
     142      ENDIF 
     143 
     144C validation of simulation 
     145      IF ((simulation /= 'AfNQIVIV') .AND. 
     146     +    (simulation /= 'TrNQIVIV') .AND. 
     147     +    (simulation /= 'AsNQIVIV') .AND. 
     148     +    (simulation /= 'CtIV') .AND. 
     149     +    (simulation /= 'CtCl ')) THEN 
     150       vsel = .FALSE. 
     151       WRITE(*,*)' eee : pb validation simulation' 
     152      ENDIF 
     153 
     154C validation of period1 and period2 
     155 
     156      IF (period1 >= period2) THEN 
     157       vsel = .FALSE. 
     158       WRITE(*,*)' eee : pb validation period1 vs period2' 
     159      ENDIF 
     160C 
     161      IF (.NOT. vsel) THEN 
     162       GOTO 994 
     163      ENDIF 
     164 
     165      CALL GETENV('IRCAAM_ID',ircaam_id) 
     166C++      ircaam_id='/usr/temp/fplod/ircaam_d/' 
     167      CALL GETENV('IRCAAM_OD',ircaam_od) 
     168C++      ircaam_od='/usr/temp/fplod/ircaam_d/' 
     169 
     170      WRITE(fullfilename,'(A,A,A,A,A,A)') 
     171     +TRIM(ircaam_id), 
     172     +'olr_nofiltre_', 
     173     +TRIM(ircaam_dataset), 
     174     +'_', 
     175     +TRIM(simulation), 
     176     +'.dat' 
     177 
     178C ask for record length 
     179      INQUIRE (IOLENGTH=record_length) 
     180     +(((olr(i,j,k),i=1,24),j=1,15),k=1,nb) 
     181 
     182      open(1,file=fullfilename 
     183     +,status='old' 
     184     +,form='unformatted',access='direct',recl=record_length) 
     185 
     186      read(1,rec=1) 
     187     +(((olr(i,j,k),i=1,24),j=1,15),k=1,nb) 
     188 
     189      CLOSE(1) 
    16190 
    17191c  l'ordre maximal du filtrage est tel que 2*MOR+1 < nb 
     
    19193 
    20194      do lon0=1,24 
    21       do lat0=1,15 
    22       do i=1,nb 
    23       vb(i)=olr(lon0,lat0,i) 
     195       do lat0=1,15 
     196        do i=1,nb 
     197         vb(i)=olr(lon0,lat0,i) 
     198        enddo 
     199        call filtre(vb,vvb,REAL(period1),nb) 
     200        call filtre(vb,vvvb,REAL(period2),nb) 
     201        do i=1,nb 
     202         olrf(lon0,lat0,i)=vvb(i)-vvvb(i) 
     203        enddo 
     204       enddo 
    24205      enddo 
    25       call filtre(vb,vvb,period1,nb) 
    26       call filtre(vb,vvvb,period2,nb) 
    27       do i=1,nb 
    28       olrf(lon0,lat0,i)=vvb(i)-vvvb(i) 
    29       enddo 
    30       enddo 
    31       enddo 
    32 c      print*,(olrf(1,1,j),j=1,nb) 
    33  
    34         open(2,file='olrf10-30_clim_sst.80.dat'  
    35      *,form='unformatted',access='direct',recl=24*15*nb*4) 
    36         write(2,rec=1)(((olrf(lon0,lat0,l),lon0=1,24),  
    37      *                lat0=1,15),l=1,nb) 
     206C      print*,(olrf(1,1,j),j=1,nb) 
     207 
     208C adjust format of output filename according to period1 and period2 values 
     209      fullfilename_format = '(A,A,' 
     210      IF (period1 < 10 ) THEN  
     211       fullfilename_format = TRIM(fullfilename_format)//'I1,' 
     212      ENDIF 
     213      IF ((period1 >= 10) .AND. (period1 < 100)) THEN  
     214       fullfilename_format = TRIM(fullfilename_format)//'I2,' 
     215      ENDIF 
     216      IF (period1 >= 100 ) THEN  
     217       fullfilename_format = TRIM(fullfilename_format)//'I3,' 
     218      ENDIF 
     219      fullfilename_format = TRIM(fullfilename_format) //'A,' 
     220      IF (period2 < 10 ) THEN  
     221       fullfilename_format = TRIM(fullfilename_format)//'I1,' 
     222      ENDIF 
     223      IF ((period2 >= 10) .AND. (period2 < 100)) THEN  
     224       fullfilename_format = TRIM(fullfilename_format)//'I2,' 
     225      ENDIF 
     226      IF (period2 >= 100 ) THEN  
     227       fullfilename_format = TRIM(fullfilename_format)//'I3,' 
     228      ENDIF 
     229 
     230      fullfilename_format = TRIM(fullfilename_format)//'A,A,A,A,A)' 
     231 
     232      WRITE(fullfilename,fullfilename_format) 
     233     +TRIM(ircaam_od), 
     234     +'olr_filtre_', 
     235     +period1, 
     236     +'-', 
     237     +period2, 
     238     +'d_', 
     239     +TRIM(ircaam_dataset), 
     240     +'_', 
     241     +TRIM(simulation), 
     242     +'.dat' 
     243 
     244      open(2,file=fullfilename 
     245     +,status='replace' 
     246     +,form='unformatted',access='direct',recl=24*15*nb*4) 
     247 
     248      write(2,rec=1)(((olrf(lon0,lat0,l),lon0=1,24), 
     249     +                lat0=1,15),l=1,nb) 
    38250      close(2) 
    39251 
    40         END 
    41  
    42       SUBROUTINE FILTRE(F,F1,PERIO,N) 
    43       PARAMETER(KOR=4,JOR=4,MOR=50) 
    44       DIMENSION F(N),W(-MOR:mor),G(-MOR:mor),F1(N) 
    45       PI=ACOS(-1.) 
    46       FC=1./PERIO 
    47       CALL KISER(G,MOR) 
    48       DO 1 I=-MOR,MOR 
    49       IF (I.EQ.0) THEN 
    50       W(I)=2.*FC 
    51       ELSE 
    52       W(I)=SIN(2.*PI*FC*FLOAT(I))/(PI*FLOAT(I))*G(I) 
    53       ENDIF 
    54    1  CONTINUE 
    55  
    56       DO 2 I=1,N 
    57       F1(I)=0. 
    58       AT=0. 
    59  
    60       IF(I.LE.KOR) THEN 
    61       L1=-KOR 
    62       L2=I-1 
    63       ENDIF 
    64  
    65       IF((I.GE.KOR+1).AND.(I.LE.MOR)) THEN 
    66       L1=-I+1 
    67       L2=I-1 
    68       ENDIF 
    69  
    70       IF((I.GE.MOR+1).AND.(I.LE.N-MOR)) THEN 
    71       L1=-MOR 
    72       L2=MOR 
    73       ENDIF 
    74  
    75       IF((I.GE.N-MOR+1).AND.(I.LE.N-JOR)) THEN 
    76       L1=-N+I 
    77       L2=N-I 
    78       ENDIF 
    79  
    80       IF(I.GE.N-JOR+1) THEN 
    81       L1=-N+I 
    82       L2=JOR 
    83       ENDIF 
    84  
    85       DO 3 K=L1,L2 
    86       F1(I)=F1(I)+W(K)*F(I-K) 
    87       AT=AT+W(K) 
    88    3  CONTINUE 
    89       F1(I)=F1(I)/AT 
    90    2  CONTINUE 
    91  
    92       RETURN 
     252994   CONTINUE 
     253      STOP 
    93254      END 
    94  
    95       SUBROUTINE KISER(W,MOR) 
    96       PARAMETER(LOR=100) 
    97       DIMENSION W(-MOR:MOR),CO(-LOR:LOR) 
    98  
    99       A=30. 
    100  
    101       IF(A.LE.21.) THEN 
    102       ALPHA=0. 
    103       ENDIF 
    104  
    105       IF((A.LT.50.).AND.(A.GT.21.)) THEN 
    106       ALPHA=0.5842*(A-21.)**0.4+0.07886*(A-21.) 
    107       ENDIF 
    108  
    109       IF(A.GE.50.) THEN 
    110       ALPHA=0.1102*(A-8.7) 
    111       ENDIF 
    112  
    113       DO 2 I=-MOR,MOR 
    114       CO(I)=ALPHA*SQRT(1.-(FLOAT(I)/FLOAT(MOR))**2) 
    115  
    116       N=0 
    117       AS=1. 
    118       AU=1. 
    119       AS1=1. 
    120       AU1=1. 
    121  
    122       DO 10 K=1,200 
    123       N=N+1 
    124  
    125       AU=AU*((CO(I)/2.)/FLOAT(N))**2 
    126       AS=AS+AU 
    127  
    128       AU1=AU1*((ALPHA/2.)/FLOAT(N))**2 
    129       AS1=AS1+AU1 
    130   10  CONTINUE 
    131       W(I)=AS/AS1 
    132    2  CONTINUE 
    133       RETURN 
    134       END 
    135  
    136  
  • trunk/src/forfilter.f

    r22 r55  
     1C 
     2C+ 
     3C 
     4C NAME 
     5C ==== 
     6C 
     7C forfilter 
     8C 
     9C DESCRIPTION 
     10C =========== 
     11C 
     12C filtre kiser ++ 
     13C 
     14C EXAMPLES 
     15C ======== 
     16C 
     17C SEE ALSO 
     18C ======== 
     19C 
     20C progfiltrage_simulation.f_ 
     21C 
     22C .. _progfiltrage_simulation.f : progfiltrage_simulation.f.html 
     23C 
     24C TODO 
     25C ==== 
     26C 
     27C improve comments 
     28C 
     29C add IMPLICIT NONE 
     30C 
     31C find bibliographical reference 
     32C 
     33C f90 module 
     34C 
     35C 2 subroutines so 2 ReSt blocks and 2 files .rst 
     36C 
     37C EVOLUTIONS 
     38C ========== 
     39C 
     40C $Id$ 
     41C 
     42C - fplod 2009-02-10T11:11:33Z aedon.locean-ipsl.upmc.fr (Darwin) 
     43C 
     44C   * replace FLOAT use by generic function REAL 
     45C 
     46C - fplod 2009-02-03T09:21:30Z aedon.locean-ipsl.upmc.fr (Darwin) 
     47C 
     48C    * creation form SIMUL_IRCAAM/progfiltrage_10_30.f 
     49C    * Comments in ReST 
     50C 
     51C- 
     52C 
     53      SUBROUTINE FILTRE(F,F1,PERIO,N) 
    154 
    2 c PROGRAM Filtrage 
     55      IMPLICIT NONE 
    356 
    4 c   filtrage sur olr JAN-DEC de 1968 
     57      INTEGER, PARAMETER :: KOR = 4 
     58      INTEGER, PARAMETER :: JOR = 4 
     59      INTEGER, PARAMETER :: MOR = 50 
    560 
    6       parameter (nb=3538.,period1=10.,period2=30.) 
     61      INTEGER, INTENT(IN) :: N 
     62      REAL, INTENT(IN), DIMENSION(N) :: F 
     63      REAL :: W(-mor:mor) 
     64      REAL :: G(-mor:mor) 
     65      REAL, INTENT(OUT) :: F1(N) 
     66      REAL, INTENT(IN) :: PERIO 
    767 
    8        dimension olr(24,15,nb),vb(nb) 
    9        dimension vvb(nb),vvvb(nb),olrf(24,15,nb) 
     68      INTEGER :: I 
     69      INTEGER :: K 
     70      INTEGER :: L1 
     71      INTEGER :: L2 
    1072 
    11       open(1,file='olr_ctl.dat'  
    12      *,form='unformatted',access='direct',recl=nb*24*15*4) 
    13       read(1,rec=1)  
    14      *(((olr(i,j,k),i=1,24),j=1,15),k=1,nb) 
    15       close(1) 
     73      REAL :: FC 
     74      REAL :: AT 
     75      REAL :: PI 
    1676 
    17 c  l'ordre maximal du filtrage est tel que 2*MOR+1 < nb 
    18 c  veuillez changer dans la subroutine FILTRE le parameter MOR 
    19  
    20       do lon0=1,24 
    21       do lat0=1,15 
    22       do i=1,nb 
    23       vb(i)=olr(lon0,lat0,i) 
    24       enddo 
    25       call filtre(vb,vvb,period1,nb) 
    26       call filtre(vb,vvvb,period2,nb) 
    27       do i=1,nb 
    28       olrf(lon0,lat0,i)=vvb(i)-vvvb(i) 
    29       enddo 
    30       enddo 
    31       enddo 
    32 c      print*,(olrf(1,1,j),j=1,nb) 
    33  
    34         open(2,file='olrf10-30_clim_sst.80.dat'  
    35      *,form='unformatted',access='direct',recl=24*15*nb*4) 
    36         write(2,rec=1)(((olrf(lon0,lat0,l),lon0=1,24),  
    37      *                lat0=1,15),l=1,nb) 
    38       close(2) 
    39  
    40         END 
    41  
    42       SUBROUTINE FILTRE(F,F1,PERIO,N) 
    43       PARAMETER(KOR=4,JOR=4,MOR=50) 
    44       DIMENSION F(N),W(-MOR:mor),G(-MOR:mor),F1(N) 
    4577      PI=ACOS(-1.) 
    4678      FC=1./PERIO 
     
    5082      W(I)=2.*FC 
    5183      ELSE 
    52       W(I)=SIN(2.*PI*FC*FLOAT(I))/(PI*FLOAT(I))*G(I) 
     84      W(I)=SIN(2.*PI*FC*REAL(I))/(PI*REAL(I))*G(I) 
    5385      ENDIF 
    5486   1  CONTINUE 
     
    94126 
    95127      SUBROUTINE KISER(W,MOR) 
    96       PARAMETER(LOR=100) 
    97       DIMENSION W(-MOR:MOR),CO(-LOR:LOR) 
     128C 
     129      IMPLICIT NONE 
     130 
     131      INTEGER, INTENT(IN) :: MOR 
     132      INTEGER, PARAMETER :: LOR = 100 
     133      REAL, INTENT(INOUT), DIMENSION(-MOR:MOR) :: W 
     134      REAL CO(-LOR:LOR) 
     135 
     136      REAL :: A 
     137      REAL :: AS 
     138      REAL :: AS1 
     139      REAL :: AU 
     140      REAL :: AU1 
     141      REAL :: ALPHA 
     142      INTEGER :: I 
     143      INTEGER :: K 
     144      INTEGER :: N 
    98145 
    99146      A=30. 
     
    112159 
    113160      DO 2 I=-MOR,MOR 
    114       CO(I)=ALPHA*SQRT(1.-(FLOAT(I)/FLOAT(MOR))**2) 
     161      CO(I)=ALPHA*SQRT(1.-(REAL(I)/REAL(MOR))**2) 
    115162 
    116163      N=0 
     
    133180      RETURN 
    134181      END 
    135  
    136  
  • trunk/src/ircaam_profile.sh

    r27 r55  
    2525# define IRCAAM environnement 
    2626# 
    27 # ${IRCAAM} is the base directory of tools. 
     27# ${IRCAAM} is the source base directory of tools. 
    2828# 
    2929# ${IRCAAM_LOG} is the directory where log files  will be written. 
     
    3232# 
    3333# ${IRCAAM_OD} is the directory where output files will be written. 
     34# 
     35# ${IRCAAM}/../bin/ is added to PATH. 
    3436# 
    3537# MANPATH++ 
     
    4648# EXAMPLES 
    4749# ======== 
    48 # 
    4950# 
    5051# For fplod, on aedon.locean-ipsl.upmc.fr: 
     
    9798# 
    9899# $Id$ 
     100# 
     101# - fplod 2009-02-04T13:35:30Z zeus.locean-ipsl.upmc.fr (Linux) 
     102# 
     103#  * ${IRCAAM}/../bin/ is added to PATH. 
    99104# 
    100105# - fplod 2008-08-14T12:28:16Z aedon.locean-ipsl.upmc.fr (Darwin) 
     
    203208fi 
    204209# 
     210# add ${IRCAAM}/../bin tools to PATH 
     211# if not already done 
     212echo ${PATH} | grep -q "${IRCAAM}/../bin" 
     213test_path=${?} 
     214if [ ${test_path} -ne 0 ] 
     215then 
     216   PATH=${IRCAAM}/../bin/:${PATH} 
     217   export PATH 
     218else 
     219   # option bavarde oui/non pas encore implantée ++ 
     220   echo "${command} : iii : ${IRCAAM}/../bin/ already in \${PATH}" 
     221fi 
     222# 
    205223IRCAAM_LOG=${tempdir} 
    206224export IRCAAM_LOG 
Note: See TracChangeset for help on using the changeset viewer.