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 2287 for branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS – NEMO

Ignore:
Timestamp:
2010-10-18T09:53:52+02:00 (14 years ago)
Author:
smasson
Message:

update licence of all NEMO files...

Location:
branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS
Files:
54 edited
3 moved

Legend:

Unmodified
Added
Removed
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/ddatetoymdhms.h90

    r2281 r2287  
     1   !!---------------------------------------------------------------------- 
     2   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     3   !! $Id$ 
     4   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     5   !!---------------------------------------------------------------------- 
     6 
    17   SUBROUTINE ddatetoymdhms( ddate, kyea, kmon, kday, khou, kmin, ksec ) 
    28      !!---------------------------------------------------------------------- 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/diaobs.F90

    r2281 r2287  
    104104   LOGICAL, DIMENSION(:), ALLOCATABLE :: & 
    105105      & ld_velav     !: Velocity data is daily averaged 
     106 
     107   !!---------------------------------------------------------------------- 
     108   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     109   !! $Id$ 
     110   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     111   !!---------------------------------------------------------------------- 
    106112 
    107113CONTAINS 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/find_obs_proc.h90

    r2281 r2287  
     1   !!---------------------------------------------------------------------- 
     2   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     3   !! $Id$ 
     4   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     5   !!---------------------------------------------------------------------- 
     6 
    17   SUBROUTINE find_obs_proc(kldi,klei,kldj,klej,kmyproc,kobsp,kobsi,kobsj,kno) 
    28      !!---------------------------------------------------------------------- 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/grt_cir_dis.h90

    r2281 r2287  
     1   !!---------------------------------------------------------------------- 
     2   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     3   !! $Id$ 
     4   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     5   !!---------------------------------------------------------------------- 
     6 
    17   REAL(KIND=wp) FUNCTION grt_cir_dis( pa1, pa2, pb1, pb2, pc1, pc2 ) 
    28      !!---------------------------------------------------------------------- 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/grt_cir_dis_saa.h90

    r2281 r2287  
     1   !!---------------------------------------------------------------------- 
     2   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     3   !! $Id$ 
     4   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     5   !!---------------------------------------------------------------------- 
     6 
    17   REAL(KIND=wp) FUNCTION grt_cir_dis_saa( pa, pb, pc ) 
    28      !!---------------------------------------------------------------------- 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/linquad.h90

    r2281 r2287  
     1   !!---------------------------------------------------------------------- 
     2   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     3   !! $Id$ 
     4   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     5   !!---------------------------------------------------------------------- 
     6 
    17   LOGICAL FUNCTION linquad( px, py, pxv, pyv ) 
    28      !!---------------------------------------------------------------------- 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/maxdist.h90

    r2281 r2287  
     1   !!---------------------------------------------------------------------- 
     2   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     3   !! $Id$ 
     4   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     5   !!---------------------------------------------------------------------- 
     6 
    17   REAL FUNCTION maxdist( pxv, pyv ) 
    28      !!---------------------------------------------------------------------- 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/mpp_map.F90

    r2281 r2287  
    4242   INTEGER, DIMENSION(:,:), ALLOCATABLE :: & 
    4343      & mppmap 
     44 
     45   !!---------------------------------------------------------------------- 
     46   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     47   !! $Id$ 
     48   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     49   !!---------------------------------------------------------------------- 
    4450 
    4551CONTAINS 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_const.F90

    r2281 r2287  
    44   !! Observation diagnostics: Constants used by many modules 
    55   !!=====================================================================  
     6   !!---------------------------------------------------------------------- 
     7   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     8   !! $Id$ 
     9   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     10   !!---------------------------------------------------------------------- 
     11 
    612   !! * Modules used 
    713   USE par_kind, ONLY : & ! Precision variables 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_conv.F90

    r2281 r2287  
    3434      & dep_to_p 
    3535    
     36   !!---------------------------------------------------------------------- 
     37   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     38   !! $Id$ 
     39   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     40   !!---------------------------------------------------------------------- 
     41 
    3642CONTAINS 
    3743 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_conv_functions.h90

    r2281 r2287  
    1    REAL(KIND=wp) FUNCTION potemp( ps, pt, pp, ppr ) 
     1    !!---------------------------------------------------------------------- 
     2   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     3   !! $Id$ 
     4   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     5   !!---------------------------------------------------------------------- 
     6 
     7  REAL(KIND=wp) FUNCTION potemp( ps, pt, pp, ppr ) 
    28      !!---------------------------------------------------------------------- 
    39      !!                    ***  FUNCTION potemp  *** 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_fbm.F90

    r2281 r2287  
    126126 
    127127   PRIVATE putvaratt_obfbdata 
     128 
     129   !!---------------------------------------------------------------------- 
     130   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     131   !! $Id$ 
     132   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     133   !!---------------------------------------------------------------------- 
    128134 
    129135CONTAINS 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_grid.F90

    r2281 r2287  
    8282   CHARACTER(LEN=44), PUBLIC :: & 
    8383      & grid_search_file    ! file name head for grid search lookup  
     84 
     85   !!---------------------------------------------------------------------- 
     86   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     87   !! $Id$ 
     88   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     89   !!---------------------------------------------------------------------- 
    8490 
    8591CONTAINS 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_grid_search_bruteforce.h90

    r2281 r2287  
     1   !!---------------------------------------------------------------------- 
     2   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     3   !! $Id$ 
     4   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     5   !!---------------------------------------------------------------------- 
     6 
    17   SUBROUTINE obs_grid_search_bruteforce( kpi, kpj, kpiglo, kpjglo,       & 
    28      &                                   kldi, klei, kldj, klej,         & 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_inter_h2d.F90

    r2281 r2287  
    4444      &   obs_int_h2d_init    ! Set up weights and vertical mask 
    4545 
     46   !!---------------------------------------------------------------------- 
     47   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     48   !! $Id$ 
     49   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     50   !!---------------------------------------------------------------------- 
     51 
    4652CONTAINS 
    4753  
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_inter_sup.F90

    r2281 r2287  
    2626      &   obs_int_comm_2d    ! Get 2D interpolation stencil 
    2727    
     28   !!---------------------------------------------------------------------- 
     29   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     30   !! $Id$ 
     31   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     32   !!---------------------------------------------------------------------- 
     33 
    2834CONTAINS 
    2935 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_inter_z1d.F90

    r2281 r2287  
    2424                             ! interpolating function used with a cubic spline 
    2525 
     26   !!---------------------------------------------------------------------- 
     27   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     28   !! $Id$ 
     29   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     30   !!---------------------------------------------------------------------- 
     31 
    2632CONTAINS 
    2733 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_level_search.h90

    r2281 r2287  
     1   !!---------------------------------------------------------------------- 
     2   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     3   !! $Id$ 
     4   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     5   !!---------------------------------------------------------------------- 
     6 
    17   SUBROUTINE obs_level_search( kgrd, pgrddep, kobs, pobsdep, kobsk ) 
    28      !!---------------------------------------------------------------------- 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_mpp.F90

    r2281 r2287  
    4646      &   mpp_alltoallv_real,    & 
    4747      &   mpp_global_max 
     48 
     49   !!---------------------------------------------------------------------- 
     50   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     51   !! $Id$ 
     52   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     53   !!---------------------------------------------------------------------- 
    4854 
    4955CONTAINS 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_oper.F90

    r2281 r2287  
    5252 
    5353   INTEGER, PARAMETER, PUBLIC :: imaxavtypes = 20 ! Max number of daily avgd obs types 
     54 
     55   !!---------------------------------------------------------------------- 
     56   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     57   !! $Id$ 
     58   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     59   !!---------------------------------------------------------------------- 
    5460 
    5561CONTAINS 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_prep.F90

    r2281 r2287  
    4040      & obs_pre_vel, &     ! First level check and screening of velocity profiles 
    4141      & calc_month_len     ! Calculate the number of days in the months of a year   
     42 
     43   !!---------------------------------------------------------------------- 
     44   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     45   !! $Id$ 
     46   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     47   !!---------------------------------------------------------------------- 
    4248 
    4349CONTAINS 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_prof_io.F90

    r2281 r2287  
    2020   INTEGER, PARAMETER :: imaxlev = 10000 
    2121 
     22   !!---------------------------------------------------------------------- 
     23   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     24   !! $Id$ 
     25   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     26   !!---------------------------------------------------------------------- 
     27 
    2228CONTAINS 
    2329 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_profiles.F90

    r2281 r2287  
    55   !!                          arrays and additional flags etc. 
    66   !!===================================================================== 
     7   !!---------------------------------------------------------------------- 
     8   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     9   !! $Id$ 
     10   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     11   !!---------------------------------------------------------------------- 
     12 
    713    
    814   !! * Modules used  
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_profiles_def.F90

    r2281 r2287  
    183183 
    184184   END TYPE obs_prof 
     185 
     186   !!---------------------------------------------------------------------- 
     187   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     188   !! $Id$ 
     189   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     190   !!---------------------------------------------------------------------- 
    185191 
    186192CONTAINS 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_read_altbias.F90

    r2281 r2287  
    4141   PUBLIC obs_rea_altbias     ! Read the altimeter bias 
    4242 
     43   !!---------------------------------------------------------------------- 
     44   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     45   !! $Id$ 
     46   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     47   !!---------------------------------------------------------------------- 
     48 
    4349CONTAINS 
    4450 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_read_prof.F90

    r2281 r2287  
    3333 
    3434   PUBLIC obs_rea_pro_dri  ! Read the profile observations  
     35 
     36   !!---------------------------------------------------------------------- 
     37   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     38   !! $Id$ 
     39   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     40   !!---------------------------------------------------------------------- 
    3541 
    3642CONTAINS 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_read_seaice.F90

    r2281 r2287  
    3131 
    3232   PUBLIC obs_rea_seaice      ! Read the seaice observations from the point data 
    33  
    3433    
     34   !!---------------------------------------------------------------------- 
     35   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     36   !! $Id$ 
     37   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     38   !!---------------------------------------------------------------------- 
     39 
    3540CONTAINS 
    3641 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_read_sla.F90

    r2281 r2287  
    3131 
    3232   PUBLIC obs_rea_sla  ! Read the SLA observations from the AVISO/SLA database 
     33 
     34   !!---------------------------------------------------------------------- 
     35   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     36   !! $Id$ 
     37   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     38   !!---------------------------------------------------------------------- 
    3339 
    3440CONTAINS 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_read_sst.F90

    r2281 r2287  
    3434   PUBLIC obs_rea_sst_rey  ! Read the gridded Reynolds SST  
    3535    
     36   !!---------------------------------------------------------------------- 
     37   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     38   !! $Id$ 
     39   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     40   !!---------------------------------------------------------------------- 
     41 
    3642CONTAINS 
    3743 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_read_vel.F90

    r2281 r2287  
    3333 
    3434   PUBLIC obs_rea_vel_dri  ! Read the profile observations  
     35 
     36   !!---------------------------------------------------------------------- 
     37   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     38   !! $Id$ 
     39   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     40   !!---------------------------------------------------------------------- 
    3541 
    3642CONTAINS 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_readmdt.F90

    r2281 r2287  
    5454                          ! used one 
    5555 
     56   !!---------------------------------------------------------------------- 
     57   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     58   !! $Id$ 
     59   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     60   !!---------------------------------------------------------------------- 
     61 
    5662CONTAINS 
    5763 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_rot_vel.F90

    r2281 r2287  
    2727 
    2828   PUBLIC obs_rotvel            ! Rotate the observations 
     29 
     30   !!---------------------------------------------------------------------- 
     31   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     32   !! $Id$ 
     33   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     34   !!---------------------------------------------------------------------- 
    2935 
    3036CONTAINS 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_seaice.F90

    r2281 r2287  
    55   !!                          arrays and additional flags etc. 
    66   !!===================================================================== 
     7   !!---------------------------------------------------------------------- 
     8   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     9   !! $Id$ 
     10   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     11   !!---------------------------------------------------------------------- 
     12 
    713    
    814   !! * Modules used  
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_seaice_io.F90

    r2281 r2287  
    1818   IMPLICIT NONE 
    1919 
     20   !!---------------------------------------------------------------------- 
     21   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     22   !! $Id$ 
     23   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     24   !!---------------------------------------------------------------------- 
     25 
    2026CONTAINS 
    2127 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_sla.F90

    r2281 r2287  
    55   !!                          arrays and additional flags etc. 
    66   !!===================================================================== 
     7   !!---------------------------------------------------------------------- 
     8   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     9   !! $Id$ 
     10   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     11   !!---------------------------------------------------------------------- 
    712    
    813   !! * Modules used  
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_sla_io.F90

    r2281 r2287  
    1818   IMPLICIT NONE 
    1919 
     20   !!---------------------------------------------------------------------- 
     21   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     22   !! $Id$ 
     23   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     24   !!---------------------------------------------------------------------- 
     25 
    2026CONTAINS 
    2127 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_sla_types.F90

    r2281 r2287  
    88   !!---------------------------------------------------------------------- 
    99   !!---------------------------------------------------------------------- 
     10   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     11   !! $Id$ 
     12   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    1013   !!---------------------------------------------------------------------- 
     14 
    1115   IMPLICIT NONE 
    1216 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_sort.F90

    r2281 r2287  
    2020   PUBLIC sort_dp_indx   ! Get indicies for ascending order for a double prec. array 
    2121   
     22   !!---------------------------------------------------------------------- 
     23   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     24   !! $Id$ 
     25   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     26   !!---------------------------------------------------------------------- 
     27 
    2228CONTAINS 
    2329 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_sst.F90

    r2281 r2287  
    55   !!                          arrays and additional flags etc. 
    66   !!===================================================================== 
     7   !!---------------------------------------------------------------------- 
     8   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     9   !! $Id$ 
     10   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     11   !!---------------------------------------------------------------------- 
     12 
    713    
    814   !! * Modules used  
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_sst_io.F90

    r2281 r2287  
    1818   IMPLICIT NONE 
    1919 
     20   !!---------------------------------------------------------------------- 
     21   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     22   !! $Id$ 
     23   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     24   !!---------------------------------------------------------------------- 
     25 
    2026CONTAINS 
    2127 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_surf_def.F90

    r2281 r2287  
    9494 
    9595   END TYPE obs_surf 
     96 
     97   !!---------------------------------------------------------------------- 
     98   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     99   !! $Id$ 
     100   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     101   !!---------------------------------------------------------------------- 
    96102 
    97103CONTAINS 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_types.F90

    r2281 r2287  
    4646   PUBLIC obs_wmo_init 
    4747   PUBLIC obs_alt_typ_init 
     48 
     49   !!---------------------------------------------------------------------- 
     50   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     51   !! $Id$ 
     52   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     53   !!---------------------------------------------------------------------- 
    4854 
    4955CONTAINS  
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_utils.F90

    r2281 r2287  
    3333      &   ddatetoymdhms       ! Convert YYYYMMDD.hhmmss to components 
    3434          
     35   !!---------------------------------------------------------------------- 
     36   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     37   !! $Id$ 
     38   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     39   !!---------------------------------------------------------------------- 
     40 
    3541CONTAINS 
    3642  
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_vel_io.F90

    r2281 r2287  
    2020   INTEGER, PARAMETER :: imaxlev = 10000 
    2121 
     22   !!---------------------------------------------------------------------- 
     23   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     24   !! $Id$ 
     25   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     26   !!---------------------------------------------------------------------- 
     27 
    2228CONTAINS 
    2329 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_write.F90

    r2281 r2287  
    5151      CHARACTER(len=ilenunit), POINTER, DIMENSION(:,:) :: cdunit 
    5252   END TYPE obswriinfo 
     53 
     54   !!---------------------------------------------------------------------- 
     55   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     56   !! $Id$ 
     57   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     58   !!---------------------------------------------------------------------- 
    5359 
    5460CONTAINS 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obsinter_h2d.h90

    r2281 r2287  
    11   !!---------------------------------------------------------------------- 
    2    !!    This software is governed by the CeCILL licence (Version 2) 
    3    !!    (See NEMOVAR_CeCILL.txt) 
     2   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     3   !! $Id$ 
     4   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    45   !!---------------------------------------------------------------------- 
     6 
    57   SUBROUTINE obs_int_h2d_init( kpk,   kpk2,  k2dint, plam,  pphi, & 
    68      &                         pglam, pgphi, pmask,  pweig, pobsmask, & 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obsinter_z1d.h90

    r2281 r2287  
     1   !!---------------------------------------------------------------------- 
     2   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     3   !! $Id$ 
     4   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     5   !!---------------------------------------------------------------------- 
     6 
    17   SUBROUTINE obs_int_z1d( kpk, kkco, k1dint, kdep, & 
    28      &                    pobsdep, pobsk, pobs2k,  & 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obsprof_io.h90

    r2281 r2287  
     1   !!---------------------------------------------------------------------- 
     2   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     3   !! $Id$ 
     4   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     5   !!---------------------------------------------------------------------- 
    16 
    27   SUBROUTINE read_enactfile( cdfilename, inpfile, kunit, ldwp, ldgrid ) 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obsseaice_io.h90

    r2281 r2287  
     1   !!---------------------------------------------------------------------- 
     2   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     3   !! $Id$ 
     4   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     5   !!---------------------------------------------------------------------- 
     6 
    17   SUBROUTINE read_seaice( cdfilename, inpfile, kunit, ldwp, ldgrid ) 
    28      !!--------------------------------------------------------------------- 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obssla_io.h90

    r2281 r2287  
     1   !!---------------------------------------------------------------------- 
     2   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     3   !! $Id$ 
     4   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     5   !!---------------------------------------------------------------------- 
     6 
    17   SUBROUTINE read_avisofile( cdfilename, inpfile, kunit, ldwp, ldgrid ) 
    28      !!--------------------------------------------------------------------- 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obssla_types.h90

    r2281 r2287  
     1   !!---------------------------------------------------------------------- 
     2   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     3   !! $Id$ 
     4   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     5   !!---------------------------------------------------------------------- 
     6 
    17   INTEGER, PARAMETER :: imaxmissions=8 
    28   CHARACTER(len=3) :: cmissions(0:imaxmissions) = & 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obssst_io.h90

    r2281 r2287  
     1   !!---------------------------------------------------------------------- 
     2   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     3   !! $Id$ 
     4   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     5   !!---------------------------------------------------------------------- 
     6 
    17   SUBROUTINE read_ghrsst( cdfilename, inpfile, kunit, ldwp, ldgrid ) 
    28      !!--------------------------------------------------------------------- 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obsvel_io.h90

    r2281 r2287  
     1   !!---------------------------------------------------------------------- 
     2   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     3   !! $Id$ 
     4   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     5   !!---------------------------------------------------------------------- 
     6 
    17   SUBROUTINE read_taondbc( cdfilename, inpfile, kunit, ldwp, ldgrid ) 
    28      !!--------------------------------------------------------------------- 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/str_c_to_for.h90

    r2281 r2287  
     1   !!---------------------------------------------------------------------- 
     2   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     3   !! $Id$ 
     4   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     5   !!---------------------------------------------------------------------- 
     6 
    17   SUBROUTINE str_c_to_for( cd_str ) 
    28      !!--------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.