Changeset 1154
- Timestamp:
- May 4, 2009, 5:24:19 PM (16 years ago)
- Location:
- LMDZ4/branches/LMDZ4-dev
- Files:
-
- 16 added
- 11 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ4/branches/LMDZ4-dev/arch/arch-SX8_BRODIE.path
r826 r1154 1 set NETCDF_LIBDIR=/SXlocal/pub/netCDF/ netCDF-3.6.1/lib2 set NETCDF_INCDIR=/SXlocal/pub/netCDF/ netCDF-3.6.1/include1 set NETCDF_LIBDIR=/SXlocal/pub/netCDF/3.6.1-openmp/lib 2 set NETCDF_INCDIR=/SXlocal/pub/netCDF/3.6.1-openmp/include 3 3 set IOIPSL_INCDIR=$LMDGCM/../../lib 4 4 set IOIPSL_LIBDIR=$LMDGCM/../../lib … … 9 9 set INCA_LIBDIR=$LMDGCM/../INCA3/config/lib 10 10 set INCA_INCDIR=$LMDGCM/../INCA3/config/lib 11 -
LMDZ4/branches/LMDZ4-dev/bld.cfg
r1019 r1154 67 67 bld::excl_dep inc::netcdf.inc 68 68 bld::excl_dep use::netcdf 69 bld::excl_dep use::typesizes 69 70 bld::excl_dep h::netcdf.inc 70 71 bld::excl_dep h::mpif.h … … 77 78 bld::excl_dep use::mod_prism_put_proto 78 79 bld::excl_dep use::mkl_dfti 80 79 81 # Don't generate interface files 80 82 bld::tool::geninterface none -
LMDZ4/branches/LMDZ4-dev/libf/dyn3d/etat0_netcdf.F
r1151 r1154 14 14 USE phys_state_var_mod 15 15 USE filtreg_mod 16 use regr_lat_time_climoz_m, only: regr_lat_time_climoz 16 17 #endif 17 18 !#endif of #ifdef CPP_EARTH 19 use netcdf, only: nf90_open, NF90_NOWRITE, nf90_close 18 20 ! 19 21 IMPLICIT NONE 20 22 ! 21 #include "netcdf.inc"22 23 #include "dimensions.h" 23 24 #include "paramet.h" … … 49 50 REAL :: vvent(iip1, jjm, llm) 50 51 REAL :: t3d(iip1, jjp1, llm), tpot(iip1, jjp1, llm) 51 REAL, ALLOCATABLE, DIMENSION(:,:,:,:) :: q3d52 52 REAL :: qsat(iip1, jjp1, llm) 53 REAL,ALLOCATABLE :: q3d(:, :, :,:) 53 54 REAL :: tsol(klon), qsol(klon), sn(klon) 54 REAL :: tsolsrf(klon,nbsrf), qsolsrf(klon,nbsrf),snsrf(klon,nbsrf) 55 !! REAL :: tsolsrf(klon,nbsrf) 56 real qsolsrf(klon,nbsrf),snsrf(klon,nbsrf) 55 57 REAL :: albe(klon,nbsrf), evap(klon,nbsrf) 56 58 REAL :: alblw(klon,nbsrf) … … 72 74 ! 73 75 74 CHARACTER *80:: varname76 CHARACTER(len=80) :: varname 75 77 ! 76 78 INTEGER :: i,j, ig, l, ji,ii1,ii2 … … 102 104 REAL :: w(ip1jmp1,llm) 103 105 REAL ::phystep 104 REAL :: rugsrel(iip1*jjp1)106 CC REAL :: rugsrel(iip1*jjp1) 105 107 REAL :: fder(klon) 106 real zrel(iip1*jjp1),chmin,chmax107 108 CHARACTER*80:: visu_file108 !! real zrel(iip1*jjp1),chmin,chmax 109 110 !! CHARACTER(len=80) :: visu_file 109 111 INTEGER :: visuid 110 112 … … 140 142 REAL :: solarlong0 141 143 real :: seuil_inversion 144 logical read_climoz ! read ozone climatology 142 145 143 146 ! … … 163 166 ! CALL defrun_new(99,.TRUE.,clesphy0) 164 167 CALL conf_gcm( 99, .TRUE. , clesphy0 ) 165 call conf_phys(ok_journe, ok_mensuel, ok_instan, & 166 & ok_hf, ok_LES, & 168 call conf_phys( ok_journe, ok_mensuel, ok_instan, ok_hf, ok_LES, & 167 169 & solarlong0,seuil_inversion, & 168 170 & fact_cldcon, facttemps,ok_newmicro,iflag_radia, & … … 174 176 & iflag_thermals,nsplit_thermals,tau_thermals, & 175 177 & iflag_thermals_ed,iflag_thermals_optflux, & 176 & iflag_coupl,iflag_clos,iflag_wake ) 178 & iflag_coupl,iflag_clos,iflag_wake, read_climoz ) 179 177 180 dtvr = daysec/FLOAT(day_step) 178 181 print*,'dtvr',dtvr 179 182 180 181 182 183 CALL iniconst() 183 184 CALL inigeom() 184 185 185 186 ! Initialisation pour traceurs 186 CALL infotrac_init 187 ALLOCATE(q3d(iip1,jjp1,llm,nqtot)) 188 187 call infotrac_init 188 ALLOCATE(q3d(iip1, jjp1, llm, nqtot)) 189 189 190 190 CALL inifilr() … … 246 246 247 247 write(*,*)'Essai de lecture masque ocean' 248 iret = nf _open("o2a.nc", NF_NOWRITE, nid_o2a)248 iret = nf90_open("o2a.nc", NF90_NOWRITE, nid_o2a) 249 249 if (iret .ne. 0) then 250 250 write(*,*)'ATTENTION!! pas de fichier o2a.nc trouve' … … 265 265 else 266 266 couple = .true. 267 iret = nf _close(nid_o2a)267 iret = nf90_close(nid_o2a) 268 268 call flininfo("o2a.nc", iml_omask, jml_omask, llm_tmp, ttm_tmp 269 269 $ , nid_o2a) … … 402 402 . maxval(qsat(:,:,:)) 403 403 ! 404 WRITE(*,*) 'QSAT :', qsat(10,20,:)404 CC WRITE(*,*) 'QSAT :', qsat(10,20,:) 405 405 ! 406 406 varname = 'q' … … 413 413 q3d(:,:,:,1) = qd(:,:,:) 414 414 ! 415 416 if (read_climoz) call regr_lat_time_climoz ! ozone climatology 417 415 418 varname = 'tsol' 416 419 ! This line needs to be replaced by a call to restget to get the values in the restart file … … 477 480 . jjm, rlonu, rlatv , interbar ) 478 481 c 479 rugsrel(:) = 0.0480 IF(ok_orodr) THEN481 DO i = 1, iip1* jjp1482 rugsrel(i) = MAX( 1.e-05, zstd(i)* zsig(i) /2. )483 ENDDO484 ENDIF482 cc rugsrel(:) = 0.0 483 cc IF(ok_orodr) THEN 484 cc DO i = 1, iip1* jjp1 485 cc rugsrel(i) = MAX( 1.e-05, zstd(i)* zsig(i) /2. ) 486 cc ENDDO 487 cc ENDIF 485 488 486 489 … … 716 719 q_ancien = 0. 717 720 agesno = 0. 721 c 718 722 frugs(1:klon,is_oce) = rugmer(1:klon) 719 723 frugs(1:klon,is_ter) = MAX(1.0e-05, zstd(1:klon)*zsig(1:klon)/2.0) … … 752 756 753 757 C Sortie Visu pour les champs dynamiques 754 if (1.eq.0 ) then755 print*,'sortie visu'756 time_step = 1.757 t_ops = 2.758 t_wrt = 2.759 itau = 2.760 visu_file='Etat0_visu.nc'761 CALL initdynav(visu_file,dayref,anneeref,time_step,762 . t_ops, t_wrt, visuid)763 CALL writedynav(visuid, itau,vvent ,764 . uvent,tpot,pk,phi,q3d,masse,psol,phis)765 else758 cc if (1.eq.0 ) then 759 cc print*,'sortie visu' 760 cc time_step = 1. 761 cc t_ops = 2. 762 cc t_wrt = 2. 763 cc itau = 2. 764 cc visu_file='Etat0_visu.nc' 765 cc CALL initdynav(visu_file,dayref,anneeref,time_step, 766 cc . t_ops, t_wrt, visuid) 767 cc CALL writedynav(visuid, itau,vvent , 768 cc . uvent,tpot,pk,phi,q3d,masse,psol,phis) 769 cc else 766 770 print*,'CCCCCCCCCCCCCCCCCC REACTIVER SORTIE VISU DANS ETAT0' 767 endif771 cc endif 768 772 print*,'entree histclo' 769 773 CALL histclo 770 771 DEALLOCATE(q3d)772 774 773 775 #endif … … 776 778 ! 777 779 END SUBROUTINE etat0_netcdf 778 -
LMDZ4/branches/LMDZ4-dev/libf/dyn3d/temps.h
r792 r1154 15 15 16 16 INTEGER itaufin 17 INTEGER *4itau_dyn, itau_phy18 INTEGER *4day_ini, day_end, annee_ref, day_ref17 INTEGER(kind=4) itau_dyn, itau_phy 18 INTEGER(kind=4) day_ini, day_end, annee_ref, day_ref 19 19 REAL dt 20 20 -
LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/etat0_netcdf.F
r1151 r1154 9 9 USE ioipsl 10 10 USE dimphy 11 USE infotrac 11 12 USE fonte_neige_mod 12 13 USE pbl_surface_mod 13 14 USE phys_state_var_mod 14 15 USE filtreg_mod 15 USE infotrac16 use regr_lat_time_climoz_m, only: regr_lat_time_climoz 16 17 #endif 17 18 !#endif of #ifdef CPP_EARTH 19 use netcdf, only: nf90_open, NF90_NOWRITE, nf90_close 18 20 ! 19 21 IMPLICIT NONE 20 22 ! 21 #include "netcdf.inc"22 23 #include "dimensions.h" 23 24 #include "paramet.h" … … 43 44 ! local variables: 44 45 REAL :: latfi(klon), lonfi(klon) 45 REAL :: orog(iip1,jjp1), rugo(iip1,jjp1) ,46 .psol(iip1, jjp1), phis(iip1, jjp1)46 REAL :: orog(iip1,jjp1), rugo(iip1,jjp1) 47 REAL :: psol(iip1, jjp1), phis(iip1, jjp1) 47 48 REAL :: p3d(iip1, jjp1, llm+1) 48 49 REAL :: uvent(iip1, jjp1, llm) … … 52 53 REAL,ALLOCATABLE :: q3d(:, :, :,:) 53 54 REAL :: tsol(klon), qsol(klon), sn(klon) 54 REAL :: tsolsrf(klon,nbsrf), qsolsrf(klon,nbsrf),snsrf(klon,nbsrf) 55 !! REAL :: tsolsrf(klon,nbsrf) 56 real qsolsrf(klon,nbsrf),snsrf(klon,nbsrf) 55 57 REAL :: albe(klon,nbsrf), evap(klon,nbsrf) 56 58 REAL :: alblw(klon,nbsrf) … … 72 74 ! 73 75 74 CHARACTER *80:: varname76 CHARACTER(len=80) :: varname 75 77 ! 76 78 INTEGER :: i,j, ig, l, ji,ii1,ii2 77 INTEGER :: nq78 79 REAL :: xpi 79 80 ! … … 103 104 REAL :: w(ip1jmp1,llm) 104 105 REAL ::phystep 105 REAL :: rugsrel(iip1*jjp1)106 CC REAL :: rugsrel(iip1*jjp1) 106 107 REAL :: fder(klon) 107 real zrel(iip1*jjp1),chmin,chmax108 109 CHARACTER*80:: visu_file108 !! real zrel(iip1*jjp1),chmin,chmax 109 110 !! CHARACTER(len=80) :: visu_file 110 111 INTEGER :: visuid 111 112 … … 141 142 REAL :: solarlong0 142 143 real :: seuil_inversion 144 logical read_climoz ! read ozone climatology 143 145 144 146 ! … … 174 176 & iflag_thermals,nsplit_thermals,tau_thermals, & 175 177 & iflag_thermals_ed,iflag_thermals_optflux, & 176 & iflag_coupl,iflag_clos,iflag_wake )178 & iflag_coupl,iflag_clos,iflag_wake, read_climoz ) 177 179 178 180 dtvr = daysec/FLOAT(day_step) … … 181 183 CALL iniconst() 182 184 CALL inigeom() 183 ! 185 184 186 CALL inifilr() 185 C initpour traceurs187 ! Initialisation pour traceurs 186 188 call infotrac_init 187 ALLOCATE(q3d(iip1, jjp1, llm, nqtot))188 ! 189 ALLOCATE(q3d(iip1, jjp1, llm, nqtot)) 190 ! CALL phys_state_var_init() 189 191 ! 190 192 latfi(1) = ASIN(1.0) … … 243 245 244 246 write(*,*)'Essai de lecture masque ocean' 245 iret = nf _open("o2a.nc", NF_NOWRITE, nid_o2a)247 iret = nf90_open("o2a.nc", NF90_NOWRITE, nid_o2a) 246 248 if (iret .ne. 0) then 247 249 write(*,*)'ATTENTION!! pas de fichier o2a.nc trouve' … … 262 264 else 263 265 couple = .true. 264 iret = nf _close(nid_o2a)266 iret = nf90_close(nid_o2a) 265 267 call flininfo("o2a.nc", iml_omask, jml_omask, llm_tmp, ttm_tmp 266 268 $ , nid_o2a) … … 399 401 . maxval(qsat(:,:,:)) 400 402 ! 401 WRITE(*,*) 'QSAT :', qsat(10,20,:)403 CC WRITE(*,*) 'QSAT :', qsat(10,20,:) 402 404 ! 403 405 varname = 'q' … … 410 412 q3d(:,:,:,1) = qd(:,:,:) 411 413 ! 414 415 if (read_climoz) call regr_lat_time_climoz ! ozone climatology 416 412 417 varname = 'tsol' 413 418 ! This line needs to be replaced by a call to restget to get the values in the restart file … … 474 479 . jjm, rlonu, rlatv , interbar ) 475 480 c 476 rugsrel(:) = 0.0477 IF(ok_orodr) THEN478 DO i = 1, iip1* jjp1479 rugsrel(i) = MAX( 1.e-05, zstd(i)* zsig(i) /2. )480 ENDDO481 ENDIF481 cc rugsrel(:) = 0.0 482 cc IF(ok_orodr) THEN 483 cc DO i = 1, iip1* jjp1 484 cc rugsrel(i) = MAX( 1.e-05, zstd(i)* zsig(i) /2. ) 485 cc ENDDO 486 cc ENDIF 482 487 483 488 … … 750 755 751 756 C Sortie Visu pour les champs dynamiques 752 if (1.eq.0 ) then753 print*,'sortie visu'754 time_step = 1.755 t_ops = 2.756 t_wrt = 2.757 itau = 2.758 visu_file='Etat0_visu.nc'759 CALL initdynav(visu_file,dayref,anneeref,time_step,760 . t_ops, t_wrt, visuid)761 CALL writedynav(visuid, itau,vvent ,762 . uvent,tpot,pk,phi,q3d,masse,psol,phis)763 else757 cc if (1.eq.0 ) then 758 cc print*,'sortie visu' 759 cc time_step = 1. 760 cc t_ops = 2. 761 cc t_wrt = 2. 762 cc itau = 2. 763 cc visu_file='Etat0_visu.nc' 764 cc CALL initdynav(visu_file,dayref,anneeref,time_step, 765 cc . t_ops, t_wrt, visuid) 766 cc CALL writedynav(visuid, itau,vvent , 767 cc . uvent,tpot,pk,phi,q3d,masse,psol,phis) 768 cc else 764 769 print*,'CCCCCCCCCCCCCCCCCC REACTIVER SORTIE VISU DANS ETAT0' 765 endif770 cc endif 766 771 print*,'entree histclo' 767 772 CALL histclo … … 772 777 ! 773 778 END SUBROUTINE etat0_netcdf 774 -
LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/temps.h
r985 r1154 15 15 16 16 INTEGER itaufin 17 INTEGER *4itau_dyn, itau_phy18 INTEGER *4day_ini, day_end, annee_ref, day_ref17 INTEGER(kind=4) itau_dyn, itau_phy 18 INTEGER(kind=4) day_ini, day_end, annee_ref, day_ref 19 19 REAL dt 20 20 !$OMP THREADPRIVATE(/temps/) -
LMDZ4/branches/LMDZ4-dev/libf/phylmd/clesphys.h
r1150 r1154 13 13 INTEGER nbapp_rad, iflag_con 14 14 REAL co2_ppm, solaire 15 REAL *8RCO2, RCH4, RN2O, RCFC11, RCFC1216 REAL *8CH4_ppb, N2O_ppb, CFC11_ppt, CFC12_ppt15 REAL(kind=8) RCO2, RCH4, RN2O, RCFC11, RCFC12 16 REAL(kind=8) CH4_ppb, N2O_ppb, CFC11_ppt, CFC12_ppt 17 17 18 18 !OM ---> correction du bilan d'eau global … … 39 39 !IM lev_histmth : niveau sorties mensuelles 40 40 INTEGER lev_histhf, lev_histday, lev_histmth 41 CHARACTER *4type_run41 CHARACTER(len=4) type_run 42 42 ! aer_type: pour utiliser un fichier constant dans readaerosol 43 43 CHARACTER*8 :: aer_type -
LMDZ4/branches/LMDZ4-dev/libf/phylmd/conf_phys.F90
r1150 r1154 7 7 8 8 subroutine conf_phys(ok_journe, ok_mensuel, ok_instan, ok_hf, & 9 &ok_LES,&10 &solarlong0,seuil_inversion, &11 &fact_cldcon, facttemps,ok_newmicro,iflag_radia,&12 &iflag_cldcon, &13 &iflag_ratqs,ratqsbas,ratqshaut, &14 &ok_ade, ok_aie, aerosol_couple, &15 &flag_aerosol, new_aod, &16 &bl95_b0, bl95_b1,&17 &iflag_thermals,nsplit_thermals,tau_thermals, &18 &iflag_thermals_ed,iflag_thermals_optflux, &19 & iflag_coupl,iflag_clos,iflag_wake)9 ok_LES,& 10 solarlong0,seuil_inversion, & 11 fact_cldcon, facttemps,ok_newmicro,iflag_radia,& 12 iflag_cldcon, & 13 iflag_ratqs,ratqsbas,ratqshaut, & 14 ok_ade, ok_aie, aerosol_couple, & 15 flag_aerosol, new_aod, & 16 bl95_b0, bl95_b1,& 17 iflag_thermals,nsplit_thermals,tau_thermals, & 18 iflag_thermals_ed,iflag_thermals_optflux, & 19 iflag_coupl,iflag_clos,iflag_wake, read_climoz) 20 20 21 21 use IOIPSL … … 140 140 LOGICAL,SAVE :: ok_strato_omp 141 141 LOGICAL,SAVE :: ok_hines_omp 142 143 logical, intent(out):: read_climoz ! read ozone climatology 142 144 ! 143 145 … … 1221 1223 call getin('ecrit_LES', ecrit_LES_omp) 1222 1224 ! 1225 read_climoz = .false. ! default value 1226 call getin('read_climoz', read_climoz) 1223 1227 1224 1228 !$OMP END MASTER … … 1467 1471 1468 1472 write(numout,*)' lonmin lonmax latmin latmax bilKP_ins =',& 1469 &lonmin_ins, lonmax_ins, latmin_ins, latmax_ins1473 lonmin_ins, lonmax_ins, latmin_ins, latmax_ins 1470 1474 write(numout,*)' ecrit_ hf, day, mth, reg, tra, ISCCP, LES',& 1471 &ecrit_hf, ecrit_day, ecrit_mth, ecrit_reg, ecrit_tra, ecrit_ISCCP, ecrit_LES1475 ecrit_hf, ecrit_day, ecrit_mth, ecrit_reg, ecrit_tra, ecrit_ISCCP, ecrit_LES 1472 1476 1473 1477 write(numout,*) 'ok_strato = ', ok_strato 1474 1478 write(numout,*) 'ok_hines = ', ok_hines 1479 write(numout,*) 'read_climoz = ', read_climoz 1475 1480 1476 1481 !$OMP END MASTER -
LMDZ4/branches/LMDZ4-dev/libf/phylmd/indicesol.h
r793 r1154 24 24 PARAMETER (epsfra=1.0E-05) 25 25 ! 26 CHARACTER *3clnsurf(nbsrf)26 CHARACTER(len=3) clnsurf(nbsrf) 27 27 DATA clnsurf/'ter', 'lic', 'oce', 'sic'/ 28 28 SAVE clnsurf -
LMDZ4/branches/LMDZ4-dev/libf/phylmd/physiq.F
r1150 r1154 28 28 USE fonte_neige_mod, ONLY : fonte_neige_get_vars 29 29 USE phys_output_mod 30 use open_climoz_m, only: open_climoz ! ozone climatology 31 use regr_pr, only: regr_pr_av 32 use netcdf95, only: nf95_close 33 use mod_phys_lmdz_mpi_data, only: is_mpi_root 30 34 31 35 IMPLICIT none … … 710 714 SAVE lmt_pas ! frequence de mise a jour 711 715 c$OMP THREADPRIVATE(lmt_pas) 716 real zmasse(klon, llm) 717 C (column-density of mass of air in a cell, in kg m-2) 718 real, parameter:: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2 712 719 713 720 cIM sorties … … 1093 1100 LOGICAL,SAVE :: first=.true. 1094 1101 c$OMP THREADPRIVATE(first) 1102 1103 logical, save:: read_climoz ! read ozone climatology 1104 integer, save:: ncid_climoz ! NetCDF file containing ozone climatology 1105 1106 real, pointer, save:: press_climoz(:) 1107 ! edges of pressure intervals for ozone climatology, in Pa, in strictly 1108 ! ascending order 1109 1095 1110 #include "YOMCST.h" 1096 1111 #include "YOETHF.h" … … 1139 1154 1140 1155 torsfc=0. 1156 forall (k=1: llm) zmasse(:, k) = (paprs(:, k)-paprs(:, k+1)) / rg 1141 1157 1142 1158 if (first) then … … 1234 1250 . iflag_thermals_ed,iflag_thermals_optflux, 1235 1251 cnv flags pour la convection et les poches froides 1236 . iflag_coupl,iflag_clos,iflag_wake )1252 . iflag_coupl,iflag_clos,iflag_wake, read_climoz) 1237 1253 1238 1254 print*,'iflag_coupl,iflag_clos,iflag_wake', … … 1555 1571 call iniradia(klon,klev,paprs(1,1:klev+1)) 1556 1572 1573 C$omp single 1574 if (read_climoz) then 1575 call open_climoz(ncid_climoz, press_climoz) 1576 END IF 1577 C$omp end single 1557 1578 ENDIF 1558 1579 ! … … 1723 1744 c 1724 1745 IF (MOD(itap-1,lmt_pas) .EQ. 0) THEN 1725 if(prt_level.ge.1) WRITE(lunout,*)' PHYS cond julien ',julien 1726 CALL ozonecm( FLOAT(julien), rlat, paprs, wo) 1746 C Once per day, update ozone: 1747 if (read_climoz) then 1748 C Ozone climatology from a NetCDF file 1749 call regr_pr_av(ncid_climoz, "tro3", julien, press_climoz, 1750 $ paprs, wo) 1751 ! Convert from mole fraction of ozone to column density of ozone in a 1752 ! cell, in kDU: 1753 wo = wo * 48. / 29. * zmasse / dobson_u / 1e3 1754 C (By regridding ozone values for LMDZ only once per day, we 1755 C have already neglected the variation of pressure in one 1756 C day. So do not recompute "wo" at each time step even if 1757 C "zmasse" changes a little.) 1758 else 1759 CALL ozonecm(real(julien), rlat, paprs, wo) 1760 end if 1727 1761 ENDIF 1728 1762 c … … 3496 3530 ! write(97) u_seri,v_seri,t_seri,q_seri 3497 3531 ! close(97) 3532 C$OMP single 3533 if (read_climoz) then 3534 if (is_mpi_root) then 3535 call nf95_close(ncid_climoz) 3536 end if 3537 deallocate(press_climoz) ! pointer 3538 end if 3539 C$OMP end single nowait 3498 3540 ENDIF 3499 3541 -
LMDZ4/branches/LMDZ4-dev/makelmdz_fcm
r1140 r1154 210 210 endif 211 211 212 if ( ( "$parallel" == 'omp' || "$parallel" == 'mpi_omp' ) \ 213 && ( "$compil_mod" == 'debug' ) ) then 214 echo 'Usually, parallelization with OpenMP requires some optimization.' 215 echo 'We suggest switching to "-dev".' 216 exit 1 217 ##set COMPIL_FFLAGS="%DEV_FFLAGS" 218 endif 219 212 220 if ( "$veget" == 'true' ) then 213 221 set CPP_KEY="$CPP_KEY CPP_VEGET"
Note: See TracChangeset
for help on using the changeset viewer.