Ignore:
Timestamp:
09/15/16 17:52:05 (8 years ago)
Author:
dumas
Message:

Bug correction in flottab : call to determin_tache suppressed | sealevel added in Netcdf output class 1

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/SOURCES/Netcdf-routines/sortie_netcdf_GRISLI_mod.0.2-hassine.f90

    r66 r86  
    111111                                                             !< des variables dans chaque fichier  
    112112  integer,dimension(:),allocatable:: idef_time               !< 1 ou 0 si le temp est defini ou non 
     113  integer,dimension(:),allocatable:: idef_sealevel           !< 1 ou 0 si sealevel est defini ou non 
    113114  integer,dimension(:,:),allocatable:: idef                  !< 1 ou 0 si la varaible est defini ou non 
    114115  integer,dimension(:),allocatable :: num_ncdf_file          !< compteur des fichiers netcdf par class   
     
    504505    if (.not.allocated(nrecs) .and. .not.allocated(nbsnap) .and. .not.allocated(num_ncdf_file) & 
    505506         .and. .not. allocated(idef) .and. .not. allocated(idef_time)) then 
    506        allocate(nrecs(nclassout),nbsnap(nclassout),num_ncdf_file(nclassout),idef(nclassout,ntab),idef_time(nclassout)) 
     507       allocate(nrecs(nclassout),nbsnap(nclassout),num_ncdf_file(nclassout),idef(nclassout,ntab),idef_time(nclassout),idef_sealevel(nclassout)) 
    507508       nrecs=1 
    508509       idef=0 
    509510       idef_time=0 
     511       idef_sealevel=0 
    510512       num_ncdf_file=0 
    511513    end if 
     
    516518          idef(j,:)=0 
    517519          idef_time(j)=0 
     520          idef_sealevel(j)=0 
    518521          nbsnap(j)=0 
    519522          ! numerote le fichier sortie 
     
    558561       idef(posis,:)=0 
    559562       idef_time(posis)=0 
     563       idef_sealevel(posis)=0 
    560564       nbsnap(posis)=0 
    561565       ! numerote le fichier sortie 
     
    654658    character(len=20) :: nametmp                         !< nom intermediaire 
    655659    real*8,pointer,dimension(:) :: liste_time => null()  !< liste des snapshot des variables ecrites en netcdf 
     660    real*8,pointer,dimension(:) :: sealevel_p => null()  !< pointeur vers sealevel pour ecriture netcdf 
    656661    real*8,pointer,dimension(:) :: x,y,x1,y1,z,nzzm    
    657662    real*8,pointer,dimension(:,:):: lat,lon => null() 
     
    683688       liste_time(1)=-1 
    684689    end if 
     690    if (.not.associated(sealevel_p)) then 
     691       allocate(sealevel_p(1)) 
     692       sealevel_p(1)=-1 
     693    end if 
    685694 
    686695liste_times:  if ((liste_time(1) .ne.timetmp) .or.(liste_time(1) .eq. -1) ) then 
    687696       liste_time(1)= timetmp 
     697       sealevel_p(1)= sealevel 
    688698       ! print*,"time outncdf=",liste_time(1) 
    689699       write(charint,'(i0)') floor(timetmp) 
     
    720730! ecrit le temps 
    721731          call write_ncdf_var('time','time',trim(fil_sortie(k)),liste_time,nbsnap(k)+1,idef_time(k),'double') 
     732           
     733          sealevel_p=sealevel 
     734          call write_ncdf_var('sealevel','time',trim(fil_sortie(k)),sealevel_p,nrecs(k),idef_sealevel(k),'double') 
    722735 
    723736          fait = .FALSE. 
Note: See TracChangeset for help on using the changeset viewer.