Ignore:
Timestamp:
10/20/17 09:31:39 (7 years ago)
Author:
aquiquet
Message:

Grisli-iLoveclim branch: merged to trunk at revision 145

Location:
branches/iLoveclim
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • branches/iLoveclim

  • branches/iLoveclim/SOURCES/Ant40_files/output_anta40_mod-0.4.f90

    r123 r146  
    1515USE module3D_phy 
    1616use bilan_eau_mod 
    17  
     17use netcdf 
     18use io_netcdf_grisli 
     19use bilan_flux_mod 
    1820 
    1921implicit none 
    2022       
    2123!real ::  vol ; !integer :: np 
     24integer :: nflot                      !< nbr de point flottant 
    2225real ::  bmean                        !< 
    2326real ::  accmean                      !< accumulation moyenne 
     
    3538real ::  hdotmean                     !< moyenne derivee / temps de h 
    3639real ::  bdotmean                     !< moyenne bedrock derive / temps 
    37 real :: volf                          !< volume au dessus de la flottaison 
     40real ::  volf                         !< volume au dessus de la flottaison 
     41 
     42real :: lim                           !< Total ice mass 
     43real :: iareag                        !< surface posee 
     44real :: iareaf                        !< surface flottante 
     45real :: tendacabf                     !< Total SMB flux 
     46real :: tendlibmassbf                 !< Total Basal mass balance flux 
     47real :: tendlicalvf                   !< Total calving flux 
     48real :: tendligroundf                 !< Total grounding line flux 
     49 
     50real,dimension(nx,ny) :: corrsurf     !< facteur de correction de la surface 
     51!real,parameter :: ice_density=910.    !< densite de la glace pour conversion en masse 
     52 
     53! variables netcdf 
     54integer,parameter :: ncshortout=1 ! 1 sorties netcdf short initMIP 
     55integer,parameter :: nvar=8 ! nombre de variables dans le fichier de sortie temporel netcdf  
     56integer :: ncid 
     57integer :: status 
     58integer :: timeDimID 
     59integer :: timeVarID 
     60integer,dimension(nvar) :: varID 
     61integer :: nbtimeout  ! index time output 
     62 
     63real,dimension(nvar) :: var_shortoutput 
    3864 
    3965 
     
    4167 
    4268subroutine init_outshort 
     69 
     70double precision,dimension(:,:),pointer      :: tab               !< tableau 2d real pointer 
     71character(len=100),dimension(nvar) :: namevar ! name, standard_name, long_name, units 
     72character(len=100),dimension(nvar) :: standard_name 
     73character(len=100),dimension(nvar) :: long_name 
     74character(len=100),dimension(nvar) :: units 
    4375 
    4476!ndisp sorite courte tous les ndisp 
    4577NDISP=100 
     78 
     79 
     80 
     81if (ncshortout.eq.1) then  ! ecriture netcdf 
     82 
     83! lecture du fichier avec les corrections de surface 
     84  call Read_Ncdf_var('z',trim(DIRNAMEINP)//'/corrsurf-initMIP-16km.grd',tab) 
     85  corrsurf(:,:)=tab(:,:) 
     86 
     87  open(568,file=trim(dirsource)//'/Fichiers-parametres/short-initMIPnc.dat',status='old') 
     88! lecture en-tete 
     89  read(568,*) 
     90  read(568,*) 
     91  read(568,*) 
     92  read(568,*) 
     93  read(568,*) 
     94! lecture des infos sur les variables : 
     95  do k=1,nvar 
     96    read(568,'(a100)') namevar(k) 
     97    read(568,'(a100)') standard_name(k) 
     98    read(568,'(a100)') long_name(k) 
     99    read(568,'(a100)') units(k) 
     100    read(568,*) 
     101  enddo 
     102  close(568) 
     103! Fichier Netcdf initMIP 
     104! creation du fichier Netcdf : 
     105  status=nf90_create(path = 'short'//runname//'.nc', cmode = nf90_clobber, ncid = ncid) 
     106  if (status /= nf90_noerr) call handle_err(status) 
     107 
     108! definition des dimension : 
     109  status=nf90_def_dim(ncid, name="time", len=NF90_UNLIMITED, dimid=timeDimID) 
     110  if (status /= nf90_noerr) call handle_err(status) 
     111  status=nf90_def_var(ncid, name="time", xtype=nf90_float, dimids=(/ timeDimID/), varid=timeVarID)  
     112  if (status /= nf90_noerr) call handle_err(status) 
     113  status=nf90_put_att(ncid, timeVarID, "standard_name", "time") 
     114  if (status /= nf90_noerr) call handle_err(status) 
     115  status=nf90_put_att(ncid, timeVarID,"units", "years since 2007-01-01 00:00:00") 
     116  if (status /= nf90_noerr) call handle_err(status) 
     117 
     118! definition des variables de sortie : 
     119  do k=1,nvar  ! boucle sur le nbr de variable a definir 
     120    status=nf90_def_var(ncid, name=trim(namevar(k)), xtype=nf90_float, dimids= & 
     121          (/ timeDimID /), varid=varID(k)) 
     122    if (status /= nf90_noerr) call handle_err(status) 
     123    status=nf90_put_att(ncid, varID(k), "standard_name", trim(standard_name(k))) 
     124    if (status /= nf90_noerr) call handle_err(status) 
     125    status=nf90_put_att(ncid, varID(k), "long_name", trim(long_name(k))) 
     126    if (status /= nf90_noerr) call handle_err(status) 
     127    status=nf90_put_att(ncid, varID(k), "units", trim(units(k))) 
     128    if (status /= nf90_noerr) call handle_err(status) 
     129  enddo 
     130 
     131! fin de la definition du fchier : 
     132  status=nf90_enddef(ncid) 
     133  if (status /= nf90_noerr) call handle_err(status) 
     134  nbtimeout = 0 ! initialisation compteur sorties axe time 
     135else ! pas de sortie netcdf et sans correction de surface 
     136  corrsurf(:,:)=1. 
     137endif 
     138 
    46139end subroutine init_outshort 
    47140 
     
    54147!------------------ 
    55148real ::  smax 
     149 
    56150      vol=0.  
    57151      np=0 
     152      nflot=0 
    58153      hmax=0.  
    59154      smax=0. 
     
    74169      bdotmean=0. 
    75170      volf=0. 
    76   
     171      lim=0. 
     172      tendacabf=0. 
     173      iareag=0. 
     174      iareaf=0. 
     175      tendlicalvf=0. 
     176      tendligroundf=0. 
     177      tendlibmassbf=0. 
    77178! 2_preparing outputs 
    78179!--------------------       
    79     do i=1,nx  
    80       do j=1,ny 
    81         if (.not.flot(i,j)) then  
    82 !       if (h(i,j).gt.1.) then  
    83           np=np+1 
    84           vol=vol+h(i,j)  
    85  
    86 !        calcul de la hauteur au dessus de la flottaison 
    87          if (sealevel-B(i,j).le.0.) then    ! socle au dessus du niveau des mers 
    88                volf=volf+h(i,j) 
    89          else 
    90             volf=volf+h(i,j)-row/ro*(sealevel-b(i,j)) 
    91          endif 
    92  
    93  
    94           if (h(i,j).gt.hmax) hmax=h(i,j)  
    95           if (s(i,j).gt.smax) smax=s(i,j)  
    96           bmean=bm(i,j)+bmean  
    97           accmean=acc(i,j)+accmean 
    98           tbmean=tbmean+t(i,j,nz) 
    99           tbdotmean=tbdotmean+tbdot(i,j) 
    100           vsmean=vsmean+sqrt(ux(i,j,1)**2+uy(i,j,1)**2) 
     180    do j=1,ny 
     181      do i=1,nx 
     182        if (ice(i,j).eq.1) then ! point englace 
     183          if (.not.flot(i,j)) then ! point pose  
     184            np=np+1 
     185            vol=vol+h(i,j) 
     186            iareag=iareag+1.*corrsurf(i,j)                            ! surface englacee posee 
     187 
     188!         calcul de la hauteur au dessus de la flottaison 
     189            if (sealevel-B(i,j).le.0.) then    ! socle au dessus du niveau des mers 
     190              volf=volf+h(i,j)*corrsurf(i,j)                          ! volume au-dessus de la flottaison 
     191            else 
     192              volf=volf+(h(i,j)-row/ro*(sealevel-b(i,j)))*corrsurf(i,j) ! volume au-dessus de la flottaison 
     193            endif 
     194 
     195            if (h(i,j).gt.hmax) hmax=h(i,j)  
     196            if (s(i,j).gt.smax) smax=s(i,j)  
     197            bmean=bm(i,j)+bmean  
     198            accmean=acc(i,j)+accmean 
     199            tbmean=tbmean+t(i,j,nz) 
     200            tbdotmean=tbdotmean+tbdot(i,j) 
     201            vsmean=vsmean+sqrt(ux(i,j,1)**2+uy(i,j,1)**2) 
    101202!          vsdotmean=vsdotmean+vsdot(i,j) 
    102203!          uzsmean=uzsmean+uz(i,j,1) 
    103           uzsdotmean=uzsdotmean+uzsdot(i,j) 
    104           uzkmean=uzkmean+uzk(i,j) 
    105           hdotmean=hdotmean+abs(hdot(i,j))  
    106           bdotmean=bdotmean+abs(bdot(i,j))  
    107           bmeltmean=bmeltmean+bmelt(i,j) 
     204            uzsdotmean=uzsdotmean+uzsdot(i,j) 
     205            uzkmean=uzkmean+uzk(i,j) 
     206            hdotmean=hdotmean+abs(hdot(i,j))  
     207            bdotmean=bdotmean+abs(bdot(i,j))  
     208            bmeltmean=bmeltmean+bmelt(i,j) 
     209          else ! point flottant 
     210            iareaf=iareaf+1.*corrsurf(i,j)                               ! surface flottante 
     211          endif 
     212          lim=lim+h(i,j)*corrsurf(i,j)                                   ! volume total de glace 
     213          tendacabf=tendacabf+bm_dtt(i,j)*corrsurf(i,j)/dtt              ! smb surface 
     214          tendlibmassbf=tendlibmassbf-bmelt_dtt(i,j)*corrsurf(i,j)/dtt   ! fonte basale      
    108215        endif 
    109         calvmean=calvmean+calv(i,j)   
    110         ablbordmean=ablbordmean+ablbord(i,j) 
     216        tendlicalvf=tendlicalvf+calv_dtt(i,j)*corrsurf(i,j)/dtt        ! calving 
     217        tendlibmassbf=tendlibmassbf-ablbord_dtt(i,j)*corrsurf(i,j)/dtt ! partie ablbord de la fonte basale 
     218        tendligroundf=tendligroundf+grline_dtt(i,j)*corrsurf(i,j)/dtt  ! flux a la grounding line 
    111219      end do 
    112       end do 
     220    end do 
    113221 
    114222 
     
    116224        hmean=vol/np  
    117225        vol=vol*dx*dy  
    118         volf=volf*dx*dy 
     226        volf=volf*dx*dy*ice_density 
    119227        bmean=bmean/np  
    120228        accmean=accmean/np  
     
    130238        uzsdotmean=uzsdotmean/np 
    131239        uzkmean=uzkmean/np 
    132         hdotmean=hdotmean/np  
    133       endif  
    134  
     240        hdotmean=hdotmean/np 
     241      endif 
     242      lim=lim*dx*dy*ice_density 
     243      iareag=iareag*dx*dy  
     244      iareaf=iareaf*dx*dy 
     245      tendacabf=tendacabf*dx*dy*ice_density/secyear 
     246      tendlibmassbf=tendlibmassbf*dx*dy*ice_density/secyear 
     247      tendlicalvf=tendlicalvf*dx*dy*ice_density/secyear 
     248      tendligroundf=tendligroundf*ice_density/secyear 
     249       
     250       
    135251      bdotmean=bdotmean/nx/ny   
    136252 
     
    154270!940   format('%%%% ',a,'   time=',f8.0,' %%%%') 
    155271 
     272 
     273if (ncshortout.eq.1) then  ! ecriture netcdf 
     274  ! Total ice mass 
     275  var_shortoutput(1)=lim 
     276  ! Mass above floatation 
     277  var_shortoutput(2)=volf 
     278  ! Grounded ice area 
     279  var_shortoutput(3)=iareag 
     280  ! Floating ice area 
     281  var_shortoutput(4)=iareaf 
     282  ! Total SMB flux  
     283  var_shortoutput(5)=tendacabf 
     284  ! Total Basal mass balance flux 
     285  var_shortoutput(6)=tendlibmassbf 
     286  ! Total calving flux  
     287  var_shortoutput(7)=tendlicalvf 
     288  ! Total grounding line flux 
     289  var_shortoutput(8)=tendligroundf 
     290 
     291  nbtimeout=nbtimeout+1 
     292   
     293  status=nf90_put_var(ncid, timeVarID, time, start=(/nbtimeout/)) 
     294  if (status /= nf90_noerr) call handle_err(status) 
     295 
     296  do k=1,nvar  ! boucle sur le nbr de variable a ecrire 
     297    status=nf90_put_var(ncid, varID(k), var_shortoutput(k),start=(/nbtimeout/)) 
     298    if (status /= nf90_noerr) call handle_err(status) 
     299  enddo 
     300  status=nf90_sync(ncid) 
     301  if (status /= nf90_noerr) call handle_err(status) 
     302endif 
     303 
     304 
    156305end subroutine shortoutput 
     306 
     307subroutine handle_err(status) 
     308  integer, intent(in) :: status 
     309  if (status /= nf90_noerr) then 
     310     print*,trim(nf90_strerror(status)) 
     311     stop "stopped" 
     312  end if 
     313end subroutine handle_err 
     314 
    157315end module  output_antarcti_mod 
Note: See TracChangeset for help on using the changeset viewer.