Introduced properties

fun add_job(repo_slug: String): LoaderJob

github :: Loader :: add_job

Add a new job
protected fun branches=(branches: BranchRepo)

github :: Loader :: branches=

fun check_error(api: GithubAPI, message: nullable String)

github :: Loader :: check_error

Check if the API is in error state then abort
protected fun commits=(commits: CommitRepo)

github :: Loader :: commits=

protected fun config=(config: LoaderConfig)

github :: Loader :: config=

fun error(msg: String)

github :: Loader :: error

Display a error and exit
fun finish_job(job: LoaderJob)

github :: Loader :: finish_job

Finish a job
fun get_commit(job: LoaderJob, commit_sha: String)

github :: Loader :: get_commit

fun get_commits(job: LoaderJob, branch: Branch)

github :: Loader :: get_commits

fun get_issues(job: LoaderJob)

github :: Loader :: get_issues

Load game for repo_name.
protected fun issue_comments=(issue_comments: IssueCommentRepo)

github :: Loader :: issue_comments=

protected fun issue_events=(issue_events: IssueEventRepo)

github :: Loader :: issue_events=

protected fun issues=(issues: IssueRepo)

github :: Loader :: issues=

fun jobs: LoaderJobRepo

github :: Loader :: jobs

Jobs repository
protected fun jobs=(jobs: LoaderJobRepo)

github :: Loader :: jobs=

Jobs repository
fun log: PopLogger

github :: Loader :: log

Logger shortcut
protected fun pulls=(pulls: PullRequestRepo)

github :: Loader :: pulls=

fun remove(repo_slug: String)

github :: Loader :: remove

protected fun repos=(repos: RepoRepo)

github :: Loader :: repos=

fun show_jobs

github :: Loader :: show_jobs

Show jobs status
fun show_wallet

github :: Loader :: show_wallet

Show wallet status
fun start(repo_slug: String)

github :: Loader :: start

Redefined properties

redef type SELF: Loader

github $ Loader :: SELF

Type of this instance, automatically specialized in every class

All properties

fun !=(other: nullable Object): Bool

core :: Object :: !=

Have self and other different values?
fun ==(other: nullable Object): Bool

core :: Object :: ==

Have self and other the same value?
type CLASS: Class[SELF]

core :: Object :: CLASS

The type of the class of self.
type SELF: Object

core :: Object :: SELF

Type of this instance, automatically specialized in every class
fun add_job(repo_slug: String): LoaderJob

github :: Loader :: add_job

Add a new job
protected fun branches=(branches: BranchRepo)

github :: Loader :: branches=

fun check_error(api: GithubAPI, message: nullable String)

github :: Loader :: check_error

Check if the API is in error state then abort
protected fun class_factory(name: String): CLASS

core :: Object :: class_factory

Implementation used by get_class to create the specific class.
fun class_name: String

core :: Object :: class_name

The class name of the object.
protected fun commits=(commits: CommitRepo)

github :: Loader :: commits=

protected fun config=(config: LoaderConfig)

github :: Loader :: config=

fun error(msg: String)

github :: Loader :: error

Display a error and exit
fun finish_job(job: LoaderJob)

github :: Loader :: finish_job

Finish a job
fun get_class: CLASS

core :: Object :: get_class

The meta-object representing the dynamic type of self.
fun get_commit(job: LoaderJob, commit_sha: String)

github :: Loader :: get_commit

fun get_commits(job: LoaderJob, branch: Branch)

github :: Loader :: get_commits

fun get_issues(job: LoaderJob)

github :: Loader :: get_issues

Load game for repo_name.
fun hash: Int

core :: Object :: hash

The hash code of the object.
init init

core :: Object :: init

fun inspect: String

core :: Object :: inspect

Developer readable representation of self.
protected fun inspect_head: String

core :: Object :: inspect_head

Return "CLASSNAME:#OBJECTID".
intern fun is_same_instance(other: nullable Object): Bool

core :: Object :: is_same_instance

Return true if self and other are the same instance (i.e. same identity).
fun is_same_serialized(other: nullable Object): Bool

core :: Object :: is_same_serialized

