Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 1 addition & 1 deletion bootstrap/src/Build.hs
Original file line number Diff line number Diff line change
Expand Up @@ -259,7 +259,7 @@ createSourceToObjectMap buildDirectory libraryDirectory sourceFile =

sourceFileToObjectFile :: FilePath -> FilePath -> FilePath -> FilePath
sourceFileToObjectFile buildDirectory libraryDirectory sourceFile =
buildDirectory
(foldl (</>) "" $ splitDirectories buildDirectory)
</> map
toLower
(pathSeparatorsToUnderscores
Expand Down
1 change: 1 addition & 0 deletions fpm/.gitignore
Original file line number Diff line number Diff line change
@@ -1 +1,2 @@
build/*
*/FODDER/*
8 changes: 4 additions & 4 deletions fpm/app/main.f90
Original file line number Diff line number Diff line change
Expand Up @@ -17,15 +17,15 @@ program main

select type(settings=>cmd_settings)
type is (fpm_new_settings)
call cmd_new()
call cmd_new(settings)
type is (fpm_build_settings)
call cmd_build(settings)
type is (fpm_run_settings)
call cmd_run()
call cmd_run(settings)
type is (fpm_test_settings)
call cmd_test()
call cmd_test(settings)
type is (fpm_install_settings)
call cmd_install()
call cmd_install(settings)
end select

end program main
13 changes: 12 additions & 1 deletion fpm/fpm.toml
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,18 @@ copyright = "2020 fpm contributors"
git = "https://github.com/toml-f/toml-f"
tag = "v0.2"

[dependencies.M_CLI2]
git = "https://github.com/urbanjost/M_CLI2.git"
rev = "5c7df1267c918ec2b1b8e2c6a0ac000367b562cf"

[[test]]
name = "cli-test"
source-dir = "test/cli_test"
main = "cli_test.f90"

[[test]]
name = "fpm-test"
source-dir = "test"
source-dir = "test/fpm_test"
main = "main.f90"


120 changes: 102 additions & 18 deletions fpm/src/fpm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -2,15 +2,19 @@ module fpm

use fpm_strings, only: string_t, str_ends_with
use fpm_backend, only: build_package
use fpm_command_line, only: fpm_build_settings
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
fpm_run_settings, fpm_install_settings, fpm_test_settings
use fpm_environment, only: run, get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
use fpm_filesystem, only: join_path, number_of_rows, list_files, exists
use fpm_filesystem, only: join_path, number_of_rows, list_files, exists, basename
use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t
use fpm_sources, only: add_executable_sources, add_sources_from_dir, &
resolve_module_dependencies
use fpm_manifest, only : get_package_data, default_executable, &
default_library, package_t
use fpm_error, only : error_t
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
& stdout=>output_unit, &
& stderr=>error_unit
implicit none
private
public :: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test
Expand All @@ -30,18 +34,31 @@ subroutine build_model(model, settings, package, error)

! #TODO: Choose flags and output directory based on cli settings & manifest inputs
model%fortran_compiler = 'gfortran'
model%output_directory = 'build/gfortran_debug'
model%fortran_compile_flags = ' -Wall -Wextra -Wimplicit-interface -fPIC -fmax-errors=1 -g '// &
'-fbounds-check -fcheck-array-temporaries -fbacktrace '// &
'-J'//join_path(model%output_directory,model%package_name)

if(settings%release)then
model%output_directory = 'build/gfortran_release'
model%fortran_compile_flags=' &
& -O3 &
& -Wimplicit-interface &
& -fPIC &
& -fmax-errors=1 &
& -ffast-math &
& -funroll-loops ' // &
& '-J'//join_path(model%output_directory,model%package_name)
else
model%output_directory = 'build/gfortran_debug'
model%fortran_compile_flags = ' -Wall -Wextra -Wimplicit-interface -fPIC -fmax-errors=1 -g '// &
'-fbounds-check -fcheck-array-temporaries -fbacktrace '// &
'-J'//join_path(model%output_directory,model%package_name)
endif
model%link_flags = ''

! Add sources from executable directories
if (allocated(package%executable)) then

call add_executable_sources(model%sources, package%executable, &
is_test=.false., error=error)

if (allocated(error)) then
return
end if
Expand Down Expand Up @@ -111,24 +128,91 @@ subroutine cmd_build(settings)

end subroutine

subroutine cmd_install()
subroutine cmd_install(settings)
type(fpm_install_settings), intent(in) :: settings
print *, "fpm error: 'fpm install' not implemented."
error stop 1
end subroutine

subroutine cmd_new()
print *, "fpm error: 'fpm new' not implemented."
error stop 1
end subroutine
end subroutine cmd_install

subroutine cmd_new(settings) ! --with-executable F --with-test F '
type(fpm_new_settings), intent(in) :: settings
character(len=:),allocatable :: message(:)
character(len=:),allocatable :: bname
bname=basename(settings%name) !! new basename(dirname) if full paths are allowed ???

message=[character(len=80) :: & ! create fpm.toml
&'name = "'//bname//'" ', &
&'version = "0.1.0" ', &
&'license = "license" ', &
&'author = "Jane Doe" ', &
&'maintainer = "jane.doe@example.com" ', &
&'copyright = "2020 Jane Doe" ', &
&' ', &
&'[library] ', &
&'source-dir="src" ', &
&'']

if(settings%with_test)then
message=[character(len=80) :: message, & ! create next section of fpm.toml
&'[[test]] ', &
&'name="runTests" ', &
&'source-dir="test" ', &
&'main="main.f90" ', &
&'']
endif

if(settings%with_executable)then
message=[character(len=80) :: message, & ! create next section of fpm.toml
&'[[executable]] ', &
&'name="'//bname//'" ', &
&'source-dir="app" ', &
&'main="main.f90" ', &
&'']
endif

write(*,'(a)')message
print *, "fpm error: 'fpm new' not implemented."
error stop 1
end subroutine cmd_new

subroutine cmd_run(settings)
type(fpm_run_settings), intent(in) :: settings
integer :: i

write(*,*)'RELEASE=',settings%release
if(size(settings%name).eq.0)then
write(*,*)'RUN DEFAULTS with arguments ['//settings%args//']'
else
do i=1,size(settings%name)
write(*,*)'RUN:'//trim(settings%name(i))//' with arguments ['//settings%args//']'
enddo
endif

subroutine cmd_run()
print *, "fpm error: 'fpm run' not implemented."
error stop 1
end subroutine

subroutine cmd_test()
end subroutine cmd_run

subroutine cmd_test(settings)
type(fpm_test_settings), intent(in) :: settings
character(len=:),allocatable :: release_name
integer :: i

!! looks like would get this from model when cmd_test is implimented
release_name=trim(merge('gfortran_release','gfortran_debug ',settings%release))

write(*,*)'RELEASE=',settings%release,' RELEASE_NAME=',release_name,' ARGS=',settings%args
if( size(settings%name) .gt.0 )then
write(*,*)'RUN THESE:'
do i=1,size(settings%name)
write(*,*)'RUN:'//trim(settings%name(i))//' with arguments ['//settings%args//']'
enddo
else
write(*,*)'RUN DEFAULTS: with arguments ['//settings%args//']'
endif

print *, "fpm error: 'fpm test' not implemented."
error stop 1
end subroutine
end subroutine cmd_test

end module fpm
Loading