New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 3340 for branches/2012/dev_r3337_NOCS10_ICB/NEMOGCM/NEMO/OPA_SRC/DIA/diawri.F90 – NEMO

Ignore:
Timestamp:
2012-04-02T13:05:35+02:00 (12 years ago)
Author:
sga
Message:

NEMO branch dev_r3337_NOCS10_ICB: add changes to ocean code to allow interface to iceberg code

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2012/dev_r3337_NOCS10_ICB/NEMOGCM/NEMO/OPA_SRC/DIA/diawri.F90

    r3294 r3340  
    3232   USE sbc_oce         ! Surface boundary condition: ocean fields 
    3333   USE sbc_ice         ! Surface boundary condition: ice fields 
     34   USE icb_oce         ! Icebergs 
     35   USE icbdia          ! Iceberg budgets 
    3436   USE sbcssr          ! restoring term toward SST/SSS climatology 
    3537   USE phycst          ! physical constants 
     
    5961 
    6062   INTEGER ::   nid_T, nz_T, nh_T, ndim_T, ndim_hT   ! grid_T file 
     63   INTEGER ::          nb_T              , ndim_bT   ! grid_T file 
    6164   INTEGER ::   nid_U, nz_U, nh_U, ndim_U, ndim_hU   ! grid_U file 
    6265   INTEGER ::   nid_V, nz_V, nh_V, ndim_V, ndim_hV   ! grid_V file 
     
    6568   INTEGER, SAVE, ALLOCATABLE, DIMENSION(:) :: ndex_hT, ndex_hU, ndex_hV 
    6669   INTEGER, SAVE, ALLOCATABLE, DIMENSION(:) :: ndex_T, ndex_U, ndex_V 
     70   INTEGER, SAVE, ALLOCATABLE, DIMENSION(:) :: ndex_bT 
    6771 
    6872   !! * Substitutions 
     
    234238      INTEGER  ::   ierr                                     ! error code return from allocation 
    235239      INTEGER  ::   iimi, iima, ipk, it, itmod, ijmi, ijma   ! local integers 
     240      INTEGER  ::   jn, ierror                               ! local integers 
    236241      REAL(wp) ::   zsto, zout, zmax, zjulian, zdt           ! local scalars 
    237242      !! 
     
    320325         CALL wheneq( jpi*jpj*ipk, tmask, 1, 1., ndex_T , ndim_T  )      ! volume 
    321326         CALL wheneq( jpi*jpj    , tmask, 1, 1., ndex_hT, ndim_hT )      ! surface 
     327         ! 
     328         IF( ln_icebergs ) THEN 
     329            ! 
     330            !! allocation cant go in dia_wri_alloc because ln_icebergs is only set after  
     331            !! that routine is called from nemogcm, so do it here immediately before its needed 
     332            ALLOCATE( ndex_bT(jpi*jpj*nclasses), STAT=ierror ) 
     333            IF( lk_mpp )   CALL mpp_sum( ierror ) 
     334            IF( ierror /= 0 ) THEN 
     335               CALL ctl_stop('dia_wri: failed to allocate iceberg diagnostic array') 
     336               RETURN 
     337            ENDIF 
     338            ! 
     339            !! iceberg vertical coordinate is class number 
     340            CALL histvert( nid_T, "class", "Iceberg class",      &  ! Vertical grid: class 
     341               &           "number", nclasses, class_num, nb_T ) 
     342            ! 
     343            !! each class just needs the surface index pattern 
     344            ndim_bT = 3 
     345            DO jn = 1,nclasses 
     346               ndex_bT((jn-1)*jpi*jpj+1:jn*jpi*jpj) = ndex_hT(1:jpi*jpj) 
     347            ENDDO 
     348            ! 
     349         ENDIF 
    322350 
    323351         ! Define the U grid FILE ( nid_U ) 
     
    401429         CALL histdef( nid_T, "sowindsp", "wind speed at 10m"                  , "m/s"    ,   &  ! wndm 
    402430            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     431! 
     432         IF( ln_icebergs ) THEN 
     433            CALL histdef( nid_T, "calving"             , "calving mass input"                       , "kg/s"   , & 
     434               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     435            CALL histdef( nid_T, "calving_heat"        , "calving heat flux"                        , "XXXX"   , & 
     436               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     437            CALL histdef( nid_T, "berg_floating_melt"  , "Melt rate of icebergs + bits"             , "kg/m2/s", & 
     438               &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     439            CALL histdef( nid_T, "berg_stored_ice"     , "Accumulated ice mass by class"            , "kg"     , & 
     440               &          jpi, jpj, nh_T, nclasses  , 1, nclasses  , nb_T , 32, clop, zsto, zout ) 
     441            IF( ln_bergdia ) THEN 
     442               CALL histdef( nid_T, "berg_melt"           , "Melt rate of icebergs"                    , "kg/m2/s", & 
     443                  &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     444               CALL histdef( nid_T, "berg_melt_buoy"      , "Buoyancy component of iceberg melt rate"  , "kg/m2/s", & 
     445                  &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     446               CALL histdef( nid_T, "berg_melt_eros"      , "Erosion component of iceberg melt rate"   , "kg/m2/s", & 
     447                  &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     448               CALL histdef( nid_T, "berg_melt_conv"      , "Convective component of iceberg melt rate", "kg/m2/s", & 
     449                  &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     450               CALL histdef( nid_T, "berg_virtual_area"   , "Virtual coverage by icebergs"             , "m2"     , & 
     451                  &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     452               CALL histdef( nid_T, "bits_src"           , "Mass source of bergy bits"                , "kg/m2/s", & 
     453                  &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     454               CALL histdef( nid_T, "bits_melt"          , "Melt rate of bergy bits"                  , "kg/m2/s", & 
     455                  &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     456               CALL histdef( nid_T, "bits_mass"          , "Bergy bit density field"                  , "kg/m2"  , & 
     457                  &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     458               CALL histdef( nid_T, "berg_mass"           , "Iceberg density field"                    , "kg/m2"  , & 
     459                  &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     460               CALL histdef( nid_T, "berg_real_calving"   , "Calving into iceberg class"               , "kg/s"   , & 
     461                  &          jpi, jpj, nh_T, nclasses  , 1, nclasses  , nb_T , 32, clop, zsto, zout ) 
     462            ENDIF 
     463         ENDIF 
     464 
    403465#if ! defined key_coupled  
    404466         CALL histdef( nid_T, "sohefldp", "Surface Heat Flux: Damping"         , "W/m2"   ,   &  ! qrp 
     
    555617      CALL histwrite( nid_T, "soicecov", it, fr_i          , ndim_hT, ndex_hT )   ! ice fraction    
    556618      CALL histwrite( nid_T, "sowindsp", it, wndm          , ndim_hT, ndex_hT )   ! wind speed    
     619! 
     620      IF( ln_icebergs ) THEN 
     621         ! 
     622         CALL histwrite( nid_T, "calving"             , it, berg_grid%calving      , ndim_hT, ndex_hT )   
     623         CALL histwrite( nid_T, "calving_heat"        , it, berg_grid%calving_hflx , ndim_hT, ndex_hT )          
     624         CALL histwrite( nid_T, "berg_floating_melt"  , it, berg_grid%floating_melt, ndim_hT, ndex_hT )   
     625         ! 
     626         CALL histwrite( nid_T, "berg_stored_ice"     , it, berg_grid%stored_ice   , ndim_bT, ndex_bT ) 
     627         ! 
     628         IF( ln_bergdia ) THEN 
     629            CALL histwrite( nid_T, "berg_melt"           , it, berg_melt        , ndim_hT, ndex_hT   )   
     630            CALL histwrite( nid_T, "berg_melt_buoy"      , it, melt_buoy        , ndim_hT, ndex_hT   )   
     631            CALL histwrite( nid_T, "berg_melt_eros"      , it, melt_eros        , ndim_hT, ndex_hT   )   
     632            CALL histwrite( nid_T, "berg_melt_conv"      , it, melt_conv        , ndim_hT, ndex_hT   )   
     633            CALL histwrite( nid_T, "berg_virtual_area"   , it, virtual_area     , ndim_hT, ndex_hT   )   
     634            CALL histwrite( nid_T, "bits_src"           , it, bits_src        , ndim_hT, ndex_hT   )   
     635            CALL histwrite( nid_T, "bits_melt"          , it, bits_melt       , ndim_hT, ndex_hT   )   
     636            CALL histwrite( nid_T, "bits_mass"          , it, bits_mass       , ndim_hT, ndex_hT   )   
     637            CALL histwrite( nid_T, "berg_mass"           , it, berg_mass        , ndim_hT, ndex_hT   )   
     638            ! 
     639            CALL histwrite( nid_T, "berg_real_calving"   , it, real_calving     , ndim_bT, ndex_bT   ) 
     640         ENDIF 
     641      ENDIF 
     642 
    557643#if ! defined key_coupled 
    558644      CALL histwrite( nid_T, "sohefldp", it, qrp           , ndim_hT, ndex_hT )   ! heat flux damping 
Note: See TracChangeset for help on using the changeset viewer.