Is self the same as other in a serialization context?
intern fun is_same_type(other: Object): Bool

core :: Object :: is_same_type

Return true if self and other have the same dynamic type.
protected fun issue_comments=(issue_comments: IssueCommentRepo)

github :: Loader :: issue_comments=

protected fun issue_events=(issue_events: IssueEventRepo)

github :: Loader :: issue_events=

protected fun issues=(issues: IssueRepo)

github :: Loader :: issues=

fun jobs: LoaderJobRepo

github :: Loader :: jobs

Jobs repository
protected fun jobs=(jobs: LoaderJobRepo)

github :: Loader :: jobs=

Jobs repository
fun log: PopLogger

github :: Loader :: log

Logger shortcut
intern fun object_id: Int

core :: Object :: object_id

An internal hash code for the object based on its identity.
fun output

core :: Object :: output

Display self on stdout (debug only).
intern fun output_class_name

core :: Object :: output_class_name

Display class name on stdout (debug only).
protected fun pulls=(pulls: PullRequestRepo)

github :: Loader :: pulls=

fun remove(repo_slug: String)

github :: Loader :: remove

protected fun repos=(repos: RepoRepo)

github :: Loader :: repos=

fun serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
fun show_jobs

github :: Loader :: show_jobs

Show jobs status
fun show_wallet

github :: Loader :: show_wallet

Show wallet status
fun start(repo_slug: String)

github :: Loader :: start

intern fun sys: Sys

core :: Object :: sys

Return the global sys object, the only instance of the Sys class.
abstract fun to_jvalue(env: JniEnv): JValue

core :: Object :: to_jvalue

fun to_s: String

core :: Object :: to_s

User readable representation of self.
package_diagram github::Loader Loader core::Object Object github::Loader->core::Object

Parents

interface Object

core :: Object

The root of the class hierarchy.

Class definitions

