pic_knowledge.f90 Source File

the gathered knowledge of the species


This file depends on

sourcefile~~pic_knowledge.f90~~EfferentGraph sourcefile~pic_knowledge.f90 pic_knowledge.f90 sourcefile~pic_logger.f90 pic_logger.f90 sourcefile~pic_knowledge.f90->sourcefile~pic_logger.f90 sourcefile~pic_string_type.f90 pic_string_type.F90 sourcefile~pic_knowledge.f90->sourcefile~pic_string_type.f90 sourcefile~pic_types.f90 pic_types.F90 sourcefile~pic_knowledge.f90->sourcefile~pic_types.f90 sourcefile~pic_logger.f90->sourcefile~pic_types.f90 sourcefile~pic_global_definitions.f90 pic_global_definitions.f90 sourcefile~pic_logger.f90->sourcefile~pic_global_definitions.f90 sourcefile~pic_string_type.f90->sourcefile~pic_types.f90 sourcefile~pic_ascii.f90 pic_ascii.f90 sourcefile~pic_string_type.f90->sourcefile~pic_ascii.f90 sourcefile~pic_optional.f90 pic_optional.f90 sourcefile~pic_string_type.f90->sourcefile~pic_optional.f90 sourcefile~pic_ascii.f90->sourcefile~pic_types.f90 sourcefile~pic_global_definitions.f90->sourcefile~pic_types.f90 sourcefile~pic_optional.f90->sourcefile~pic_types.f90

Source Code

! SPDX-License-Identifier: MIT
! Copyright (c) 2025 Jorge Luis Galvez Vallejo
!! the gathered knowledge of the species
module pic_knowledge
  !! a simple module that collects phrases and prints them out randomly, like fortune
   use pic_types, only: int32, dp
   use pic_logger, only: logger => global_logger
   use pic_string_type, only: string_type, assignment(=), char
   implicit none

   private

   public :: get_knowledge

contains

   subroutine get_knowledge()
    !! I print random knowledge
      type(string_type), allocatable :: knowledge(:)
      integer(int32) :: n, idx
      real(dp) :: r
      allocate (knowledge(11))

      knowledge(1) = "The long line! (CS,2023)"
      knowledge(2) = "Maybe I have the Fortran brain-rot in Dijkstra's words (IP,2025)"
      knowledge(3) = "Mojo, yes, do I approve it, no. (IP, 2025)"
      knowledge(4) = "No, rice does not contain gluten (EG, dawn of time)"
      knowledge(5) = "Yes, potatoes are gluten free (EG, dawn of time)"
      knowledge(6) = "Stonks (MS, 2019)"
      knowledge(7) = "Praise the machine god"
      knowledge(8) = "Maybe I WILL use a more efficient language: Fortran (Jorge, to CS)"
      knowledge(9) = "No one owns Makefiles!"
      knowledge(10) = "Why did you choose CMake over any other build system? Jorge: Stockholm Syndrome?"
      knowledge(11) = "That is exactly what Bjarne Sostrup intended when he created C++ - in response to RS doing an abomination in C++, by CS"

      n = size(knowledge)

      call random_number(r)
      idx = int(r*n) + 1
      if (idx > n) idx = n

      call logger%knowledge(trim(char(knowledge(idx))))

   end subroutine get_knowledge

end module pic_knowledge