diff --git a/src/MNH/drag_bld.f90 b/src/MNH/drag_bld.f90
index 02de3d18214954b08f6539e041d493dd5dcaeb90..fbb25dc13bdcb4837a23d39130417db344f58a48 100644
--- a/src/MNH/drag_bld.f90
+++ b/src/MNH/drag_bld.f90
@@ -1,4 +1,4 @@
-!MNH_LIC Copyright 2019-2020 CNRS, Meteo-France and Universite Paul Sabatier
+!MNH_LIC Copyright 2019-2021 CNRS, Meteo-France and Universite Paul Sabatier
 !MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
 !MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
 !MNH_LIC for details. version 1.
@@ -51,19 +51,26 @@ SUBROUTINE DRAG_BLD(PTSTEP, PUT, PVT, PTKET, PRHODJ, PZZ, PRUS, PRVS, PRTKES )
   !!    MODIFICATIONS
   !!    -------------
   !!      Original    09/2019
+  !  P. Wautelet 04/03/2021: budgets: add DRAGB source term
   !!---------------------------------------------------------------
   !
   !*       0.    DECLARATIONS
   !              ------------
   !
+  use modd_budget,     only: lbudget_u, lbudget_v, lbudget_tke, &
+                             NBUDGET_U, NBUDGET_V, NBUDGET_TKE, &
+                             tbudgets
   USE MODD_CONF
   USE MODD_CST
   USE MODD_DRAGBLDG_n
   USE MODD_DYN
   USE MODD_DYN_n
   USE MODD_GROUND_PAR
-  USE MODD_PGDFIELDS
   USE MODD_NSV
+  USE MODD_PGDFIELDS
+
+  use mode_budget,     only: Budget_store_init, Budget_store_end
+
   USE MODI_MNHGET_SURF_PARAM_n
   USE MODI_SHUMAN
   !
@@ -103,6 +110,10 @@ SUBROUTINE DRAG_BLD(PTSTEP, PUT, PVT, PTKET, PRHODJ, PZZ, PRUS, PRVS, PRTKES )
   !
   !*       0.3     Initialization
   !
+  if ( lbudget_u   ) call Budget_store_init( tbudgets(NBUDGET_U  ), 'DRAGB', prus  (:, :, :) )
+  if ( lbudget_v   ) call Budget_store_init( tbudgets(NBUDGET_V  ), 'DRAGB', prvs  (:, :, :) )
+  if ( lbudget_tke ) call Budget_store_init( tbudgets(NBUDGET_TKE), 'DRAGB', prtkes(:, :, :) )
+
   IIU = SIZE(PUT,1)
   IJU = SIZE(PUT,2)
   IKU = SIZE(PUT,3)
@@ -232,5 +243,9 @@ SUBROUTINE DRAG_BLD(PTSTEP, PUT, PVT, PTKET, PRHODJ, PZZ, PRUS, PRVS, PRTKES )
      PTSTEP * ZCDRAG(:,:,:) * ZDENSITY(:,:,:) * (SQRT( ZUT_SCAL(:,:,:)**2 + ZVT_SCAL(:,:,:)**2 ))**3
   !
   PRTKES(:,:,:) = PRTKES(:,:,:) + (ZTKES(:,:,:)-ZTKET(:,:,:))*PRHODJ(:,:,:)/PTSTEP
-  !
+
+  if ( lbudget_u   ) call Budget_store_end( tbudgets(NBUDGET_U  ), 'DRAGB', prus  (:, :, :) )
+  if ( lbudget_v   ) call Budget_store_end( tbudgets(NBUDGET_V  ), 'DRAGB', prvs  (:, :, :) )
+  if ( lbudget_tke ) call Budget_store_end( tbudgets(NBUDGET_TKE), 'DRAGB', prtkes(:, :, :) )
+
 END SUBROUTINE DRAG_BLD
diff --git a/src/MNH/ini_budget.f90 b/src/MNH/ini_budget.f90
index d0be92f6b18304f6a5ecffe856bcbce179c4488f..bf86f65d3b8f89d3773b8bbb83551d07e104166b 100644
--- a/src/MNH/ini_budget.f90
+++ b/src/MNH/ini_budget.f90
@@ -206,6 +206,7 @@ end subroutine Budget_preallocate
 !  P. Wautelet 10/02/2021: budgets: add missing sources for NSV_C2R2BEG+3 budget
 !  P. Wautelet 11/02/2021: budgets: add missing term SCAV for NSV_LIMA_SCAVMASS budget
 !  P. Wautelet 02/03/2021: budgets: add terms for blowing snow
