diff --git a/src/MNH/budget.f90 b/src/MNH/budget.f90
index 77c35cd6122527af0095d96a7f0190cf6fdfe54d..334f1ce3c8947e725ecf25f29c1a195422608795 100644
--- a/src/MNH/budget.f90
+++ b/src/MNH/budget.f90
@@ -298,6 +298,8 @@ REAL     :: ZTIME2  ! CPU time counter
 !
 !-------------------------------------------------------------------------------
 !
+call Print_msg( NVERB_DEBUG, 'BUD', 'Budget', 'called for '//trim( hbuvar ) )
+
 !* Reproductivity checks
 !  Warning: requires an adaptation of the makefile in order to run two runs in
 !  parallel for comparison
@@ -660,7 +662,7 @@ CONTAINS
           NBUCTR_ACTV(KBUDN) = NBUCTR_ACTV(KBUDN)             &
                              + NBUINC(KBUDN,NBUCTR_ACTV(KBUDN))
           RETURN
-      END SELECT          
+      END SELECT
   END SELECT
 !
   END SUBROUTINE BUDGET_CASE
diff --git a/src/MNH/ini_budget.f90 b/src/MNH/ini_budget.f90
index 5f88ea1328235a0b055bbdf6339bb71e57ba70db..d8382a7ba6533fbb1718bc161123210633b000fc 100644
--- a/src/MNH/ini_budget.f90
+++ b/src/MNH/ini_budget.f90
@@ -3443,6 +3443,8 @@ subroutine Budget_source_add( tpbudget, tpsource, ocond, kgroupin, odonotinit, o
 
   integer :: isourcenumber
 
+  call Print_msg( NVERB_DEBUG, 'BUD', 'Budget_source_add', 'called for '//trim( tpbudget%cname )//': '//trim( tpsource%cmnhname ) )
+
   isourcenumber = tpbudget%nsources + 1
   if ( isourcenumber > tpbudget%nsourcesmax ) then
     call Print_msg( NVERB_FATAL, 'BUD', 'Budget_source_add', 'insufficient number of source terms' )
@@ -3500,6 +3502,8 @@ subroutine Ini_budget_groups( tpbudgets, kbudim1, kbudim2, kbudim3 )
   real                               :: zval
   real                               :: zvalmax, zvalmin
 
+  call Print_msg( NVERB_DEBUG, 'BUD', 'Ini_budget_groups', 'called' )
+
   BUDGETS: do ji = 1, size( tpbudgets )
     ENABLED: if ( tpbudgets(ji)%lenabled ) then
       isources = size( tpbudgets(ji)%tsources )
diff --git a/src/MNH/write_budget.f90 b/src/MNH/write_budget.f90
index 2fc4e91faf017765c46a1b7eb1d0053b32540cc7..6c9b59cc9eec1e76da0310deb39f8c0f0541b82c 100644
--- a/src/MNH/write_budget.f90
+++ b/src/MNH/write_budget.f90
@@ -151,6 +151,8 @@ subroutine Write_budget( tpdiafile, tpdtcur, ptstep, ksv )
   !
   !-------------------------------------------------------------------------------
   !
+  call Print_msg( NVERB_DEBUG, 'BUD', 'Write_budget', 'called' )
+
   gnocompress = .true.
   !
   !* Write TSTEP and BULEN
@@ -399,6 +401,8 @@ subroutine Store_one_budget_rho_old( tpdiafile, tpdates, pburhodj, kp, knocompre
   character(len=100), dimension(:), allocatable  :: yworkunit     ! comment
   integer,            dimension(:), allocatable  :: iworkgrid     ! grid label
 
+  call Print_msg( NVERB_DEBUG, 'BUD', 'Store_one_budget_rho_old', 'called' )
+
   if ( allocated( prhodjn ) ) deallocate( prhodjn )
 
   ! pburhodj storage
@@ -507,6 +511,8 @@ subroutine Store_one_budget_rho( tpdiafile, tpdates, tpbudget, kp, knocompress,
   character(len=100), dimension(:), allocatable  :: yworkunit     ! comment
   integer,            dimension(:), allocatable  :: iworkgrid     ! grid label
 
+  call Print_msg( NVERB_DEBUG, 'BUD', 'Store_one_budget_rho', 'called for '//trim( tpbudget%trhodj%cmnhname ) )
+
   if ( allocated( prhodjn ) ) deallocate( prhodjn )
 
   ! pburhodj storage
@@ -608,6 +614,7 @@ subroutine Store_one_budget_old( tpdiafile, tpdates, pbudarray, prhodjn, kp, kno
   real,               dimension(:),           allocatable :: zconvert   ! unit conversion coefficient
   real,               dimension(:,:,:,:,:,:), allocatable :: zworkt
 
+  call Print_msg( NVERB_DEBUG, 'BUD', 'Store_one_budget_old', 'called' )
 
   if( .not. allocated( prhodjn ) ) then
     call Print_msg( NVERB_ERROR, 'BUD', 'Store_one_budget_old', 'prhodjn not allocated' )
@@ -795,6 +802,7 @@ subroutine Store_one_budget( tpdiafile, tpdates, tpbudget, prhodjn, kp, knocompr
   real,               dimension(:),           allocatable :: zconvert   ! unit conversion coefficient
   real,               dimension(:,:,:,:,:,:), allocatable :: zworkt
 
+  call Print_msg( NVERB_DEBUG, 'BUD', 'Store_one_budget', 'called for '//trim( tpbudget%cname ) )
 
   if( .not. allocated( prhodjn ) ) then
     call Print_msg( NVERB_ERROR, 'BUD', 'Store_one_budget', 'prhodjn not allocated' )
diff --git a/src/MNH/write_diachro.f90 b/src/MNH/write_diachro.f90
index d6d8e310b4903787d2259cffa0274e27417e8834..6cb6ff405fde134a8e56a79718515b6da76f667c 100644
--- a/src/MNH/write_diachro.f90
+++ b/src/MNH/write_diachro.f90
@@ -97,6 +97,7 @@ use mode_datetime,       only: Datetime_distance
 USE MODE_IO_FIELD_WRITE, only: IO_Field_write, IO_Field_write_box
 USE MODE_ll
 use mode_menu_diachro,   only: MENU_DIACHRO
+use mode_msg
 !
 IMPLICIT NONE
 !
@@ -139,6 +140,8 @@ real, dimension(:,:), allocatable :: zdatime
 TYPE(TFIELDDATA)  :: TZFIELD
 !------------------------------------------------------------------------------
 
+call Print_msg( NVERB_DEBUG, 'BUD', 'Write_diachro', 'called' )
+
 if ( present( oicp ) ) then
   gicp = oicp
 else