subroutine wrselafin ( out_prefix , version , start_time , ne , np , & & nm , x , y , dp , nopenbnds , & & openbnds , nopenbndnodes , openbndnodes ) ! Deltares Software Centre !>\file !> Writes Telemac Selafin file out of Selfe data ! Created : January 2013 By Leo Postma ! Modified : ! Subroutines called : wrwaqhyd ! Logical units : 534 = unit TELEMAC selafin / serafin file ! 535 = unit TELEMAC cli, boundary nodes definition file implicit none ! Parameters : ! kind function name Descriptipon character( *), intent(in ) :: out_prefix !< Output files prefix string character(48), intent(in ) :: version !< Selfe documentation string character(48), intent(in ) :: start_time !< Start time string Selfe integer ( 4), intent(in ) :: ne !< Number of elements integer ( 4), intent(in ) :: np !< Number of nodes (points) integer ( 4), intent(in ) :: nm(ne,3) !< Connectivity table real ( 4), intent(in ) :: x (np) !< X-values of the points real ( 4), intent(in ) :: y (np) !< Y-values of the points real ( 4), intent(in ) :: dp(np) !< Depth values at the points integer ( 4), intent(in ) :: nopenbnds !< Number of open boundaries integer ( 4), intent(in ) :: openbnds (2, nopenbnds ) !< Open boundary definitions integer ( 4), intent(in ) :: nopenbndnodes !< Number of open boundary nodes integer ( 4), intent(in ) :: openbndnodes(nopenbndnodes) !< Their nodenumbers ! Locals character(128) outstrng ! Help string for output integer ( 4 ) i, j, k ! Loop and help variables integer ( 4 ) iparam(10) ! integers table integer ( 4 ), allocatable :: ipobo(:) ! boundary points outstrng = out_prefix i = len_trim(outstrng) outstrng(i:i+3) = '.dat' open ( 534, file=outstrng, form='unformatted', convert='big_endian' ) outstrng = out_prefix i = len_trim(outstrng) outstrng(i:i+3) = '.cli' open ( 535, file=outstrng ) outstrng = 'Selfetest' outstrng(11:50) = version outstrng(51:80) = start_time write ( 534 ) outstrng(1:80) write ( 534 ) 1, 0 write ( 534 ) "FOND m " iparam = 0 iparam(1) = 1 write ( 534 ) iparam iparam(1) = ne iparam(2) = np iparam(3) = 3 iparam(4) = 1 write ( 534 ) iparam(1:4) write ( 534 ) (nm(i,:),i=1,ne) allocate ( ipobo(np) ) ipobo = 0 do i=1,nopenbndnodes+nopenbnds+1 ipobo(i) = i enddo write ( 534 ) ipobo write ( 534 ) x write ( 534 ) y write ( 534 ) 0.0 write ( 534 ) dp close ( 534 ) k = 1 do i = 1,nopenbnds write ( 535, '(A,2i6)' ) '2 2 2 0.000000 0.000000 0.000000 0.000000 2 0.000000 0.000000 0.000000 ',0,0 do j = openbnds(1,i) , openbnds(2,i) write ( 535, '(A,2i6)' ) '5 4 4 0.000000 0.000000 0.000000 0.000000 4 0.000000 0.000000 0.000000 ',openbndnodes(k),0 k = k + 1 enddo enddo write ( 535, '(A,2i6)' ) '2 2 2 0.000000 0.000000 0.000000 0.000000 2 0.000000 0.000000 0.000000 ',0,0 close ( 535 ) return end