Skip to content

Commit

Permalink
SeaState: tidy up SeaState_output routine (remove unused errorstat ch…
Browse files Browse the repository at this point in the history
…eck)

Fix indentation so I can make sense of it
  • Loading branch information
andrew-platt committed Mar 9, 2022
1 parent 77df958 commit 4de7ac4
Show file tree
Hide file tree
Showing 2 changed files with 45 additions and 45 deletions.
2 changes: 1 addition & 1 deletion modules/hydrodyn/src/HydroDyn_Output.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1163,7 +1163,7 @@ SUBROUTINE HDOUT_Init( HydroDyn_ProgDesc, OutRootName, InputFileData, y, p, m,


CALL HDOUT_ChkOutLst( InputFileData%OutList(1:p%NumOuts), y, p, ErrStat, ErrMsg )
IF ( ErrStat /= 0 ) RETURN
IF ( ErrStat >= ErrID_Fatal ) RETURN

! Aggregate the sub-module initialization outputs for the glue code

Expand Down
88 changes: 44 additions & 44 deletions modules/seastate/src/SeaState_Output.f90
Original file line number Diff line number Diff line change
Expand Up @@ -745,57 +745,57 @@ SUBROUTINE SeaStOut_Init( SeaSt_ProgDesc, OutRootName, InputFileData, y, p, m,


CALL SeaStOUT_ChkOutLst( InputFileData%OutList(1:p%NumOuts), y, p, ErrStat, ErrMsg )
IF ( ErrStat /= 0 ) RETURN
IF ( ErrStat >= ErrID_Fatal ) RETURN

! Aggregate the sub-module initialization outputs for the glue code
! Aggregate the sub-module initialization outputs for the glue code

p%NumTotalOuts = p%NumOuts
m%LastOutTime = 0.0_DbKi
m%Decimate = 0
p%OutDec = 1 !TODO: Remove this once the parameter has been added to the HD input file GJH 7/8/2014
p%NumTotalOuts = p%NumOuts
m%LastOutTime = 0.0_DbKi
m%Decimate = 0
p%OutDec = 1 !TODO: Remove this once the parameter has been added to the HD input file GJH 7/8/2014


! Allocate the aggregate arrays

ALLOCATE ( InitOut%WriteOutputHdr ( p%NumTotalOuts ) , STAT=ErrStat )
IF ( ErrStat /= 0 ) THEN
ErrMsg = ' Error allocating memory for the WriteOutputHdr array.'
ErrStat = ErrID_Fatal
RETURN
END IF

ALLOCATE ( InitOut%WriteOutputUnt ( p%NumTotalOuts ) , STAT=ErrStat )
IF ( ErrStat /= 0 ) THEN
ErrMsg = ' Error allocating memory for the WriteOutputUnt array.'
ErrStat = ErrID_Fatal
RETURN
END IF

ALLOCATE ( y%WriteOutput ( p%NumTotalOuts ) , STAT=ErrStat )
IF ( ErrStat /= 0 ) THEN
ErrMsg = ' Error allocating memory for the WriteOutput array.'
ErrStat = ErrID_Fatal
RETURN
END IF
y%WriteOutput = 0.0_ReKi ! bjj added this only so the Intel Inspector wouldn't complain about uninitialized memory access (was harmless)


! Initialize the HD-level Hdr and Unt elements
DO I = 1,p%NumOuts

InitOut%WriteOutputHdr(I) = TRIM( p%OutParam(I)%Name )
InitOut%WriteOutputUnt(I) = TRIM( p%OutParam(I)%Units )

END DO

! Allocate the aggregate arrays

ALLOCATE ( InitOut%WriteOutputHdr ( p%NumTotalOuts ) , STAT=ErrStat )
IF ( ErrStat /= 0 ) THEN
ErrMsg = ' Error allocating memory for the WriteOutputHdr array.'
ErrStat = ErrID_Fatal
RETURN
END IF

ALLOCATE ( InitOut%WriteOutputUnt ( p%NumTotalOuts ) , STAT=ErrStat )
IF ( ErrStat /= 0 ) THEN
ErrMsg = ' Error allocating memory for the WriteOutputUnt array.'
ErrStat = ErrID_Fatal
RETURN
END IF

ALLOCATE ( y%WriteOutput ( p%NumTotalOuts ) , STAT=ErrStat )
IF ( ErrStat /= 0 ) THEN
ErrMsg = ' Error allocating memory for the WriteOutput array.'
ErrStat = ErrID_Fatal
RETURN
END IF
y%WriteOutput = 0.0_ReKi ! bjj added this only so the Intel Inspector wouldn't complain about uninitialized memory access (was harmless)


! Initialize the HD-level Hdr and Unt elements
DO I = 1,p%NumOuts

InitOut%WriteOutputHdr(I) = TRIM( p%OutParam(I)%Name )
InitOut%WriteOutputUnt(I) = TRIM( p%OutParam(I)%Units )

END DO


J = p%NumOuts + 1
J = p%NumOuts + 1


IF ( p%OutSwtch == 1 .OR. p%OutSwtch == 3 ) THEN
CALL SeaStOut_OpenOutput( SeaSt_ProgDesc, OutRootName, p, InitOut, ErrStat, ErrMsg )
IF (ErrStat >= AbortErrLev ) RETURN
END IF
IF ( p%OutSwtch == 1 .OR. p%OutSwtch == 3 ) THEN
CALL SeaStOut_OpenOutput( SeaSt_ProgDesc, OutRootName, p, InitOut, ErrStat, ErrMsg )
IF (ErrStat >= AbortErrLev ) RETURN
END IF



Expand Down

0 comments on commit 4de7ac4

Please sign in to comment.