@@ -202,9 +202,12 @@ end subroutine SetErr
202202! ===============================================================================================================
203203!- -------------------------------------------- HydroDyn Init----------------------------------------------------
204204! ===============================================================================================================
205- SUBROUTINE HydroDyn_C_Init ( OutRootName_C , &
205+ SUBROUTINE HydroDyn_C_Init ( &
206+ SeaSt_InputFilePassed , &
206207 SeaSt_InputFileString_C , SeaSt_InputFileStringLength_C , &
208+ HD_InputFilePassed , &
207209 HD_InputFileString_C , HD_InputFileStringLength_C , &
210+ OutRootName_C , &
208211 Gravity_C , defWtrDens_C , defWtrDpth_C , defMSL2SWL_C , &
209212 PtfmRefPtPositionX_C , PtfmRefPtPositionY_C , &
210213 NumNodePts_C , InitNodePositions_C , &
@@ -218,11 +221,13 @@ SUBROUTINE HydroDyn_C_Init( OutRootName_C,
218221! GCC$ ATTRIBUTES DLLEXPORT :: HydroDyn_C_Init
219222#endif
220223
221- character (kind = c_char ), intent (in ) :: OutRootName_C(IntfStrLen) ! < Root name to use for echo files and other
224+ integer (c_int ), intent (in ) :: SeaSt_InputFilePassed ! < 0: pass the input file name; 1: pass the input file content
222225 type (c_ptr), intent (in ) :: SeaSt_InputFileString_C ! < SeaSt input file as a single string with lines deliniated by C_NULL_CHAR
223226 integer (c_int), intent (in ) :: SeaSt_InputFileStringLength_C ! < SeaSt length of the input file string
227+ integer (c_int), intent (in ) :: HD_InputFilePassed ! < 0: pass the input file name; 1: pass the input file content
224228 type (c_ptr), intent (in ) :: HD_InputFileString_C ! < HD input file as a single string with lines deliniated by C_NULL_CHAR
225229 integer (c_int), intent (in ) :: HD_InputFileStringLength_C ! < HD length of the input file string
230+ character (kind= c_char), intent (in ) :: OutRootName_C(IntfStrLen) ! < Root name to use for echo files and other
226231 real (c_float), intent (in ) :: Gravity_C ! < Gravitational constant (set by calling code)
227232 real (c_float), intent (in ) :: defWtrDens_C ! < Default value for water density (may be overridden by input file)
228233 real (c_float), intent (in ) :: defWtrDpth_C ! < Default value for water density (may be overridden by input file)
@@ -248,6 +253,7 @@ SUBROUTINE HydroDyn_C_Init( OutRootName_C,
248253 character (IntfStrLen) :: OutRootName ! < Root name to use for echo files and other
249254 character (kind= C_char, len= SeaSt_InputFileStringLength_C), pointer :: SeaSt_InputFileString ! < Input file as a single string with NULL chracter separating lines
250255 character (kind= C_char, len= HD_InputFileStringLength_C), pointer :: HD_InputFileString ! < Input file as a single string with NULL chracter separating lines
256+ character (IntfStrLen) :: TmpFileName ! < Temporary file name if not passing HD or SS input file contents directly
251257
252258 real (DbKi) :: TimeInterval ! < timestep for HD
253259 integer (IntKi) :: ErrStat ! < aggregated error message
@@ -327,8 +333,21 @@ SUBROUTINE HydroDyn_C_Init( OutRootName_C,
327333 ! Get fortran pointer to C_NULL_CHAR deliniated input file as a string
328334 call C_F_pointer(SeaSt_InputFileString_C, SeaSt_InputFileString)
329335
330- ! Get the data to pass to SeaSt%Init
331- call InitFileInfo(SeaSt_InputFileString, SeaSt% InitInp% PassedFileData, ErrStat2, ErrMsg2); if (Failed()) return
336+ ! Format SeaSt input file contents
337+ if (SeaSt_InputFilePassed== 1_c_int ) then
338+ ! Get the data to pass to SeaSt%Init
339+ SeaSt% InitInp% InputFile = " passed_SeaSt_file" ! dummy
340+ SeaSt% InitInp% UseInputFile = .FALSE. ! this probably should be passed in
341+ call InitFileInfo(SeaSt_InputFileString, SeaSt% InitInp% PassedFileData, ErrStat2, ErrMsg2); if (Failed()) return
342+ else
343+ i = min (IntfStrLen,SeaSt_InputFileStringLength_C)
344+ TmpFileName = ' '
345+ TmpFileName(1 :i) = SeaSt_InputFileString(1 :i)
346+ i = INDEX (TmpFileName,C_NULL_CHAR) - 1 ! if this has a c null character at the end...
347+ if ( i > 0 ) TmpFileName = TmpFileName(1 :I) ! remove it
348+ SeaSt% InitInp% InputFile = TmpFileName
349+ SeaSt% InitInp% UseInputFile = .TRUE.
350+ endif
332351
333352 ! For diagnostic purposes, the following can be used to display the contents
334353 ! of the InFileInfo data structure.
@@ -337,8 +356,7 @@ SUBROUTINE HydroDyn_C_Init( OutRootName_C,
337356
338357 ! Set other inputs for calling SeaState_Init
339358 SeaSt% InitInp% hasIce = .FALSE. ! Always keep at false unless interfacing to ice modules
340- SeaSt% InitInp% InputFile = " passed_SeaSt_file" ! dummy
341- SeaSt% InitInp% UseInputFile = .FALSE. ! this probably should be passed in
359+
342360 ! Linearization
343361 ! for now, set linearization to false. Pass this in later when interface supports it
344362 ! Note: we may want to linearize at T=0 for added mass effects, but that might be
@@ -384,17 +402,28 @@ SUBROUTINE HydroDyn_C_Init( OutRootName_C,
384402 ! Get fortran pointer to C_NULL_CHAR deliniated input file as a string
385403 call C_F_pointer(HD_InputFileString_C, HD_InputFileString)
386404
387- ! Get the data to pass to HD%Init
388- call InitFileInfo(HD_InputFileString, HD% InitInp% PassedFileData, ErrStat2, ErrMsg2); if (Failed()) return
405+ ! Format HD input file contents
406+ if (HD_InputFilePassed== 1_c_int ) then
407+ ! Get the data to pass to HD%InitInp
408+ HD% InitInp% InputFile = " passed_hd_file" ! dummy
409+ HD% InitInp% UseInputFile = .FALSE. ! this probably should be passed in
410+ call InitFileInfo(HD_InputFileString, HD% InitInp% PassedFileData, ErrStat2, ErrMsg2); if (Failed()) return
411+ else
412+ i = min (IntfStrLen, HD_InputFileStringLength_C)
413+ TmpFileName = ' '
414+ TmpFileName(1 :i) = HD_InputFileString(1 :i)
415+ i = INDEX (TmpFileName,C_NULL_CHAR) - 1 ! if this has a c null character at the end...
416+ if ( i > 0 ) TmpFileName = TmpFileName(1 :I) ! remove it
417+ HD% InitInp% InputFile = TmpFileName
418+ HD% InitInp% UseInputFile = .TRUE.
419+ endif
389420
390421 ! For diagnostic purposes, the following can be used to display the contents
391422 ! of the InFileInfo data structure.
392423 ! CU is the screen -- system dependent.
393424 ! call Print_FileInfo_Struct( CU, HD%InitInp%PassedFileData )
394425
395426 ! Set other inputs for calling HydroDyn_Init
396- HD% InitInp% InputFile = " passed_hd_file" ! dummy
397- HD% InitInp% UseInputFile = .FALSE. ! this probably should be passed in
398427 ! Linearization
399428 ! for now, set linearization to false. Pass this in later when interface supports it
400429 ! Note: we may want to linearize at T=0 for added mass effects, but that might be
0 commit comments