aboutsummaryrefslogtreecommitdiff
path: root/favorites.f90
diff options
context:
space:
mode:
Diffstat (limited to 'favorites.f90')
-rw-r--r--favorites.f9018
1 files changed, 13 insertions, 5 deletions
diff --git a/favorites.f90 b/favorites.f90
index a1e0a6b..90cd2d1 100644
--- a/favorites.f90
+++ b/favorites.f90
@@ -60,9 +60,9 @@ contains
res = 1
do i = 2, size(array)
- if(mymin .and. string_compare(array(res), array(i)) < 0) then
+ if(mymin .and. string_compare(array(res), array(i)) > 0) then
res = i
- else if((.not. mymin) .and. string_compare(array(res), array(i)) > 0) then
+ else if((.not. mymin) .and. string_compare(array(res), array(i)) < 0) then
res = i
end if
end do
@@ -230,17 +230,25 @@ contains
end subroutine write_favorite
- subroutine write_favorites(unit_number, faves)
+ subroutine write_favorites(unit_number, faves, skip_heading)
implicit none
integer, intent(in)::unit_number
type(favorite), dimension(:), intent(in)::faves
+ logical, intent(in), optional::skip_heading
integer::i
character(8)::n_text
- write(unit_number, '(A11)') "# Favorites"
- write(unit_number, *)
+ if(present(skip_heading)) then
+ if(.not. skip_heading) then
+ write(unit_number, '(A11)') "# Favorites"
+ write(unit_number, *)
+ end if
+ else
+ write(unit_number, '(A11)') "# Favorites"
+ write(unit_number, *)
+ end if
write(n_text, '(I8)') size(faves)