All global entities of a module, by default, can be accessed by a program or another module using the USE statement. But, it is possible to set some restrictions that some entities are private. A private entity of a module can only be accessed that module. On the other hand, one can explicitly list those entities that can be accessed from outside. This is done with the PUBLIC and PRIVATE statements:
PUBLIC :: name-1, name-2, ..., name-n PRIVATE :: name-1, name-2, ..., name-n
All entities listed in PRIVATE will not be accessible from outside of the module and all entities listed in PUBLIC can be accessed from outside of the module. All not listed entities, by default, can be accessed from outside of the module.
You can have many PRIVATE and PUBLIC statements.
In the following code segment, since VolumeOfDeathStar,
SecretConstant and BlackKnight are listed in
a  statement, they can only be used with the module.
On the other hand, SkyWalker and Princess are listed
in PUBLIC, they can be accessed from outside of the
module.  There are entities not listed:
function WeaponPower() and DeathStar.  By default,
they are public and can be accessed from outside of the module.
MODULE  TheForce
   IMPLICIT   NONE
   INTEGER :: SkyWalker, Princess
   REAL    :: BlackKnight
   LOGICAL :: DeathStar
   REAL, PARAMETER :: SecretConstant = 0.123456
   PUBLIC  :: SkyWalker, Princess
   PRIVATE :: VolumeOfDeathStar
   PRIVATE :: SecretConstant, BlackKnight
CONTAINS
   INTEGER FUNCTION  VolumeOfDeathStar()
      ..........
   END FUNCTION VolumeOfDeathStar
   REAL FUNCTION  WeaponPower(SomeWeapon)
      ..........
   END FUNCTION
      ..........
END MODULE  TheForce
 A Programming Example
In a previous example of
using degree in trigonometric functions,
four constants and four functions are defined.  But, most of them are
used in and meaningful to the module
MyTrigonometricFunctions.  Thus, one can make them private so that
they cannot be accessed from outside of this module.  Here is a rewritten
version:
Click here to download this module.
You also need a main program to test it.  This mean program is identical to
the one used in a previous example.  If you need it, click
here to download a copy.
! --------------------------------------------------------------------
! MODULE  MyTrigonometricFunctions:
!    This module provides the following functions and constants
!    (1) RadianToDegree()     - converts its argument in radian to
!                               degree
!    (2) DegreeToRadian()     - converts its argument in degree to
!                               radian
!    (3) MySIN()              - compute the sine of its argument in
!                               degree
!    (4) MyCOS()              - compute the cosine of its argument
!                               in degree
! --------------------------------------------------------------------
MODULE  MyTrigonometricFunctions
   IMPLICIT   NONE
   REAL, PARAMETER :: PI        = 3.1415926       ! some constants
   REAL, PARAMETER :: Degree180 = 180.0
   REAL, PARAMETER :: R_to_D    = Degree180/PI
   REAL, PARAMETER :: D_to_R    = PI/Degree180
   PRIVATE         :: Degree180, R_to_D, D_to_R
   PRIVATE         :: RadianToDegree, DegreeToRadian
   PUBLIC          :: MySIN, MyCOS
CONTAINS
! --------------------------------------------------------------------
! FUNCTION  RadianToDegree():
!    This function takes a REAL argument in radian and converts it to
! the equivalent degree.
! --------------------------------------------------------------------
   REAL FUNCTION  RadianToDegree(Radian)
      IMPLICIT  NONE
      REAL, INTENT(IN) :: Radian
      RadianToDegree = Radian * R_to_D
   END FUNCTION  RadianToDegree
! --------------------------------------------------------------------
! FUNCTION  DegreeToRadian():
!    This function takes a REAL argument in degree and converts it to
! the equivalent radian.
! --------------------------------------------------------------------
   REAL FUNCTION  DegreeToRadian(Degree)
      IMPLICIT  NONE
      REAL, INTENT(IN) :: Degree
      DegreeToRadian = Degree * D_to_R
   END FUNCTION  DegreeToRadian
! --------------------------------------------------------------------
! FUNCTION  MySIN():
!    This function takes a REAL argument in degree and computes its
! sine value.  It does the computation by converting its argument to
! radian and uses Fortran's sin().
! --------------------------------------------------------------------
   REAL FUNCTION  MySIN(x)
      IMPLICIT  NONE
      REAL, INTENT(IN) :: x
      MySIN = SIN(DegreeToRadian(x))
   END FUNCTION  MySIN
! --------------------------------------------------------------------
! FUNCTION  MySIN():
!    This function takes a REAL argument in degree and computes its
! cosine value.  It does the computation by converting its argument to
! radian and uses Fortran's cos().
! --------------------------------------------------------------------
   REAL FUNCTION  MyCOS(x)
      IMPLICIT  NONE
      REAL, INTENT(IN) :: x
      MyCOS = COS(DegreeToRadian(x))
   END FUNCTION  MyCOS
END MODULE  MyTrigonometricFunctions
In this module, there are four PARAMETERs. Of these four, only PI is not listed as PRIVATE and hence can be accessed from outside of this module. There are four internal functions, MySIN(), MyCOS(), RadianToDegree() and DegreeToRadian(). The former two are listed as PUBLIC and can be accessed from outside of this module. The latter two are listed as PRIVATE and therefore cannot be accessed from outside of this module.
Note that if PI is also made PRIVATE, then the main program will have a mistake since it displays the value of PI:
PROGRAM  TrigonFunctTest
   USE  MyTrigonometricFunctions
   IMPLICIT  NONE
      ..........
   WRITE(*,*)  'Value of PI = ', PI   ! PI cannot be used here
      ..........
END PROGRAM  TrigonFunctTest