From f81a2cf3718fb418dede6248a895e1e3af65bcfa Mon Sep 17 00:00:00 2001
From: Philippe WAUTELET <philippe.wautelet@aero.obs-mip.fr>
Date: Fri, 28 Jul 2023 12:10:50 +0200
Subject: [PATCH] Philippe 28/07/2023: minor: remove personal comments (some
 commited by error)

---
 LIBTOOLS/tools/lfi2cdf/src/mode_util.f90        | 2 --
 src/LIB/SURCOUCHE/src/mode_field.f90            | 8 --------
 src/LIB/SURCOUCHE/src/mode_io_field_write.f90   | 6 ------
 src/LIB/SURCOUCHE/src/mode_io_manage_struct.f90 | 4 ----
 src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90     | 2 --
 src/LIB/SURCOUCHE/src/mode_msg.f90              | 1 -
 src/MNH/ini_aircraft_balloon.f90                | 1 -
 src/MNH/modd_budget.f90                         | 1 -
 src/MNH/mode_les_diachro.f90                    | 1 -
 src/MNH/profilern.f90                           | 1 -
 src/MNH/read_grid_time_mesonh_case.f90          | 2 --
 src/MNH/write_les_rt_budgetn.f90                | 1 -
 src/MNH/write_les_sv_budgetn.f90                | 1 -
 src/MNH/write_lesn.f90                          | 2 --
 src/MNH/write_lfifm1_for_diag.f90               | 5 -----
 src/MNH/zoom_pgd.f90                            | 1 -
 src/MNH/zsmt_pgd.f90                            | 2 --
 src/PHYEX/micro/rain_ice_warm.f90               | 1 -
 src/PHYEX/turb/mode_turb_ver_sv_flux.f90        | 1 -
 19 files changed, 43 deletions(-)

diff --git a/LIBTOOLS/tools/lfi2cdf/src/mode_util.f90 b/LIBTOOLS/tools/lfi2cdf/src/mode_util.f90
index 80463b15e..904898810 100644
--- a/LIBTOOLS/tools/lfi2cdf/src/mode_util.f90
+++ b/LIBTOOLS/tools/lfi2cdf/src/mode_util.f90
@@ -570,7 +570,6 @@ END DO
         tpreclist(ji)%TFIELD%NTYPE    = tpreclist(idx_var)%TFIELD%NTYPE
         tpreclist(ji)%TFIELD%NDIMS    = tpreclist(idx_var)%TFIELD%NDIMS
 #if 0
-!PW: TODO?
         tpreclist(ji)%TFIELD%NFILLVALUE
         tpreclist(ji)%TFIELD%XFILLVALUE
         tpreclist(ji)%TFIELD%NVALIDMIN
@@ -1427,7 +1426,6 @@ END DO
         ISTATUS = NF90_GET_ATT(IFILE_ID, KVAR_ID, 'split_nblocks', iblocks)
         IF (istatus /= NF90_NOERR) CALL IO_Err_handle_nc4( istatus, 'IO_Metadata_get_nc4', 'NF90_GET_ATT', 'split_nblocks' )
 