github $ Loader
class Loader

	var config = new LoaderConfig

	# Jobs repository
	var jobs: LoaderJobRepo is lazy do
		return new LoaderJobRepo(config.db.collection("loader_status"))
	end

	var repos: RepoRepo is lazy do
		return new RepoRepo(config.db.collection("repos"))
	end

	var branches: BranchRepo is lazy do
		return new BranchRepo(config.db.collection("branches"))
	end

	var commits: CommitRepo is lazy do
		return new CommitRepo(config.db.collection("commits"))
	end

	var issues: IssueRepo is lazy do
		return new IssueRepo(config.db.collection("issues"))
	end

	var pulls: PullRequestRepo is lazy do
		return new PullRequestRepo(config.db.collection("pull_requests"))
	end

	var issue_comments: IssueCommentRepo is lazy do
		return new IssueCommentRepo(config.db.collection("issue_comments"))
	end

	var issue_events: IssueEventRepo is lazy do
		return new IssueEventRepo(config.db.collection("issue_events"))
	end

	fun start(repo_slug: String) do
		var job = jobs.find_by_id(repo_slug)
		if job == null then
			log.info "Creating new job for `{repo_slug}`"
			job = add_job(repo_slug)
		else
			log.info "Resuming pending job for `{repo_slug}`"
		end
		print "Load history for {job}..."
		get_branches(job)
		get_issues(job)
		finish_job(job)
	end

	fun remove(repo_slug: String) do
		var job = jobs.find_by_id(repo_slug)
		if job == null then
			log.info "No job found for `{repo_slug}`"
		else
			jobs.remove_by_id(repo_slug)
			log.info "Deleted job for `{repo_slug}`"
		end
	end

	# Show wallet status
	fun show_wallet do config.wallet.show_status(config.no_colors)

	# Show jobs status
	fun show_jobs do
		var jobs = jobs.find_all
		print "{jobs.length} jobs pending..."
		for job in jobs do
			print " * {job}"
		end
		print "\nUse `loader <job> to start a new or resume a pending one"
	end

	# Add a new job
	fun add_job(repo_slug: String): LoaderJob do
		var repo = config.wallet.api.get_repo(repo_slug)
		assert repo != null else
			error "Repository `{repo_slug}` not found"
		end
		repos.save repo
		var job = new LoaderJob(repo, config.start_from_issue)
		jobs.save job
		return job
	end

	# Finish a job
	fun finish_job(job: LoaderJob) do
		print "Finished job {job}"
		jobs.remove_by_id(job.id)
	end

	fun get_branches(job: LoaderJob) do
		if config.no_branches then return

		var api = config.wallet.api
		var repo = job.repo
		for branch in api.get_repo_branches(repo.full_name) do
			branch.repo = repo
			branches.save branch
			get_commits(job, branch)
		end
	end

	fun get_commits(job: LoaderJob, branch: Branch) do
		if config.no_commits then return
		get_commit(job, branch.commit.sha)
	end

	fun get_commit(job: LoaderJob, commit_sha: String) do
		if commits.find_by_id(commit_sha) != null then return
		var api = config.wallet.api
		var commit = api.get_commit(job.repo.full_name, commit_sha)
		# print commit or else "NULL"
		if commit == null then return
		var message = commit.message or else "no message"
		log.info "Load commit {commit_sha}: {message.split("\n").first}"
		commit.repo = job.repo
		commits.save commit
		var parents = commit.parents
		if parents == null then return
		for parent in parents do
			get_commit(job, parent.sha)
		end
	end

	# Load game for `repo_name`.
	fun get_issues(job: LoaderJob) do
		if config.no_issues then return

		var api = config.wallet.api
		var page = 1
		var issues = api.get_repo_issues(job.repo.full_name, page, 100)
		while issues.not_empty do
			for issue in issues do
				get_issue(job, issue.number)
				job.last_issue = issue.number
				jobs.save job
			end
		end
	end

	# Load an issue or abort.
	private fun get_issue(job: LoaderJob, issue_number: Int) do
		if issues.find_by_id("{job.repo.mongo_id}/{issue_number}") != null then return

		var api = config.wallet.api
		var issue = api.get_issue(job.repo.full_name, issue_number)
		assert issue != null else
			check_error(api, "Issue #{issue_number} not found")
		end
		if issue.is_pull_request then
			get_pull(job, issue)
		else
			log.info "Load issue #{issue.number}: {issue.title.split("\n").first}"
			issue.repo = job.repo
			issues.save issue
			get_issue_events(job, issue)
		end
		get_issue_comments(job, issue)
	end

	# Load issue comments.
	private fun get_issue_comments(job: LoaderJob, issue: Issue) do
		if config.no_comments then return
		var api = config.wallet.api
		for comment in api.get_issue_comments(job.repo.full_name, issue.number) do
			comment.repo = job.repo
			issue_comments.save comment
		end
	end

	# Load issue events.
	private fun get_issue_events(job: LoaderJob, issue: Issue) do
		if config.no_events then return

		var api = config.wallet.api
		for event in api.get_issue_events(job.repo.full_name, issue.number) do
			event.repo = job.repo
			issue_events.save event
		end
	end

	# Load a pull request or abort.
	private fun get_pull(job: LoaderJob, issue: Issue): PullRequest do
		var api = config.wallet.api
		var pr = api.get_pull(job.repo.full_name, issue.number)
		assert pr != null else
			check_error(api, "Pull request #{issue.number} not found")
		end
		log.info "Load pull request #{issue.number}: {pr.title.split("\n").first}"
		pr.repo = job.repo
		pulls.save pr
		get_pull_events(job, pr)
		return pr
	end

	# Load pull events.
	private fun get_pull_events(job: LoaderJob, pull: PullRequest) do
		if config.no_events then return

		var api = config.wallet.api
		for event in api.get_issue_events(job.repo.full_name, pull.number) do
			event.repo = job.repo
			issue_events.save event
		end
	end

	# Check if the API is in error state then abort
	fun check_error(api: GithubAPI, message: nullable String) do
		var err = api.last_error
		if err != null then
			error message or else err.message
		end
	end

	# Logger shortcut
	fun log: PopLogger do return config.logger

	# Display a error and exit
	fun error(msg: String) do
		log.error "Error: {msg}"
		exit 1
	end
end
lib/github/loader.nit:200,1--424,3