+!  P. Wautelet 04/03/2021: budgets: add terms for drag due to buildings
 !-------------------------------------------------------------------------------
 !
 !*       0.    DECLARATIONS
@@ -217,6 +218,7 @@ use modd_blowsnow_n,    only: lsnowsubl
 use modd_budget
 use modd_ch_aerosol,    only: lorilam
 use modd_conf,          only: l1d, lcartesian, lforcing, lthinshell, nmodel
+use modd_dragbldg_n,    only: ldragbldg
 use modd_dust,          only: ldust
 use modd_dyn,           only: lcorio, xseglen
 use modd_dyn_n,         only: xtstep
@@ -533,7 +535,7 @@ if ( lbu_ru ) then
 
   !Allocate all basic source terms (used or not)
   !The size should be large enough (bigger than necessary is OK)
-  isourcesmax = 18
+  isourcesmax = 19
   tbudgets(NBUDGET_U)%nsourcesmax = isourcesmax
   allocate( tbudgets(NBUDGET_U)%tsources(isourcesmax) )
 
@@ -608,6 +610,11 @@ if ( lbu_ru ) then
   tzsource%clongname = 'drag force'
   call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, ndragu )
 
+  gcond = ldragbldg
+  tzsource%cmnhname  = 'DRAGB'
+  tzsource%clongname = 'drag force due to buildings'
+  call Budget_source_add( tbudgets(NBUDGET_U), tzsource, gcond, ndragbu )
+
   gcond = hturb == 'TKEL'
   tzsource%cmnhname  = 'VTURB'
   tzsource%clongname = 'vertical turbulent diffusion'
@@ -659,7 +666,7 @@ if ( lbu_rv ) then
 
   !Allocate all basic source terms (used or not)
   !The size should be large enough (bigger than necessary is OK)
-  isourcesmax = 18
+  isourcesmax = 19
   tbudgets(NBUDGET_V)%nsourcesmax = isourcesmax
   allocate( tbudgets(NBUDGET_V)%tsources(isourcesmax) )
 
@@ -734,6 +741,11 @@ if ( lbu_rv ) then
   tzsource%clongname = 'drag force'
   call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, ndragv )
 
+  gcond = ldragbldg
+  tzsource%cmnhname  = 'DRAGB'
+  tzsource%clongname = 'drag force due to buildings'
+  call Budget_source_add( tbudgets(NBUDGET_V), tzsource, gcond, ndragbv )
+
   gcond = hturb == 'TKEL'
   tzsource%cmnhname  = 'VTURB'
   tzsource%clongname = 'vertical turbulent diffusion'
@@ -1199,7 +1211,7 @@ if ( lbu_rtke ) then
 
   !Allocate all basic source terms (used or not)
   !The size should be large enough (bigger than necessary is OK)
-  isourcesmax = 13
+  isourcesmax = 14
   tbudgets(NBUDGET_TKE)%nsourcesmax = isourcesmax
   allocate( tbudgets(NBUDGET_TKE)%tsources(isourcesmax) )
 
@@ -1254,6 +1266,11 @@ if ( lbu_rtke ) then
   tzsource%clongname = 'drag force'
   call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource, gcond, ndragtke )
 
+  gcond = ldragbldg
+  tzsource%cmnhname  = 'DRAGB'
+  tzsource%clongname = 'drag force due to buildings'
+  call Budget_source_add( tbudgets(NBUDGET_TKE), tzsource, gcond, ndragbtke )
+
   gcond = hturb == 'TKEL'
   tzsource%cmnhname  = 'DP'
   tzsource%clongname = 'dynamic production'
diff --git a/src/MNH/modd_budget.f90 b/src/MNH/modd_budget.f90
index ba2aabb5dbfa20c08514e72fe39aeb3e9f5651b3..cd64563ae66f1f12cc5e794e2ea446242f2aa454 100644
--- a/src/MNH/modd_budget.f90
+++ b/src/MNH/modd_budget.f90
@@ -62,6 +62,7 @@
 !  P. Wautelet 03/02/2021: add new source if LIMA splitting: CORR2
 !  P. Wautelet 02/03/2021: add terms for blowing snow
 !  P. Wautelet 03/03/2021: add tbudiachrometadata type (useful to pass more information to Write_diachro)
+!  P. Wautelet 04/03/2021: add terms for drag due to buildings
 !-------------------------------------------------------------------------------
 !
 !*       0.   DECLARATIONS
@@ -249,6 +250,7 @@ INTEGER, SAVE :: NDRAGU  = 0 ! vegetation drag
 INTEGER, SAVE :: NMAFLU  = 0 ! mass flux
 INTEGER, SAVE :: NPRESU  = 0 ! pressure term
 INTEGER, SAVE :: NVISCU  = 0 ! viscosity
