Changeset 136 for trunk/SOURCES


Ignore:
Timestamp:
10/13/17 18:21:01 (7 years ago)
Author:
dumas
Message:

Flux output and short netcdf output for initMIP

Location:
trunk/SOURCES
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • trunk/SOURCES/3D-physique-gen_mod.f90

    r124 r136  
    226226  integer,dimension(nx,ny) :: FRONTFACEY!< type de front sur les faces y 
    227227  integer,dimension(nx,ny) :: gr_line_schoof ! points ou on impose le flux de schoof (pour sorties) 
     228  integer,dimension(nx,ny) :: gr_line   !< points grounding line pour les sorties 
    228229  integer,dimension(nx,ny) :: ICE       !< presence de glace au point considere, 
    229230  !< seuil 0 si pose, 1 si flottant 
  • trunk/SOURCES/Ant40_files/output_anta40_mod-0.4.f90

    r113 r136  
    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 
     51real, 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    print*,trim(namevar(k)) 
     98    read(568,'(a100)') standard_name(k) 
     99    print*,trim(standard_name(k)) 
     100    read(568,'(a100)') long_name(k) 
     101    print*,trim(long_name(k)) 
     102    read(568,'(a100)') units(k) 
     103    print*,trim(units(k)) 
     104    read(568,*) 
     105  enddo 
     106  close(568) 
     107  print*,'apres lecture fichier descriptions variables' 
     108! Fichier Netcdf initMIP 
     109! creation du fichier Netcdf : 
     110  status=nf90_create(path = 'short'//runname//'.nc', cmode = nf90_clobber, ncid = ncid) 
     111  if (status /= nf90_noerr) call handle_err(status) 
     112  print*,'apres nf90_create' 
     113 
     114! definition des dimension : 
     115  status=nf90_def_dim(ncid, name="time", len=NF90_UNLIMITED, dimid=timeDimID) 
     116  if (status /= nf90_noerr) call handle_err(status) 
     117  print*,'apres 2' 
     118  status=nf90_def_var(ncid, name="time", xtype=nf90_float, dimids=(/ timeDimID/), varid=timeVarID)  
     119  if (status /= nf90_noerr) call handle_err(status) 
     120  status=nf90_put_att(ncid, timeVarID, "standard_name", "time") 
     121  if (status /= nf90_noerr) call handle_err(status) 
     122  print*,'apres 3' 
     123  status=nf90_put_att(ncid, timeVarID,"units", "years since 2007-01-01 00:00:00") 
     124  if (status /= nf90_noerr) call handle_err(status) 
     125  print*,'apres 4' 
     126 
     127! definition des variables de sortie : 
     128  do k=1,nvar  ! boucle sur le nbr de variable a definir 
     129    status=nf90_def_var(ncid, name=trim(namevar(k)), xtype=nf90_float, dimids= & 
     130          (/ timeDimID /), varid=varID(k)) 
     131  print*,'apres 5' 
     132    if (status /= nf90_noerr) call handle_err(status) 
     133    status=nf90_put_att(ncid, varID(k), "standard_name", trim(standard_name(k))) 
     134    print*,'apres 6',trim(standard_name(k)) 
     135    if (status /= nf90_noerr) call handle_err(status) 
     136    status=nf90_put_att(ncid, varID(k), "long_name", trim(long_name(k))) 
     137    print*,'apres 7',trim(long_name(k)) 
     138    if (status /= nf90_noerr) call handle_err(status) 
     139    status=nf90_put_att(ncid, varID(k), "units", trim(units(k))) 
     140    print*,'apres 8', trim(units(k)) 
     141    if (status /= nf90_noerr) call handle_err(status) 
     142  enddo 
     143  print*,'apres boucle' 
     144 
     145! fin de la definition du fchier : 
     146  status=nf90_enddef(ncid) 
     147  if (status /= nf90_noerr) call handle_err(status) 
     148  nbtimeout = 0 ! initialisation compteur sorties axe time 
     149else ! pas de sortie netcdf et sans correction de surface 
     150  corrsurf(:,:)=1. 
     151endif 
     152 
    46153end subroutine init_outshort 
    47154 
     
    54161!------------------ 
    55162real ::  smax 
     163 
    56164      vol=0.  
    57165      np=0 
     166      nflot=0 
    58167      hmax=0.  
    59168      smax=0. 
     
    74183      bdotmean=0. 
    75184      volf=0. 
    76   
     185      lim=0. 
     186      tendacabf=0. 
     187      iareag=0. 
     188      iareaf=0. 
     189      tendlicalvf=0. 
     190      tendligroundf=0. 
     191      tendlibmassbf=0. 
    77192! 2_preparing outputs 
    78193!--------------------       
    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) 
     194    do j=1,ny 
     195      do i=1,nx 
     196        if (ice(i,j).eq.1) then ! point englace 
     197          if (.not.flot(i,j)) then ! point pose  
     198            np=np+1 
     199            vol=vol+h(i,j) 
     200            iareag=iareag+1.*corrsurf(i,j)                            ! surface englacee posee 
     201 
     202!         calcul de la hauteur au dessus de la flottaison 
     203            if (sealevel-B(i,j).le.0.) then    ! socle au dessus du niveau des mers 
     204              volf=volf+h(i,j)*corrsurf(i,j)                          ! volume au-dessus de la flottaison 
     205            else 
     206              volf=volf+(h(i,j)-row/ro*(sealevel-b(i,j)))*corrsurf(i,j) ! volume au-dessus de la flottaison 
     207            endif 
     208 
     209            if (h(i,j).gt.hmax) hmax=h(i,j)  
     210            if (s(i,j).gt.smax) smax=s(i,j)  
     211            bmean=bm(i,j)+bmean  
     212            accmean=acc(i,j)+accmean 
     213            tbmean=tbmean+t(i,j,nz) 
     214            tbdotmean=tbdotmean+tbdot(i,j) 
     215            vsmean=vsmean+sqrt(ux(i,j,1)**2+uy(i,j,1)**2) 
    101216!          vsdotmean=vsdotmean+vsdot(i,j) 
    102217!          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) 
     218            uzsdotmean=uzsdotmean+uzsdot(i,j) 
     219            uzkmean=uzkmean+uzk(i,j) 
     220            hdotmean=hdotmean+abs(hdot(i,j))  
     221            bdotmean=bdotmean+abs(bdot(i,j))  
     222            bmeltmean=bmeltmean+bmelt(i,j) 
     223          else ! point flottant 
     224            iareaf=iareaf+1.*corrsurf(i,j)                               ! surface flottante 
     225          endif 
     226          lim=lim+h(i,j)*corrsurf(i,j)                                   ! volume total de glace 
     227          tendacabf=tendacabf+bm_dtt(i,j)*corrsurf(i,j)/dtt              ! smb surface 
     228          tendlibmassbf=tendlibmassbf-bmelt_dtt(i,j)*corrsurf(i,j)/dtt   ! fonte basale      
    108229        endif 
    109         calvmean=calvmean+calv(i,j)   
    110         ablbordmean=ablbordmean+ablbord(i,j) 
     230        tendlicalvf=tendlicalvf+calv_dtt(i,j)*corrsurf(i,j)/dtt        ! calving 
     231        tendlibmassbf=tendlibmassbf-ablbord_dtt(i,j)*corrsurf(i,j)/dtt ! partie ablbord de la fonte basale 
     232        tendligroundf=tendligroundf+grline_dtt(i,j)*corrsurf(i,j)/dtt  ! flux a la grounding line 
    111233      end do 
    112       end do 
     234    end do 
    113235 
    114236 
     
    116238        hmean=vol/np  
    117239        vol=vol*dx*dy  
    118         volf=volf*dx*dy 
     240        volf=volf*dx*dy*ice_density 
    119241        bmean=bmean/np  
    120242        accmean=accmean/np  
     
    130252        uzsdotmean=uzsdotmean/np 
    131253        uzkmean=uzkmean/np 
    132         hdotmean=hdotmean/np  
    133       endif  
    134  
     254        hdotmean=hdotmean/np 
     255      endif 
     256      lim=lim*dx*dy*ice_density 
     257      iareag=iareag*dx*dy  
     258      iareaf=iareaf*dx*dy 
     259      tendacabf=tendacabf*dx*dy*ice_density/86400. 
     260      tendlibmassbf=tendlibmassbf*ice_density/86400. 
     261      tendlicalvf=tendlicalvf*ice_density/86400. 
     262      tendligroundf=tendligroundf*ice_density/86400. 
     263       
     264       
    135265      bdotmean=bdotmean/nx/ny   
    136266 
     
    154284!940   format('%%%% ',a,'   time=',f8.0,' %%%%') 
    155285 
     286print*, 'dans shortoutput avant netcdf ncshortout', ncshortout 
     287 
     288if (ncshortout.eq.1) then  ! ecriture netcdf 
     289  ! Total ice mass 
     290  var_shortoutput(1)=lim 
     291  ! Mass above floatation 
     292  var_shortoutput(2)=volf 
     293  ! Grounded ice area 
     294  var_shortoutput(3)=iareag 
     295  ! Floating ice area 
     296  var_shortoutput(4)=iareaf 
     297  ! Total SMB flux  
     298  var_shortoutput(5)=tendacabf 
     299  ! Total Basal mass balance flux 
     300  var_shortoutput(6)=tendlibmassbf 
     301  ! Total calving flux  
     302  var_shortoutput(7)=tendlicalvf 
     303  ! Total grounding line flux 
     304  var_shortoutput(8)=tendligroundf 
     305 
     306  nbtimeout=nbtimeout+1 
     307  print*,'ecriture shortnc', nbtimeout 
     308  status=nf90_put_var(ncid, timeVarID, time, start=(/nbtimeout/)) 
     309  if (status /= nf90_noerr) call handle_err(status) 
     310 
     311  do k=1,nvar  ! boucle sur le nbr de variable a ecrire 
     312    status=nf90_put_var(ncid, varID(k), var_shortoutput(k),start=(/nbtimeout/)) 
     313    if (status /= nf90_noerr) call handle_err(status) 
     314  enddo 
     315  status=nf90_sync(ncid) 
     316  if (status /= nf90_noerr) call handle_err(status) 
     317endif 
     318 
     319 
    156320end subroutine shortoutput 
     321 
     322subroutine handle_err(status) 
     323  integer, intent(in) :: status 
     324  if (status /= nf90_noerr) then 
     325     print*,trim(nf90_strerror(status)) 
     326     stop "stopped" 
     327  end if 
     328end subroutine handle_err 
     329 
    157330end module  output_antarcti_mod 
  • trunk/SOURCES/Makefile.grisli.inc

    r135 r136  
    7777        calving_frange.o no_calving.o no_lakes.o \ 
    7878        out_profile_mod.o printtable_mod.o mix-SIA-L1_mod.o \ 
    79         furst_schoof_mod.o \ 
     79        furst_schoof_mod.o bilan_flux_output_mod.o \ 
    8080        relaxation_water_diffusion.o \ 
    8181        prescribe-H-i2s_mod.o  \ 
     
    9797        calving_frange.o no_calving.o no_lakes.o \ 
    9898        out_profile_mod.o printtable_mod.o mix-SIA-L1_mod.o \ 
    99         furst_schoof_mod.o \ 
     99        furst_schoof_mod.o bilan_flux_output_mod.o \ 
    100100        relaxation_water_diffusion.o \ 
    101101        prescribe-H-i2s_mod.o   \ 
  • trunk/SOURCES/ablation_bord.f90

    r113 r136  
    5555ablbord_dtt(:,:) = ablbord_dtt(:,:) + ablbord(:,:) 
    5656 
    57 ablbord(:,:)=0. 
     57!cdc deplace dans bilan_flux_output_mod ablbord(:,:)=0. 
    5858 
    5959end subroutine ablation_bord 
  • trunk/SOURCES/bilan_eau_mod.f90

    r112 r136  
    3131real,dimension(nx,ny) :: Bmelt_dtt    !< basal melting on ice points accumulated during dtt 
    3232real,dimension(nx,ny) :: calv_dtt     !< calving sur dtt (pour calcul bilan d'eau) 
     33real,dimension(nx,ny) :: archimtab    ! point pose si > 0 
     34real,dimension(nx,ny) :: grline_dtt   ! grounding line flux during dtt 
    3335 
    3436real :: sum_H_old 
    3537real :: diff_H 
     38real :: alpha_flot                      ! ro/row  
    3639 
    3740real,dimension(nx,ny) :: bm_dt,bmelt_dt 
     
    4750        bm_dt(:,:)=0. 
    4851        bmelt_dt(:,:)=0. 
     52  alpha_flot=ro/row 
    4953end subroutine init_bilan_eau 
    5054 
     
    8791endwhere 
    8892 
     93archimtab(:,:) = Bsoc(:,:)+H(:,:)*alpha_flot - sealevel 
     94gr_line(:,:)=0 
     95do j=1,ny 
     96  do i=1,nx 
     97    if ((H(i,j).gt.0.).and.(archimtab(i,j).GE.0.).and.(Bsoc(i,j).LE.sealevel)) then ! grounded with ice 
     98      if (archimtab(i-1,j).LT.0..and.Uxbar(i,j).LT.0..and..not.flot_marais(i-1,j)) gr_line(i,j)=1 
     99      if (archimtab(i+1,j).LT.0..and.Uxbar(i+1,j).GT.0..and..not.flot_marais(i+1,j)) gr_line(i,j)=1 
     100      if (archimtab(i,j-1).LT.0..and.Uybar(i,j).LT.0..and..not.flot_marais(i,j-1)) gr_line(i,j)=1 
     101      if (archimtab(i,j+1).LT.0..and.Uybar(i,j+1).GT.0..and..not.flot_marais(i,j+1)) gr_line(i,j)=1 
     102    endif 
     103  enddo 
     104enddo 
     105 
     106where (gr_line(:,:).eq.1) 
     107!~   grline_dtt(:,:)= (((uxbar(:,:)+eoshift(uxbar(:,:),shift=1,boundary=0.,dim=1))**2+ & 
     108!~                     (uybar(:,:)+eoshift(uybar(:,:),shift=1,boundary=0.,dim=2))**2)**0.5)*0.5 & 
     109!~                     *H(:,:) + grline_dtt(:,:) 
     110  grline_dtt(:,:)= (abs(uxbar(:,:)+eoshift(uxbar(:,:),shift=1,boundary=0.,dim=1))/2.*dy + & 
     111                    abs(uybar(:,:)+eoshift(uybar(:,:),shift=1,boundary=0.,dim=2))/2.*dx)  & 
     112                    *H(:,:) + grline_dtt(:,:)              
     113endwhere 
     114 
     115 
    89116if (isynchro.eq.1) then 
    90117! on raisonne en bilan annuel pour simplifier : 
  • trunk/SOURCES/initial-0.3.f90

    r93 r136  
    3030  use sorties_ncdf_grisli 
    3131  use util_recovery 
     32  use bilan_flux_mod 
    3233 
    3334  !------------------------------------------------------------------------------------- 
     
    135136  call init_calving 
    136137 
     138  call init_bilan_flux 
    137139! 
    138140!------------------------------------------------------------------------------------- 
  • trunk/SOURCES/steps_time_loop.f90

    r129 r136  
    2222  use icetempmod 
    2323  use diagno_mod 
    24   use bilan_eau_mod  
     24  use bilan_eau_mod 
     25  use bilan_flux_mod 
    2526  !  use track_debug  
    2627 
     
    6465 
    6566     call bilan_eau 
     67     call bilan_flux_output 
    6668     if (isynchro.eq.1) then 
    6769         call shortoutput 
     
    7274         ablbord_dtt(:,:)=0. 
    7375         diff_H_2D(:,:)=0. 
     76         grline_dtt(:,:)=0. 
    7477      endif 
    7578      
Note: See TracChangeset for help on using the changeset viewer.