26
26
! Open64 ? ? -module -I -mp discontinued
27
27
! Unisys ? ? ? ? ? discontinued
28
28
module fpm_compiler
29
- use fpm_model, only: fpm_model_t
30
- use fpm_filesystem, only: join_path, basename, get_temp_filename
31
29
use fpm_environment, only: &
30
+ run, &
32
31
get_os_type, &
33
32
OS_LINUX, &
34
33
OS_MACOS, &
@@ -38,13 +37,17 @@ module fpm_compiler
38
37
OS_FREEBSD, &
39
38
OS_OPENBSD, &
40
39
OS_UNKNOWN
40
+ use fpm_filesystem, only: join_path, basename, get_temp_filename, delete_file, unix_path
41
+ use fpm_strings, only: string_cat, string_t
41
42
implicit none
42
43
public :: is_unknown_compiler
43
44
public :: get_module_flags
44
45
public :: get_default_compile_flags
45
46
public :: get_debug_compile_flags
46
47
public :: get_release_compile_flags
47
- public :: get_archiver
48
+
49
+ public :: compiler_t, archiver_t
50
+ public :: debug
48
51
49
52
enum, bind(C)
50
53
enumerator :: &
@@ -70,6 +73,52 @@ module fpm_compiler
70
73
end enum
71
74
integer , parameter :: compiler_enum = kind (id_unknown)
72
75
76
+
77
+ ! > Definition of compiler object
78
+ type :: compiler_t
79
+ ! > Path to the Fortran compiler
80
+ character (len= :), allocatable :: fc
81
+ ! > Path to the C compiler
82
+ character (len= :), allocatable :: cc
83
+ ! > Print all commands
84
+ logical :: echo = .true.
85
+ contains
86
+ ! > Compile a Fortran object
87
+ procedure :: compile_fortran
88
+ ! > Compile a C object
89
+ procedure :: compile_c
90
+ ! > Link executable
91
+ procedure :: link
92
+ end type compiler_t
93
+
94
+
95
+ ! > Definition of archiver object
96
+ type :: archiver_t
97
+ ! > Path to archiver
98
+ character (len= :), allocatable :: ar
99
+ ! > Use response files to pass arguments
100
+ logical :: use_response_file = .false.
101
+ ! > Print all command
102
+ logical :: echo = .true.
103
+ contains
104
+ ! > Create static archive
105
+ procedure :: make_archive
106
+ end type archiver_t
107
+
108
+
109
+ ! > Constructor for archiver
110
+ interface archiver_t
111
+ module procedure :: new_archiver
112
+ end interface archiver_t
113
+
114
+
115
+ ! > Create debug printout
116
+ interface debug
117
+ module procedure :: debug_compiler
118
+ module procedure :: debug_archiver
119
+ end interface debug
120
+
121
+
73
122
contains
74
123
75
124
subroutine get_default_compile_flags (compiler , release , flags )
@@ -460,29 +509,148 @@ function check_compiler(compiler, expected) result(match)
460
509
end if
461
510
end function check_compiler
462
511
512
+
463
513
function is_unknown_compiler (compiler ) result(is_unknown)
464
514
character (len=* ), intent (in ) :: compiler
465
515
logical :: is_unknown
466
516
is_unknown = get_compiler_id(compiler) == id_unknown
467
517
end function is_unknown_compiler
468
518
469
519
470
- function get_archiver () result(archiver)
471
- character (:), allocatable :: archiver
520
+ ! > Create new archiver
521
+ function new_archiver () result(self)
522
+ ! > New instance of the archiver
523
+ type (archiver_t) :: self
472
524
integer :: estat, os_type
473
525
474
526
os_type = get_os_type()
475
527
if (os_type /= OS_WINDOWS .and. os_type /= OS_UNKNOWN) then
476
- archiver = " ar -rs "
528
+ self % ar = " ar -rs "
477
529
else
478
530
call execute_command_line(" ar --version > " // get_temp_filename()// " 2>&1" , &
479
531
& exitstat= estat)
480
532
if (estat /= 0 ) then
481
- archiver = " lib /OUT:"
533
+ self % ar = " lib /OUT:"
482
534
else
483
- archiver = " ar -rs "
535
+ self % ar = " ar -rs "
484
536
end if
485
537
end if
486
- end function
538
+ self% use_response_file = os_type == OS_WINDOWS
539
+ self% echo = .true.
540
+ end function new_archiver
541
+
542
+
543
+ ! > Compile a Fortran object
544
+ subroutine compile_fortran (self , input , output , args , stat )
545
+ ! > Instance of the compiler object
546
+ class(compiler_t), intent (in ) :: self
547
+ ! > Source file input
548
+ character (len=* ), intent (in ) :: input
549
+ ! > Output file of object
550
+ character (len=* ), intent (in ) :: output
551
+ ! > Arguments for compiler
552
+ character (len=* ), intent (in ) :: args
553
+ ! > Status flag
554
+ integer , intent (out ) :: stat
555
+
556
+ call run(self% fc // " -c " // input // " " // args // " -o " // output, &
557
+ & echo= self% echo, exitstat= stat)
558
+ end subroutine compile_fortran
559
+
560
+
561
+ ! > Compile a C object
562
+ subroutine compile_c (self , input , output , args , stat )
563
+ ! > Instance of the compiler object
564
+ class(compiler_t), intent (in ) :: self
565
+ ! > Source file input
566
+ character (len=* ), intent (in ) :: input
567
+ ! > Output file of object
568
+ character (len=* ), intent (in ) :: output
569
+ ! > Arguments for compiler
570
+ character (len=* ), intent (in ) :: args
571
+ ! > Status flag
572
+ integer , intent (out ) :: stat
573
+
574
+ call run(self% cc // " -c " // input // " " // args // " -o " // output, &
575
+ & echo= self% echo, exitstat= stat)
576
+ end subroutine compile_c
577
+
578
+
579
+ ! > Link an executable
580
+ subroutine link (self , output , args , stat )
581
+ ! > Instance of the compiler object
582
+ class(compiler_t), intent (in ) :: self
583
+ ! > Output file of object
584
+ character (len=* ), intent (in ) :: output
585
+ ! > Arguments for compiler
586
+ character (len=* ), intent (in ) :: args
587
+ ! > Status flag
588
+ integer , intent (out ) :: stat
589
+
590
+ call run(self% fc // " " // args // " -o " // output, echo= self% echo, exitstat= stat)
591
+ end subroutine link
592
+
593
+
594
+ ! > Create an archive
595
+ subroutine make_archive (self , output , args , stat )
596
+ ! > Instance of the archiver object
597
+ class(archiver_t), intent (in ) :: self
598
+ ! > Name of the archive to generate
599
+ character (len=* ), intent (in ) :: output
600
+ ! > Object files to include into the archive
601
+ type (string_t), intent (in ) :: args(:)
602
+ ! > Status flag
603
+ integer , intent (out ) :: stat
604
+
605
+ if (self% use_response_file) then
606
+ call write_response_file(output// " .resp" , args)
607
+ call run(self% ar // output // " @" // output// " .resp" , echo= self% echo, exitstat= stat)
608
+ call delete_file(output// " .resp" )
609
+ else
610
+ call run(self% ar // output // " " // string_cat(args, " " ), &
611
+ & echo= self% echo, exitstat= stat)
612
+ end if
613
+ end subroutine make_archive
614
+
615
+
616
+ ! > Response files allow to read command line options from files.
617
+ ! > Whitespace is used to separate the arguments, we will use newlines
618
+ ! > as separator to create readable response files which can be inspected
619
+ ! > in case of errors.
620
+ subroutine write_response_file (name , argv )
621
+ character (len=* ), intent (in ) :: name
622
+ type (string_t), intent (in ) :: argv(:)
623
+
624
+ integer :: iarg, io
625
+
626
+ open (file= name, newunit= io)
627
+ do iarg = 1 , size (argv)
628
+ write (io, ' (a)' ) unix_path(argv(iarg)% s)
629
+ end do
630
+ close (io)
631
+ end subroutine write_response_file
632
+
633
+
634
+ ! > String representation of a compiler object
635
+ pure function debug_compiler (self ) result(repr)
636
+ ! > Instance of the compiler object
637
+ type (compiler_t), intent (in ) :: self
638
+ ! > Representation as string
639
+ character (len= :), allocatable :: repr
640
+
641
+ repr = ' fc="' // self% fc// ' ", cc="' // self% cc// ' "'
642
+ end function debug_compiler
643
+
644
+
645
+ ! > String representation of an archiver object
646
+ pure function debug_archiver (self ) result(repr)
647
+ ! > Instance of the archiver object
648
+ type (archiver_t), intent (in ) :: self
649
+ ! > Representation as string
650
+ character (len= :), allocatable :: repr
651
+
652
+ repr = ' ar="' // self% ar// ' "'
653
+ end function debug_archiver
654
+
487
655
488
656
end module fpm_compiler
0 commit comments