+INTEGER, SAVE :: NDRAGBU = 0 ! buildings drag
 !
 !      Allowed processes for the budget of RV (wind component along y)
 !                                                  
@@ -271,6 +273,7 @@ INTEGER, SAVE :: NDRAGV  = 0 ! vegetation drag
 INTEGER, SAVE :: NMAFLV  = 0 ! mass flux
 INTEGER, SAVE :: NPRESV  = 0 ! pressure term
 INTEGER, SAVE :: NVISCV  = 0 ! viscosity
+INTEGER, SAVE :: NDRAGBV = 0 ! buildings drag
 !
 !      Allowed processes for the budget of RW (wind vertical component)
 !                                                  
@@ -367,6 +370,7 @@ INTEGER, SAVE :: NTPTKE   = 0 ! thermal production of TKE
 INTEGER, SAVE :: NDRAGTKE = 0 ! vegetation drag
 INTEGER, SAVE :: NDISSTKE = 0 ! dissipation of TKE
 INTEGER, SAVE :: NTRTKE   = 0 ! turbulent transport of TKE
+INTEGER, SAVE :: NDRAGBTKE = 0 ! buildings drag
 !
 !
 !      Allowed processes for the budget of moist variable RRV (water vapor)
diff --git a/src/MNH/modn_budget.f90 b/src/MNH/modn_budget.f90
index 5a9b0fe6162fa91b87e73afd6af7c33aca24299b..0c698002d79314670ac41437a6d7cc2a5c839f4b 100644
--- a/src/MNH/modn_budget.f90
+++ b/src/MNH/modn_budget.f90
@@ -229,6 +229,7 @@
 !  P. Wautelet 09/03/2020: add missing budgets for electricity
 !  P. Wautelet 30/06/2020: add NNETURSV, NNEADVSV and NNECONSV variables
 !  P. Wautelet 02/03/2021: budgets: add terms for blowing snow
+!  P. Wautelet 04/03/2021: add terms for drag due to buildings
 !-------------------------------------------------------------------------------
 !
 !*       0.   DECLARATIONS
@@ -242,10 +243,10 @@ NAMELIST/NAM_BUDGET/CBUTYPE, NBUMOD, XBULEN, NBUKL, NBUKH, LBU_KCP, XBUWRI, &
                     NBUIL, NBUIH, NBUJL, NBUJH, LBU_ICP, LBU_JCP, NBUMASK 
 !
 NAMELIST/NAM_BU_RU/LBU_RU, NASSEU, NNESTU, NADVU, NFRCU, NNUDU, &
-                   NCURVU, NCORU, NDIFU, NRELU, NDRAGU, NHTURBU, NVTURBU, NMAFLU, NPRESU, NVISCU
+                   NCURVU, NCORU, NDIFU, NRELU, NDRAGU, NDRAGBU, NHTURBU, NVTURBU, NMAFLU, NPRESU, NVISCU
 !
 NAMELIST/NAM_BU_RV/LBU_RV, NASSEV, NNESTV, NADVV, NFRCV, NNUDV, &
-                   NCURVV, NCORV, NDIFV, NRELV, NDRAGV, NHTURBV, NVTURBV, NMAFLV, NPRESV, NVISCV
+                   NCURVV, NCORV, NDIFV, NRELV, NDRAGV, NDRAGBV, NHTURBV, NVTURBV, NMAFLV, NPRESV, NVISCV
 
 NAMELIST/NAM_BU_RW/LBU_RW, NASSEW, NNESTW, NADVW, NFRCW, NNUDW, &
                    NCURVW, NCORW, NGRAVW, NDIFW, NRELW, NHTURBW, NVTURBW, NPRESW, NVISCW
@@ -259,7 +260,7 @@ NAMELIST/NAM_BU_RTH/LBU_RTH, NASSETH, NNESTTH, NADVTH, NFRCTH, &
                    NHINDTH, NHINCTH, NHONHTH, NHONCTH, NHONRTH, NCEDSTH, NSEDITH, NVISCTH
 !
 NAMELIST/NAM_BU_RTKE/LBU_RTKE, NASSETKE, NADVTKE,    &
-                     NFRCTKE, NDIFTKE, NRELTKE, NDRAGTKE,                           &
+                     NFRCTKE, NDIFTKE, NRELTKE, NDRAGTKE, NDRAGBTKE, &
                      NDPTKE, NTPTKE, NDISSTKE, NTRTKE
 !
 NAMELIST/NAM_BU_RRV/LBU_RRV, NASSERV, NNESTRV, NADVRV, NFRCRV, &