-!PW: todo:check tfiles_ioz exist
         IFILE_ID = TPFILE%TFILES_IOZ(1)%TFILE%NNCID
 
         istatus = NF90_INQ_VARID(IFILE_ID,trim(TPREC%NAME)//'0001',ivar_id)
diff --git a/src/LIB/SURCOUCHE/src/mode_field.f90 b/src/LIB/SURCOUCHE/src/mode_field.f90
index 5ed1db232..c024a4390 100644
--- a/src/LIB/SURCOUCHE/src/mode_field.f90
+++ b/src/LIB/SURCOUCHE/src/mode_field.f90
@@ -789,8 +789,6 @@ call Add_field2list( TFIELDDATA( &
   CSTDNAME   = 'projection_x_coordinate', &
   CLONGNAME  = 'XHAT_ll',        &
   CUNITS     = 'm',              &
-!PW:BUG?: CDIR=XX => correct? variable is NOT distributed (same value on all processes) (see alse YHAT_ll...)
-!PW:BUG?: NGRID=2 => correct? variable is NOT distributed (same value on all processes)
 !PW:TODO?: create a new field to say if the variable is distributed? and how (X,Y,XY...)?
   CDIR       = 'XX',             &
   CCOMMENT   = 'Position x in the conformal or cartesian plane (all domain)', &
@@ -3162,7 +3160,6 @@ call Add_field2list( TFIELDDATA( &
   CMNHNAME   = 'RTHS_EDDY_FLUX', &
   CSTDNAME   = '',               &
   CLONGNAME  = 'RTHS_EDDY_FLUX', &
-!TODO PW: units?
   CUNITS     = '',               &
   CDIR       = 'XY',             &
   CCOMMENT   = '',               &
@@ -3187,7 +3184,6 @@ call Add_field2list( TFIELDDATA( &
   CMNHNAME   = 'RVS_EDDY_FLUX',  &
   CSTDNAME   = '',               &
   CLONGNAME  = 'RVS_EDDY_FLUX',  &
-!TODO PW: units?
   CUNITS     = '',               &
   CDIR       = 'XY',             &
   CCOMMENT   = '',               &
@@ -3211,7 +3207,6 @@ call Add_field2list( TFIELDDATA( &
 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
 !
 IF (TRIM(CPROGRAM)=='REAL' .OR. TRIM(CPROGRAM) == 'LFICDF') THEN
-!PW: not yet known: IF (LFILTERING) THEN
 !
 call Add_field2list( TFIELDDATA( &
   CMNHNAME   = 'UT15',           &
@@ -3467,9 +3462,6 @@ INTEGER,SAVE :: IFIRSTGUESS=1 !Store first field to test
 CHARACTER(LEN=64) :: YMSG
 LOGICAL :: GNOWARNING
 !
-!PW: TODO: possible optimizations:
-! * Classement alphanumerique + index vers 1er champ commencant par caractere
-! * Classement dans l'ordre des ecritures + stockage dernier hit + reboucler depuis le debut => DONE
 !
 IF (.NOT.LFIELDLIST_ISINIT) THEN
   CALL PRINT_MSG(NVERB_FATAL,'GEN','FIND_FIELD_ID_FROM_MNHNAME','TFIELDLIST not yet initialized')
diff --git a/src/LIB/SURCOUCHE/src/mode_io_field_write.f90 b/src/LIB/SURCOUCHE/src/mode_io_field_write.f90
index 5a387ac24..6eed332ee 100644
--- a/src/LIB/SURCOUCHE/src/mode_io_field_write.f90
+++ b/src/LIB/SURCOUCHE/src/mode_io_field_write.f90
@@ -3050,7 +3050,6 @@ end subroutine IO_Ndimlist_reduce
     !
     CALL IO_Format_write_select(TPFILE,GLFI,GNC4)
     !
-!PW: transferer ce traitement LFI dans les subroutines LFI (en creer 1 pour les HFIELD)
     IF(GLFI) THEN
       ILE=LEN(HFIELD)
       IP=SIZE(HFIELD)
@@ -4087,7 +4086,6 @@ DO JI = 1,SIZE(TPOUTPUT%NFIELDLIST)
           ELSE
             call Print_msg( NVERB_ERROR, 'IO', 'IO_Fieldlist_write', trim(tfieldlist(idx)%cmnhname)// &
                             ': CLBTYPE/=NONE not (yet) allowed for 3D real fields' )
-            !PW: TODO?: add missing field in TFIELDLIST?
             !CALL IO_Field_write_lb(TPOUTPUT%TFILE,TFIELDLIST(IDX),***,TFIELDLIST(IDX)%TFIELD_X3D(IMI)%DATA)
           END IF
         !
@@ -4107,7 +4105,6 @@ DO JI = 1,SIZE(TPOUTPUT%NFIELDLIST)
           ELSE
             call Print_msg( NVERB_ERROR, 'IO', 'IO_Fieldlist_write', trim(tfieldlist(idx)%cmnhname)// &
                             ': CLBTYPE/=NONE not (yet) allowed for 3D integer fields' )
-            !PW: TODO?: add missing field in TFIELDLIST?
             !CALL IO_Field_write_lb(TPOUTPUT%TFILE,TFIELDLIST(IDX),***,TFIELDLIST(IDX)%TFIELD_N3D(IMI)%DATA)
           END IF
         !
@@ -4139,7 +4136,6 @@ DO JI = 1,SIZE(TPOUTPUT%NFIELDLIST)
           ELSE
             call Print_msg( NVERB_ERROR, 'IO', 'IO_Fieldlist_write', trim(tfieldlist(idx)%cmnhname)// &
                             ': CLBTYPE/=NONE not (yet) allowed for 4D real fields' )
-            !PW: TODO?: add missing field in TFIELDLIST?
             !CALL IO_Field_write_lb(TPOUTPUT%TFILE,TFIELDLIST(IDX),***,TFIELDLIST(IDX)%TFIELD_X4D(IMI)%DATA)
           END IF
         !
@@ -4171,7 +4167,6 @@ DO JI = 1,SIZE(TPOUTPUT%NFIELDLIST)
           ELSE
             call Print_msg( NVERB_ERROR, 'IO', 'IO_Fieldlist_write', trim(tfieldlist(idx)%cmnhname)// &
                             ': CLBTYPE/=NONE not (yet) allowed for 5D real fields' )
-            !PW: TODO?: add missing field in TFIELDLIST?
             !CALL IO_Field_write_lb(TPOUTPUT%TFILE,TFIELDLIST(IDX),***,TFIELDLIST(IDX)%TFIELD_X5D(IMI)%DATA)
           END IF
         !
@@ -4203,7 +4198,6 @@ DO JI = 1,SIZE(TPOUTPUT%NFIELDLIST)
           ELSE
             call Print_msg( NVERB_ERROR, 'IO', 'IO_Fieldlist_write', trim(tfieldlist(idx)%cmnhname)// &
                             ': CLBTYPE/=NONE not (yet) allowed for 6D real fields' )
-            !PW: TODO?: add missing field in TFIELDLIST?
             !CALL IO_Field_write_lb(TPOUTPUT%TFILE,TFIELDLIST(IDX),***,TFIELDLIST(IDX)%TFIELD_X6D(IMI)%DATA)
           END IF
         !
diff --git a/src/LIB/SURCOUCHE/src/mode_io_manage_struct.f90 b/src/LIB/SURCOUCHE/src/mode_io_manage_struct.f90
index 3174a2947..c3bd1d774 100644
--- a/src/LIB/SURCOUCHE/src/mode_io_manage_struct.f90
+++ b/src/LIB/SURCOUCHE/src/mode_io_manage_struct.f90
@@ -396,7 +396,6 @@ SUBROUTINE IO_SYNC_MODELS_FLOAT(KNUMB,PTIMES)
       !Value is rounded to nearest timestep
       PTIMES(IMI,JOUT) = NINT(PTIMES(IMI,JOUT)/DYN_MODEL(IMI)%XTSTEP) * DYN_MODEL(IMI)%XTSTEP
       !Output/backup time is propagated to nested models (with higher numbers)
-      !PW: TODO: BUG?: what happens if 2 dissociated models? Use NSON(:) array?
       DO JKLOOP = IMI+1,NMODEL
         IDX = 1
         CALL FIND_NEXT_AVAIL_SLOT_FLOAT(PTIMES(JKLOOP,:),IDX)
@@ -419,7 +418,6 @@ SUBROUTINE IO_SYNC_MODELS_INT(KNUMB,KSTEPS)
     IF (KSTEPS(IMI,JOUT) > 0) THEN
       KNUMB = KNUMB + 1
       !Output/backup time is propagated to nested models (with higher numbers)
-      !PW: TODO: BUG?: what happens if 2 dissociated models? Use NSON(:) array?
       DO JKLOOP = IMI+1,NMODEL
         IDX = 1
         CALL FIND_NEXT_AVAIL_SLOT_INT(KSTEPS(JKLOOP,:),IDX)
@@ -587,7 +585,6 @@ SUBROUTINE POPULATE_STRUCT(TPFILE_FIRST,TPFILE_LAST,KSTEPS,HFILETYPE,TPBAKOUTN,K
           CALL PRINT_MSG(NVERB_FATAL,'IO','POPULATE_STRUCT','unknown filetype ('//TRIM(HFILETYPE)//')')
         ENDIF
         TPBAKOUTN(IPOS)%TFILE%NLFITYPE=1 !1: to be transferred
-!PW: TODO: set NLFIVERB only when useful (only if LFI file...)
         TPBAKOUTN(IPOS)%TFILE%NLFIVERB=NVERB
         IF (LIOCDF4) THEN
           IF (.NOT.LLFIOUT) THEN
@@ -635,7 +632,6 @@ SUBROUTINE POPULATE_STRUCT(TPFILE_FIRST,TPFILE_LAST,KSTEPS,HFILETYPE,TPBAKOUTN,K
               TPBAKOUTN(IPOS)%TFILE%TFILES_IOZ(JI)%TFILE%NNCCOMPRESS_LEVEL = NOUT_COMPRESS_LEVEL(IMI)
             END IF
             TPBAKOUTN(IPOS)%TFILE%TFILES_IOZ(JI)%TFILE%NLFITYPE=1 !1: to be transferred
-!PW: TODO: set NLFIVERB only when useful (only if LFI file...)
             TPBAKOUTN(IPOS)%TFILE%TFILES_IOZ(JI)%TFILE%NLFIVERB=NVERB
             IF (LIOCDF4) THEN
               IF (.NOT.LLFIOUT) THEN
diff --git a/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90 b/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90
index f10893a96..9c6c0fc38 100644
--- a/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90
+++ b/src/LIB/SURCOUCHE/src/mode_io_write_nc4.f90
@@ -1939,7 +1939,6 @@ subroutine Gather_hor_coord1d( haxis, pcoords_loc, pcoords_glob )
   endif
 
   !If the file has Z-split subfiles, broadcast the coordinates to all processes
-  !PW: TODO: broadcast only to subfile writers
   if ( tpfile%nsubfiles_ioz > 0 ) &
     call MPI_BCAST( pcoords_glob, size( pcoords_glob ), MNHREAL_MPI, tpfile%nmaster_rank - 1,  tpfile%nmpicomm, ierr )
 
@@ -1989,7 +1988,6 @@ subroutine Gather_hor_coord2d( px, py, plat_glob, plon_glob )
   endif
 
   !If the file has Z-split subfiles, broadcast the coordinates to all processes
-  !PW: TODO: broadcast only to subfile writers
   if ( tpfile%nsubfiles_ioz > 0 ) then
     call MPI_BCAST( plat_glob, size( plat_glob ), MNHREAL_MPI, tpfile%nmaster_rank - 1,  tpfile%nmpicomm, ierr )
     call MPI_BCAST( plon_glob, size( plon_glob ), MNHREAL_MPI, tpfile%nmaster_rank - 1,  tpfile%nmpicomm, ierr )
diff --git a/src/LIB/SURCOUCHE/src/mode_msg.f90 b/src/LIB/SURCOUCHE/src/mode_msg.f90
index ac78920fa..5dfbdc2ef 100644
--- a/src/LIB/SURCOUCHE/src/mode_msg.f90
+++ b/src/LIB/SURCOUCHE/src/mode_msg.f90
@@ -129,7 +129,6 @@ IF (ASSOCIATED(TFILE_OUTPUTLISTING)) THEN
     IF (GWRITE_STDOUT) WRITE(UNIT=OUTPUT_UNIT,FMT=*) 'TFILE_OUTPUTLISTING not opened'
   END IF
 ELSE
-!PW: TODO?: temporary to detect non-initialisation
 ! should disappear except at the beginning of a run
   GWRITE_OUTLST = .FALSE.
   IF (GWRITE_STDOUT .AND. CPROGRAM/='LFICDF') WRITE(UNIT=OUTPUT_UNIT,FMT=*) 'TFILE_OUTPUTLISTING not associated'
diff --git a/src/MNH/ini_aircraft_balloon.f90 b/src/MNH/ini_aircraft_balloon.f90
index 81a9ac304..fb6aba612 100644
--- a/src/MNH/ini_aircraft_balloon.f90
+++ b/src/MNH/ini_aircraft_balloon.f90
@@ -463,7 +463,6 @@ IF ( IMI == 1 ) THEN
   END IF
 
   CALL FLYER_TIMESTEP_CORRECT( DYN_MODEL(IMODEL)%XTSTEP, TPFLYER )
-print *,'PW: ',tpflyer%CNAME,': IMI,XTSTEPaircaft=',IMI,TPFLYER%TFLYER_TIME%XTSTEP
 END IF
 
 ALLOCATE(TPFLYER%XPOSX(TPFLYER%NPOS))
diff --git a/src/MNH/modd_budget.f90 b/src/MNH/modd_budget.f90
index 0270f474a..3b413d569 100644
--- a/src/MNH/modd_budget.f90
+++ b/src/MNH/modd_budget.f90
@@ -124,7 +124,6 @@ type, extends( tfieldmetadata_base ) :: tburhodata
   real, dimension(:,:,:), allocatable :: xdata ! Array to store the budget data
 end type tburhodata
 
-!PW: a commenter + renommer???
 type :: tbudiachrometadata
   character(len=NBUNAMELGTMAX),  dimension(NMAXLEVELS) :: clevels  = '' !Name of the different groups/levels in the netCDF file
   character(len=NCOMMENTLGTMAX), dimension(NMAXLEVELS) :: ccomments ='' !Comments for the different groups/levels in the netCDF file
diff --git a/src/MNH/mode_les_diachro.f90 b/src/MNH/mode_les_diachro.f90
index 8f848f4e9..9b20b01f4 100644
--- a/src/MNH/mode_les_diachro.f90
+++ b/src/MNH/mode_les_diachro.f90
@@ -1183,7 +1183,6 @@ if ( iresp == 0 .and. any( zfield /= XUNDEF ) ) then
         tzfields(jp)%ndims     = tzfields(jp)%ndims - 1
 
         tzbudiachro%clevels(NLVL_MASK) = hmasks(jp)
-!PW:TODO? necessite le transfert d'info depuis les routines appelantes ou via des structures dans les modd
         tzbudiachro%ccomments(NLVL_MASK) = ''
 
         call Write_diachro( tzfile, tzbudiachro, [ tzfields(jp) ], tzdates, zwork6(:,:,:,:,:,jp:jp) )
diff --git a/src/MNH/profilern.f90 b/src/MNH/profilern.f90
index d176c7991..f36998381 100644
--- a/src/MNH/profilern.f90
+++ b/src/MNH/profilern.f90
@@ -212,7 +212,6 @@ IF ( .NOT. TPROFILERS_TIME%STORESTEP_CHECK_AND_SET( IN ) ) RETURN !No profiler s
 !*      8.   DATA RECORDING
 !            --------------
 !
-!PW: TODO: ne faire le calcul que si necessaire (presence de profileurs locaux,...)
 ZTEMP(:,:,:)=PTH(:,:,:)*(PP(:,:,:)/ XP00) **(XRD/XCPD)
 ! Theta_v
 ZTHV(:,:,:) = PTH(:,:,:) / (1.+WATER_SUM(PR(:,:,:,:)))*(1.+PR(:,:,:,1)/ZRDSRV)
diff --git a/src/MNH/read_grid_time_mesonh_case.f90 b/src/MNH/read_grid_time_mesonh_case.f90
index fba1ea9e9..c6446d4ee 100644
--- a/src/MNH/read_grid_time_mesonh_case.f90
+++ b/src/MNH/read_grid_time_mesonh_case.f90
@@ -150,8 +150,6 @@ TYPE(TFILEDATA),POINTER :: TZFMFILE => NULL()
 ILUOUT0 = TLUOUT0%NLU
 ZEPS=1.E-10
 !
-!PW: TODO: temporary: look for file from its name
-!     TPFMFILE should be passed in arguments
 CALL IO_File_find_byname(HFMFILE,TZFMFILE,IRESP)
 !
 !*       1.1   Original FMfile name
diff --git a/src/MNH/write_les_rt_budgetn.f90 b/src/MNH/write_les_rt_budgetn.f90
index 66df13ade..94d5c9902 100644
--- a/src/MNH/write_les_rt_budgetn.f90
+++ b/src/MNH/write_les_rt_budgetn.f90
@@ -467,7 +467,6 @@ ZLES_BUDGET(:,:,ILES) =  XG * XLES_SUBGRID_RtThv(:,:,1)   &
 !* 3.6 dissipation
 !      -----------
 !
-!PW: not in the documentation, but set to 0 anyway
 ILES=ILES+1
 YFIELDNAMES(ILES)    = 'SBG_DISS'
 YFIELDCOMMENTS(ILES) = 'subgrid dissipation'
diff --git a/src/MNH/write_les_sv_budgetn.f90 b/src/MNH/write_les_sv_budgetn.f90
index 8a412845f..538e1a3f3 100644
--- a/src/MNH/write_les_sv_budgetn.f90
+++ b/src/MNH/write_les_sv_budgetn.f90
@@ -520,7 +520,6 @@ END IF
 !      -----------
 !
 ILES=ILES+1
-!PW: not in documentation. Always set to 0
 YFIELDNAMES(ILES)    = 'SBG_DISS'
 YFIELDCOMMENTS(ILES) = 'subgrid dissipation'
 !
diff --git a/src/MNH/write_lesn.f90 b/src/MNH/write_lesn.f90
index 2e18f72ad..43a186a4f 100644
--- a/src/MNH/write_lesn.f90
+++ b/src/MNH/write_lesn.f90
@@ -1150,14 +1150,12 @@ if ( nspectra_k > 0 ) then
     call Les_diachro_2pt_write( tpdiafile, XCORRi_WRi,   XCORRj_WRi,   'WRI',  'W*ri    2 points correlations', 'm kg s-1 kg-1' )
   end if
 
-!PW: TODO: ameliorer le ygroup (tenir compte de ce qu'est la variable scalaire et pas juste son jsv!)
   do jsv = 1, nsv
     Write( ygroup, fmt = "( a2, i3.3 )" ) "SS", jsv
     call Les_diachro_2pt_write( tpdiafile, XCORRi_SvSv(:,:,:,JSV), XCORRj_SvSv(:,:,:,JSV), ygroup, &
                                 'Sv*Sv   2 points correlations','kg2 kg-2' )
   end do
 
-!PW: TODO: ameliorer le ygroup (tenir compte de ce qu'est la variable scalaire et pas juste son jsv!)
   do jsv = 1, nsv
     Write( ygroup, fmt = "( a2, i3.3 )" ) "WS", jsv
     call Les_diachro_2pt_write( tpdiafile, XCORRi_WSv(:,:,:,JSV), XCORRj_WSv(:,:,:,JSV), ygroup, &
diff --git a/src/MNH/write_lfifm1_for_diag.f90 b/src/MNH/write_lfifm1_for_diag.f90
index a6099e6a0..0fa23ed0e 100644
--- a/src/MNH/write_lfifm1_for_diag.f90
+++ b/src/MNH/write_lfifm1_for_diag.f90
@@ -1087,7 +1087,6 @@ IF (LLIMA_DIAG) THEN
   END IF
   !
   DO JSV = NSV_LIMA_BEG,NSV_LIMA_END
-!PW: bases sur CLIMA_*_CONC et pas CLIMA_*_NAMES !!!
     !
     TZFIELD%CUNITS     = 'cm-3'
     WRITE(TZFIELD%CCOMMENT,'(A6,A3,I3.3)')'X_Y_Z_','SVT',JSV
@@ -1194,7 +1193,6 @@ IF (LLIMA_DIAG) THEN
   END IF
 !
 END IF
-!PW: TODO: a documenter
 IF (LELECDIAG .AND. CELEC .NE. "NONE") THEN
   DO JSV = NSV_ELECBEG,NSV_ELECEND
     TZFIELD = TSVLIST(JSV)
@@ -1279,7 +1277,6 @@ IF (LPASPOL) THEN
 END IF
 ! Conditional sampling variables
 IF (LCONDSAMP) THEN
-!PW: TODO: a documenter!!!
   DO JSV = NSV_CSBEG, NSV_CSEND
     TZFIELD = TSVLIST(JSV)
     CALL IO_Field_write(TPFILE,TZFIELD,XSVT(:,:,:,JSV))
@@ -1319,7 +1316,6 @@ IF (LCHAQDIAG) THEN    !aqueous concentration in M
 
 
 
-!PW: TODO: LCHICDIAG n'existe pas => les variables correspondantes ne sont pas ecrites...
 
 !  ZWORK31(:,:,:)=0.
 !  DO JSV = NSV_CHICBEG,NSV_CHICEND   ! ice phase
@@ -1868,7 +1864,6 @@ END IF
 !  Blowing snow variables
 !
 IF(LBLOWSNOW) THEN
-!PW:TODO?:variables scalaires XSVT pas ecrites ici. Voulu?
   TZFIELD = TFIELDMETADATA(                                             &
     CMNHNAME   = 'SNWSUBL3D',                                           &
     CSTDNAME   = '',                                                    &
diff --git a/src/MNH/zoom_pgd.f90 b/src/MNH/zoom_pgd.f90
index 0763fd283..5f8630d8d 100644
--- a/src/MNH/zoom_pgd.f90
+++ b/src/MNH/zoom_pgd.f90
@@ -198,7 +198,6 @@ IF ( (LEN_TRIM(YZOOMFILE) == 0) .OR. (ADJUSTL(YZOOMFILE) == ADJUSTL(CPGDFILE)) )
 END IF
 !
 CALL IO_File_add2list(TZZOOMFILE,TRIM(YZOOMFILE),'PGD','WRITE',KLFINPRAR=INT(1,KIND=LFIINT),KLFITYPE=1,KLFIVERB=5)
-!PW: TODO: points to dad file (if existing) ! TZZOOMFILE%TDADFILE =>
 !
 CALL IO_File_open(TZZOOMFILE)
 CALL WRITE_HGRID(1,TZZOOMFILE)
diff --git a/src/MNH/zsmt_pgd.f90 b/src/MNH/zsmt_pgd.f90
index 3aea708e6..37b88613b 100644
--- a/src/MNH/zsmt_pgd.f90
+++ b/src/MNH/zsmt_pgd.f90
@@ -155,8 +155,6 @@ ALLOCATE(ZYHAT(IJU))
 CALL IO_Field_read(TPFILE,'XHAT',ZXHAT)
 CALL IO_Field_read(TPFILE,'YHAT',ZYHAT)
 
-!PW: bug/TODO: read a field in a file opened in WRITE mode
-!There is a test in IO_Field_read_BYFIELD_X2 to allow this if TPFILE%CMODE='LFICDF4'
 CALL IO_Field_read(TPFILE,'ZS',ZZS)
 !
 DO JI=1,JPHEXT
diff --git a/src/PHYEX/micro/rain_ice_warm.f90 b/src/PHYEX/micro/rain_ice_warm.f90
index 133dc888b..0a781900c 100644
--- a/src/PHYEX/micro/rain_ice_warm.f90
+++ b/src/PHYEX/micro/rain_ice_warm.f90
@@ -72,7 +72,6 @@ REAL,     DIMENSION(:),     INTENT(INOUT) :: PRVS     ! Water vapor m.r. source
 REAL,     DIMENSION(:),     INTENT(INOUT) :: PRCS     ! Cloud water m.r. source
 REAL,     DIMENSION(:),     INTENT(INOUT) :: PRRS     ! Rain water m.r. source
 REAL,     DIMENSION(:),     INTENT(INOUT) :: PTHS     ! Theta source
-!PW: PUSW could be a purely local variable?
 REAL,     DIMENSION(:),     INTENT(INOUT) :: PUSW     ! Undersaturation over water
 REAL,     DIMENSION(:,:,:), INTENT(INOUT) :: PEVAP3D  ! Rain evap profile
 !
diff --git a/src/PHYEX/turb/mode_turb_ver_sv_flux.f90 b/src/PHYEX/turb/mode_turb_ver_sv_flux.f90
index 27b189c1b..21443271d 100644
--- a/src/PHYEX/turb/mode_turb_ver_sv_flux.f90
+++ b/src/PHYEX/turb/mode_turb_ver_sv_flux.f90
@@ -454,7 +454,6 @@ DO JSV=1,KSV
       CMNHNAME   = TRIM( YMNHNAME ),             &
       CSTDNAME   = '',                           &
       CLONGNAME  = TRIM( YMNHNAME ),             &
-    !PW: TODO: use the correct units of the JSV variable (and multiply it by m s-1)
       CUNITS     = 'SVUNIT m s-1',               &
       CDIR       = 'XY',                         &
       CCOMMENT   = 'X_Y_Z_' // TRIM( YMNHNAME ), &
-- 
GitLab